references-0.2.1.2: Generalization of lenses, folds and traversals to handle monads and addition.

Safe HaskellNone
LanguageHaskell98

Control.Reference.Predefined

Contents

Description

Predefined references for commonly used data structures and reference generators.

When defining lenses one should use the more general types. For instance Lens instead of the more strict Lens'. This way references with different m1 and m2 monads can be combined if there is a monad m' for MMorph m1 m' and MMorph m2 m'.

Synopsis

Trivial references

self :: Lens a b a b Source

An identical lens. Accesses the context.

self & a = a & self = a

emptyRef :: Simple RefPlus s a Source

An empty reference that do not traverse anything

emptyRef &+& a = a &+& emptyRef = a
a & emptyRef = emptyRef & a = emptyRef

Reference generators

traverse :: Traversable t => Traversal (t a) (t b) a b Source

Generates a traversal for any Traversable Functor

iso :: (a -> b) -> (b -> a) -> Simple Iso a b Source

Generate a lens from a pair of inverse functions

iso' :: (a -> b) -> (a' -> b') -> (b -> a) -> (b' -> a') -> Iso a a' b b' Source

lens :: (s -> a) -> (b -> s -> t) -> Lens s t a b Source

Generates a lens from a getter and a setter

partial :: (s -> Either t (a, b -> t)) -> Partial s t a b Source

Creates a polymorphic partial lense

Either t a is used instead of Maybe a to permit the types of s and t to differ.

prism :: (a -> s) -> (b -> t) -> (s -> Either t a) -> (t -> Maybe b) -> Prism s t a b Source

Creates a polymorphic partial lens that can be turned to give a total lens

simplePrism :: (a -> s) -> (s -> Maybe a) -> Prism s s a a Source

Creates a monomorphic partial lens that can be turned to give a total lens

simplePartial :: (s -> Maybe (a, a -> s)) -> Partial s s a a Source

Creates a simple partial lens

fromLens :: (forall f. Functor f => (a -> f b) -> s -> f t) -> Lens s t a b Source

Clones a lens from Control.Lens

fromTraversal :: (forall f. Applicative f => (a -> f b) -> s -> f t) -> Traversal s t a b Source

Clones a traversal from Control.Lens

filtered :: (a -> Bool) -> Simple RefPlus a a Source

Filters the traversed elements with a given predicate. Has specific versions for traversals and partial lenses.

References for simple data structures

just :: Prism (Maybe a) (Maybe b) a b Source

A partial lens to access the value that may not exist

right :: Prism (Either a b) (Either a c) b c Source

A partial lens to access the right option of an Either

left :: Prism (Either a c) (Either b c) a b Source

A partial lens to access the left option of an Either

anyway :: Lens (Either a a) (Either b b) a b Source

Access the value that is in the left or right state of an Either

both :: Traversal (a, a) (b, b) a b Source

References both elements of a tuple

atHead :: Simple Lens [a] (Maybe a) Source

References the head of a list

headElem :: Simple Partial [a] a Source

References the element at the head of the list

_tail :: Simple Partial [a] [a] Source

References the tail of a list

dropped :: Int -> Simple Partial [a] [a] Source

References a suffix of a list

view :: Iso [a] [b] (Maybe (a, [a])) (Maybe (b, [b])) Source

Views a list as an optinal pair

text :: Simple Iso String Text Source

An isomorphism between the list and text representation of a string

reversed :: Iso [a] [b] [a] [b] Source

Accesses the reversed version of a list

'turn' reversed == reversed

_numerator :: Integral a => Simple Lens (Ratio a) a Source

Accesses the numerator of a ratio

_denominator :: Integral a => Simple Lens (Ratio a) a Source

Accesses the denominator of a ratio

_realPart :: RealFloat a => Simple Lens (Complex a) a Source

Accesses the real part of a complex number

_imagPart :: RealFloat a => Simple Lens (Complex a) a Source

Accesses the imaginary part of a complex number

_polar :: RealFloat a => Simple Lens (Complex a) (a, a) Source

Accesses the polar representation of a complex number

Stateful references

data Console Source

A dummy object to interact with the user through the console.

Constructors

Console 

consoleLine :: Simple IOLens Console String Source

Interacts with a line of text on the console. Values set are printed, getting is reading from the console.

mvar :: Simple IOLens (MVar a) a Source

Access a value inside an MVar. Setting is not atomic. If there is two supplier that may set the accessed value, one may block and can corrupt the following updates.

Reads and updates are done in sequence, always using consistent data.

ioref :: Simple IOLens (IORef a) a Source

Access the value of an IORef.

state :: forall s m a. Monad m => Simple (StateLens s m) a s Source

Access the state inside a state monad (from any context).

stRef :: Simple (STLens s) (STRef s a) a Source

Access the value inside an STRef