| Safe Haskell | Safe |
|---|---|
| Language | Haskell98 |
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.
- data Reference w r w' r' s t a b = Reference {}
- type IndexedReference i w r w' r' s t a b = i -> Reference w r w' r' s t a b
- bireference :: (RefMonads w r, RefMonads w' r') => (s -> r a) -> (b -> s -> w t) -> ((a -> w b) -> s -> w t) -> (a -> r' s) -> (t -> a -> w' b) -> ((s -> w' t) -> a -> w' b) -> Reference w r w' r' s t a b
- reference :: RefMonads w r => (s -> r a) -> (b -> s -> w t) -> ((a -> w b) -> s -> w t) -> Reference w r MU MU s t a b
- rawReference :: (RefMonads w r, RefMonads w' r') => (forall x. (a -> r x) -> s -> r x) -> (b -> s -> w t) -> ((a -> w b) -> s -> w t) -> (forall x. (s -> r' x) -> a -> r' x) -> (t -> a -> w' b) -> ((s -> w' t) -> a -> w' b) -> Reference w r w' r' s t a b
- referenceWithClose :: RefMonads w r => (s -> r a) -> (s -> r ()) -> (b -> s -> w t) -> (s -> w ()) -> ((a -> w b) -> s -> w t) -> (s -> w ()) -> Reference w r MU MU s t a b
- type RefMonads w r = (Functor w, Applicative w, Monad w, Functor r, Applicative r, Monad r)
- type MU = Proxy
- unusableOp :: a -> b -> MU c
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
| |
type IndexedReference i w r w' r' s t a b = i -> Reference w r w' r' s t a b 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.
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.
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)
unusableOp :: a -> b -> MU c Source #