references-0.1.0.0: Generalization of lenses, folds and traversals for haskell

Safe HaskellSafe-Inferred
LanguageHaskell98

Control.Reference.Representation

Description

This module declares the representation and basic classes of references.

Synopsis

Documentation

data Reference wm rm s t a b Source

A reference is an accessor to a part or different view of some data. The reference, unlike the lens has a separate getter, setter and updater.

Reference laws

As the references are generalizations of lenses, they should conform to the lens laws:

1) You get back what you put in:

lensSet l a s >>= lensGet l ≡ a

2) Putting back what you got doesn't change anything:

lensGet l a >>= b -> lensSet l b s ≡ s

3) Setting twice is the same as setting once:

lensSet l a s >>= lensSet l b ≡ lensSet l b s

But because they are more powerful than lenses, they should be more responsible.

4) Updating something is the same as getting and then setting:

lensGet l a >>= f >>= b -> lensSet l b s ≡ lensUpdate b s

Type arguments

wm
Writer monad, controls how the value can be reassembled when the part is changed. Usually Identity.
rm
Reader monad. Controls how part of the value can be accessed. See Lens, LensPart and Traversal
s
The original context.
t
The context after replacing the accessed part to something of type b.
a
The accessed part.
b
The accessed part can be changed to this.

Constructors

Reference 

Fields

lensGet :: s -> rm a

Getter for the lens

lensSet :: b -> s -> wm t

Setter for the lens

lensUpdate :: (a -> wm b) -> s -> wm t

Updater for the lens. Handles monadic update functions.

type Simple t s a = t s s a a Source

A monomorph Lens, Traversal, LensPart, etc... Setting or updating does not change the type of the base.

type Simple' w t s a = t w s s a a Source

A monomorph Lens', Traversal', LensPart', etc... Setting or updating does not change the type of the base. Needs LiberalTypeSynonyms language extension

type SimpleRef wm rm s a = Reference wm rm s s a a Source

type Lens = Reference Identity Identity Source

The Lens is a reference that represents an 1 to 1 relationship.

type Lens' w = Reference w Identity Source

type Traversal = Reference Identity [] Source

The Traversal is a reference that represents an 1 to any relationship.

type LensPart = Reference Identity Maybe Source

The parital lens is a reference that represents an 1 to 0..1 relationship.

class Monad (ResultMonad m1 m2) => MonadCompose m1 m2 where Source

Combines the functionality of two monads into one. Has two functions that lift a monadic action into the result monad.

Associated Types

type ResultMonad m1 m2 :: * -> * Source

The type of the result monad

data ComposePhantom m1 m2 :: * Source

A phantom type to help coercions. Coercions are often needed when only one of the lifting functions are used.

Methods

newComposePhantom :: ComposePhantom m1 m2 Source

Creates a new phantom variable to state that two liftings result in the same type.

liftMC1 :: ComposePhantom m1 m2 -> m1 a -> ResultMonad m1 m2 a Source

Lifts the first monad into the result monad.

liftMC2 :: ComposePhantom m1 m2 -> m2 a -> ResultMonad m1 m2 a Source

Lifts the second monad into the result monad.

Instances

MonadCompose [] [] 
MonadCompose [] IO 
MonadCompose [] Maybe 
MonadCompose [] Identity 
MonadCompose IO [] 
MonadCompose IO IO 
MonadCompose IO Maybe 
MonadCompose IO Identity 
MonadCompose Maybe [] 
MonadCompose Maybe IO 
MonadCompose Maybe Maybe 
MonadCompose Maybe Identity 
MonadCompose Identity [] 
MonadCompose Identity IO 
MonadCompose Identity Maybe 
MonadCompose Identity Identity 
MonadCompose [] (ListT IO) 
MonadCompose [] (MaybeT IO) 
MonadCompose IO (ListT IO) 
MonadCompose IO (MaybeT IO) 
MonadCompose Maybe (ListT IO) 
MonadCompose Maybe (MaybeT IO) 
MonadCompose Identity (ListT IO) 
MonadCompose Identity (MaybeT IO) 
MonadCompose (ListT IO) [] 
MonadCompose (ListT IO) IO 
MonadCompose (ListT IO) Maybe 
MonadCompose (ListT IO) Identity 
MonadCompose (MaybeT IO) [] 
MonadCompose (MaybeT IO) IO 
MonadCompose (MaybeT IO) Maybe 
MonadCompose (MaybeT IO) Identity 
MonadCompose (ListT IO) (ListT IO) 
MonadCompose (ListT IO) (MaybeT IO) 
MonadCompose (MaybeT IO) (ListT IO) 
MonadCompose (MaybeT IO) (MaybeT IO) 

class MonadSubsume m1 m2 where Source

States that m1 can be represented with m2

Methods

liftMS :: m1 a -> m2 a Source

Lifts the first monad into the second.

Instances

MonadSubsume [] [] 
MonadSubsume IO IO 
MonadSubsume Maybe [] 
MonadSubsume Maybe Maybe 
MonadSubsume Identity [] 
MonadSubsume Identity IO 
MonadSubsume Identity Maybe 
MonadSubsume Identity Identity 
MonadSubsume [] (ListT IO) 
MonadSubsume IO (ListT IO) 
MonadSubsume IO (MaybeT IO) 
MonadSubsume Maybe (ListT IO) 
MonadSubsume Maybe (MaybeT IO) 
MonadSubsume Identity (ListT IO) 
MonadSubsume Identity (MaybeT IO) 
MonadSubsume (ListT IO) (ListT IO) 
MonadSubsume (MaybeT IO) (ListT IO) 
MonadSubsume (MaybeT IO) (MaybeT IO)