references-0.3.1.1: Selectors for reading and updating data.

Safe HaskellSafe
LanguageHaskell98

Control.Reference.Representation

Description

This module declares the representation and basic classes of references. Supplies primitive functions to create references.

This module should not be imported directly.

Synopsis

Documentation

data Reference w r w' r' s t a b Source #

A reference is an accessor to a part or different view of some data. The referenc has a separate getter, setter and updater. In some cases, the semantics are a bit different

Reference laws

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

1) You get back what you put in:

refSet l a s >>= refGet l return ≡ a

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

refGet l return a >>= \b -> refSet l b s ≡ s

3) Setting twice is the same as setting once:

refSet l a s >>= refSet l b ≡ refSet l b s

But because update, set and get are different operations, .

4) Updating something is the same as getting and then setting (if the reader and writer monads are the same, or one can be converted into the other):

refGet l a >>= f >>= \b -> refSet l b s ≡ refUpdate l f s

This has some consequences. For example lensUpdate l id = return.

Type arguments of Reference

w
Writer monad, controls how the value can be reassembled when the part is changed. See differences between Lens, IOLens and StateLens
r
Reader monad. Controls how part of the value can be asked. See differences between Lens, Partial and Traversal
w'
Backward writer monad. See turn
r'
Backward reader monad. See turn
s
The type of the original context.
t
The after replacing the accessed part to something of type b the type of the context changes to t.
a
The type of the accessed part.
b
The accessed part can be changed to something of this type.

Usually s and b determines t, t and a determines s.

The reader monad usually have more information (Morph w r).

Constructors

Reference 

Fields

  • refGet :: forall x. (a -> r x) -> s -> r x

    Getter for the lens. Takes a monadic function and runs it on the accessed value. This is necessary to run actions after a read.

  • refSet :: b -> s -> w t

    Setter for the lens

  • refUpdate :: (a -> w b) -> s -> w t

    Updater for the lens. Handles monadic update functions.

  • refGet' :: forall x. (s -> r' x) -> a -> r' x
     
  • refSet' :: t -> a -> w' b
     
  • refUpdate' :: (s -> w' t) -> a -> w' b
     

type IndexedReference i w r w' r' s t a b = i -> Reference w r w' r' s t a b Source #

bireference Source #

Arguments

:: (RefMonads w r, RefMonads w' r') 
=> (s -> r a)

Getter

-> (b -> s -> w t)

Setter

-> ((a -> w b) -> s -> w t)

Updater

-> (a -> r' s)

Backward getter

-> (t -> a -> w' b)

Backward setter

-> ((s -> w' t) -> a -> w' b)

Backward updater

-> Reference w r w' r' s t a b 

reference Source #

Arguments

:: RefMonads w r 
=> (s -> r a)

Getter

-> (b -> s -> w t)

Setter

-> ((a -> w b) -> s -> w t)

Updater

-> Reference w r MU MU s t a b 

Creates a reference.

rawReference Source #

Arguments

:: (RefMonads w r, RefMonads w' r') 
=> (forall x. (a -> r x) -> s -> r x)

Getter

-> (b -> s -> w t)

Setter

-> ((a -> w b) -> s -> w t)

Updater

-> (forall x. (s -> r' x) -> a -> r' x)

Backward getter

-> (t -> a -> w' b)

Backward setter

-> ((s -> w' t) -> a -> w' b)

Backward updater

-> Reference w r w' r' s t a b 

Creates a reference where all operations are added in their original form.

The use of this method is not suggested, because it is closely related to the representation of the references.

referenceWithClose Source #

Arguments

:: (Functor w, Applicative w, Monad w, Functor r, Applicative r, Monad r) 
=> (s -> r a)

Getter

-> (s -> r ())

Close after getting

-> (b -> s -> w t)

Setter

-> (s -> w ())

Close after setting

-> ((a -> w b) -> s -> w t)

Updater

-> (s -> w ())

Close after updating

-> Reference w r MU MU s t a b 

Creates a reference with explicit close operations that are executed after the data is accessed.

class (Functor w, Applicative w, Monad w, Functor r, Applicative r, Monad r) => RefMonads w r Source #

A simple class to enforce that both reader and writer semantics of the reference are Monads (as well as Applicatives and Functors)

Instances

type MU = Proxy Source #

unusableOp :: a -> b -> MU c Source #