{- | This module provides a simple abstract data type for a piece of a data stucture that can be read from and written to. In contrast to "Data.Accessor.Basic" it is intended for unqualified import. -} module Data.Accessor ( Accessor, accessor, setVal, getVal, getA, putA, (=:), modA, (.>), (<.), ) where import qualified Data.Accessor.Basic as Accessor import qualified Data.Accessor.MonadState as State import Control.Monad.State (MonadState, ) -- |An @Accessor s a@ is an object that encodes how to -- get and put a subject of type @a@ out of/into an object -- of type @s@. -- -- In order for an instance of this data structure @a@ to be -- an 'Accessor', it must obey the following laws: -- -- > getVal a (setVal a x s) = x -- > setVal a (getVal a s) s = s type Accessor s a = Accessor.T s a -- |Construct an 'Accessor' from a @get@ and a @set@ method. -- accessor :: (s -> a) {- ^ get method -} -> (a -> s -> s) {- ^ set method -} -> Accessor s a accessor = flip Accessor.fromSetGet -- |Get a value from a record field that is specified by an Accessor getVal :: Accessor s a {- ^ record field -} -> s {- ^ record -} -> a {- ^ value of the field in the record -} getVal = Accessor.get -- |Set a value of a record field that is specified by an Accessor setVal :: Accessor s a {- ^ record field @f@ -} -> a {- ^ value @x@ to be set -} -> s {- ^ original record -} -> s {- ^ new record with field @f@ changed to @x@ -} setVal = Accessor.set infixl 9 .> {- | Accessor composition: Combine an accessor with an accessor to a sub-field. Speak \"stack\". -} (.>) :: Accessor a b -> Accessor b c -> Accessor a c (.>) = (Accessor..>) infixr 9 <. {- | Accessor composition the other direction. > (<.) = flip (.>) -} (<.) :: Accessor b c -> Accessor a b -> Accessor a c (<.) = (Accessor.<.) infix 1 =: -- |An \"assignment operator\" for state monads. -- -- > (=:) = putA (=:) :: MonadState s m => Accessor s a -> a -> m () (=:) = putA -- |A structural dereference function for state monads. getA :: MonadState s m => Accessor s a -> m a getA = State.get -- |A structural assignment function for state monads. putA :: MonadState s m => Accessor s a -> a -> m () putA = State.set -- |A structural modification function for state monads. modA :: MonadState s m => Accessor s a -> (a -> a) -> m () modA = State.modify