module Data.Accessor.Example where import Data.Accessor.Basic ((.>), ($%), (^.), (^:), (^=), ) import Data.Accessor.Tuple (first, second, ) import qualified Data.Accessor.Basic as Accessor import qualified Data.Accessor.BinaryRead as Read import qualified Data.Accessor.Show as Show import Data.Accessor.MonadState ((%=), (%:), ) import qualified Data.Accessor.MonadState as AState import Control.Monad.State (State) import Data.Char (ord, ) import Prelude hiding (init) {- * Example accesses -} {- | Example of using 'set', 'get', 'modify'. -} plain :: Int plain = Accessor.get second $ Accessor.modify second succ $ Accessor.set first 'a' $ ('b',7) state :: State (Char,Int) Int state = do AState.set first 'a' AState.modify second succ AState.get second stateInfix :: State ((Char, Int), String) Int stateInfix = do str <- AState.get second first.>first %= 'a' first.>second %: succ first.>first %= 'b' second %= '!' : str AState.get (first.>second) init :: (Char,Int) init = Accessor.compose [Accessor.set first 'b', Accessor.modify first succ, Accessor.set second 7] (undefined,undefined) -- setMany [first 'b', second 7] (undefined,undefined) initInfix :: (Char,Int) initInfix = (undefined,undefined) $% first ^= 'b' $% first ^: succ $% second ^= 7 read :: Maybe ((Char,Int), Read.Stream) read = Read.runParser (Read.record [Read.field first, Read.field second]) ((undefined,undefined), fromIntegral (ord 'c') : 59 : 154 : 202 : 0 : []) infix0 :: Int infix0 = (('b',7),"hallo")^.first^.second infix1 :: ((Char, Int), String) infix1 = (('b',7),"hallo")$%first^:second^:(1+) infix2 :: ((Char, Int), String) infix2 = (('b',7),"hallo")$%first^:second^=10 infix3 :: Int infix3 = (('b',7),"hallo")^.(first.>second) infix4 :: ((Char, Int), String) infix4 = (('b',7),"hallo")$%(first.>second)^:(1+) showsPair :: Int -> (Char, Int) -> ShowS showsPair = Show.showsPrec [Show.field "first" first, Show.field "second" second] "init" init show0 :: String show0 = showsPair 11 init "" show1 :: String show1 = showsPair 5 ('d',8) ""