state-record-0.0.1: Better records for State monad states

Data.Record.StateFields

Synopsis

Documentation

data Field c a Source

A primitive field descriptor.

Instances

record :: String -> Q [Dec] -> Q [Dec]Source

Modify the given 'data' or 'newtype' declaration so that all field names are prefixed with an underscore followed by the given string, and generate declarations of field descriptors for all fields, each bound to the corresponding field name prefixed with the given string (but no underscore).

Example usage (this goes at the top level of a module):

 record "foo" [d| data Foo = Foo { bar :: Int, baz :: Int } |]

Note: the second parameter is Q [Dec] because this is what the [d| |] form returns, which is the most convenient way to use this function. However, the list must contain exactly one declaration, and it must be a 'data' or 'newtype' declaration.

Note: in addition to adding the given prefix to each name, the first character of the original name is capitalized.

class SomeField f whereSource

The class of field descriptors. A descriptor of type 'f a b' refers to a field of type b nested somewhere within a record of type a.

Methods

getField :: f a b -> a -> bSource

Get the value of a field.

putField :: f a b -> b -> a -> aSource

Put a value into a field.

Instances

modField :: SomeField f => f s a -> (a -> a) -> s -> sSource

Modify the value of a field by applying a function.

data FieldPath f g b a c Source

A compound field descriptor.

Instances

(//) :: (SomeField f, SomeField g) => f a b -> g b c -> FieldPath f g b a cSource

Join two field descriptors into a compound. // is left-associative with precedence level 9.

getf :: (MonadState s m, SomeField f) => f s a -> m aSource

Get the value of a field from the state.

putf :: (MonadState s m, SomeField f) => f s a -> a -> m ()Source

Put a value into a field in the state.

modf :: (MonadState s m, SomeField f) => f s a -> (a -> a) -> m ()Source

Modify the value of a field in the state by applying a function.

enter :: (MonadState s m, SomeField f) => f s a -> State a b -> m bSource

Enter the context of a field and run a stateful computation there.

enterT :: (Monad m, SomeField f) => f s a -> StateT a m b -> StateT s m bSource

Like enter, but allows the stateful computation on the field to share the same underlying monad as the enclosing record.