data-accessor-0.2.1: Utilities for accessing and manipulating fields of recordsSource codeContentsIndex
Data.Accessor
Description
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.
Synopsis
type Accessor r a = T r a
accessor :: (r -> a) -> (a -> r -> r) -> Accessor r a
setVal :: Accessor r a -> a -> r -> r
(^=) :: T r a -> a -> r -> r
getVal :: Accessor r a -> r -> a
(^.) :: r -> T r a -> a
(^:) :: T r a -> (a -> a) -> r -> r
getA :: Monad m => Accessor r a -> StateT r m a
putA :: Monad m => Accessor r a -> a -> StateT r m ()
(=:) :: Monad m => Accessor r a -> a -> StateT r m ()
(%=) :: Monad m => T r a -> a -> StateT r m ()
modA :: Monad m => Accessor r a -> (a -> a) -> StateT r m ()
(%:) :: Monad m => T r a -> (a -> a) -> StateT r m ()
(.>) :: Accessor a b -> Accessor b c -> Accessor a c
(<.) :: Accessor b c -> Accessor a b -> Accessor a c
Documentation
type Accessor r a = T r aSource

An Accessor r 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 r) = x
 setVal a (getVal a r) r = r
accessorSource
::
=> r -> aget method
-> a -> r -> rset method
-> Accessor r a
Construct an Accessor from a get and a set method.
setValSource
::
=> Accessor r arecord field f
-> avalue x to be set
-> roriginal record
-> rnew record with field f changed to x
Set a value of a record field that is specified by an Accessor
(^=) :: T r a -> a -> r -> rSource
set as infix operator. This lets us write first ^= 2+3 $ second ^= 5+7 $ record.
getValSource
::
=> Accessor r arecord field
-> rrecord
-> avalue of the field in the record
Get a value from a record field that is specified by an Accessor
(^.) :: r -> T r a -> aSource
get as infix operator. This lets us write record^.field^.subfield. This imitates Modula II syntax.
(^:) :: T r a -> (a -> a) -> r -> rSource
modify as infix operator. This lets us write field^:subfield^:(2*) $ record, record$%field^:subfield^:(2*) or record$%field^:subfield^:(const 1).
getA :: Monad m => Accessor r a -> StateT r m aSource
A structural dereference function for state monads.
putA :: Monad m => Accessor r a -> a -> StateT r m ()Source
A structural assignment function for state monads.
(=:) :: Monad m => Accessor r a -> a -> StateT r m ()Source

An "assignment operator" for state monads.

 (=:) = putA
(%=) :: Monad m => T r a -> a -> StateT r m ()Source
Infix variant of set.
modA :: Monad m => Accessor r a -> (a -> a) -> StateT r m ()Source
A structural modification function for state monads.
(%:) :: Monad m => T r a -> (a -> a) -> StateT r m ()Source
Infix variant of modify.
(.>) :: Accessor a b -> Accessor b c -> Accessor a cSource
Accessor composition: Combine an accessor with an accessor to a sub-field. Speak "stack".
(<.) :: Accessor b c -> Accessor a b -> Accessor a cSource

Accessor composition the other direction.

 (<.) = flip (.>)
Produced by Haddock version 2.4.2