| 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 :: (Functor w, Applicative w, Monad w, Functor r, Applicative r, Monad 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
- class (Functor w, Applicative w, Monad w, Functor r, Applicative r, Monad r) => RefMonads w 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
Reference laws
As the references are generalizations of lenses, they should conform to the lens laws:
1) You get back what you put in:
refSetl a s >>=refGetl return ≡ a
2) Putting back what you got doesn't change anything:
refGetl return a >>= \b ->refSetl b s ≡ s
3) Setting twice is the same as setting once:
refSetl a s >>=refSetl b ≡refSetl 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):
refGetl a >>= f >>= \b ->refSetl b s ≡refUpdatel 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,IOLensandStateLens r- Reader monad. Controls how part of the value can be asked.
See differences between
Lens,PartialandTraversal 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
bthe type of the context changes tot. 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
| |
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
| :: (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
| (Functor w, Applicative w, Monad w, Functor r, Applicative r, Monad r) => RefMonads w r Source # | |
unusableOp :: a -> b -> MU c Source #