references-0.3.3.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

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

:: RefMonads w 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.

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

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

type MU = Proxy Source #

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