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

Safe HaskellSafe-Inferred
LanguageHaskell98

Control.Reference.Predefined

Contents

Description

Predefined references for commonly used data structures.

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

An identical lens. Accesses the context.

self & a = a & self = a

emptyRef :: Simple RefPlus s a

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

Generates a traversal for any Traversable Functor

iso :: (a -> b) -> (b -> a) -> Lens a a b b

Generate a lens from a pair of inverse functions

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

Generates a lens from a getter and a setter

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

Creates a monomorphic partial lense

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

Creates a simple partial lens

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

Clones a lens from Control.Lens

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

Clones a traversal from Control.Lens

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

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

References for simple data structures

just :: Partial (Maybe a) (Maybe b) a b

A partial lens to access the value that may not exist

right :: Partial (Either a b) (Either a c) b c

A partial lens to access the right option of an Either

left :: Partial (Either a c) (Either b c) a b

A partial lens to access the left option of an Either

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

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

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

References both elements of a tuple

_head :: Simple Partial [a] a

References the head of a list

_tail :: Simple Partial [a] [a]

References the tail of a list

class Association e where

Lenses for given values in a data structure that is indexed by keys.

Associated Types

type AssocIndex e :: *

type AssocElem e :: *

Instances

Association [a] 
Ord k => Association (Map k v) 

Stateful references

data Console

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

Constructors

Console 

consoleLine :: Simple IOLens Console String

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

mvar :: (Functor w, Applicative w, Monad w, MMorph IO w, MonadBaseControl IO w, Functor r, Applicative r, Monad r, MMorph IO r) => Simple (Reference w r) (MVar a) a

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

Access the value of an IORef.

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

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