references-0.1.0.0: Generalization of lenses, folds and traversals for haskell

Safe HaskellNone
LanguageHaskell98

Control.Reference.Predefined

Contents

Description

Predefined references.

_Naming convention_: If there is a reference foo and a reference foo' then foo' is the restricted version of foo. If foo is generic in it's writer monad foo' has the simplest writer monad that suffices.

Synopsis

Trivial references

simple :: Monad w => Lens' w a b a b Source

An identical lens. Accesses the context.

simple' :: Lens a b a b Source

emptyRef :: (Monad w, Monad r, MonadPlus r) => SimpleRef w r s a Source

An empty reference that do not traverse anything

Reference generators

traverse :: (Monad w, Traversable t) => Traversal' w (t a) (t b) a b Source

Generates a traversal on any traversable

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

lens :: Monad w => (s -> a) -> (b -> s -> t) -> Lens' w s t a b Source

Generates a lens from a getter and a setter

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

partial :: Monad w => (s -> Maybe a) -> (a -> s -> s) -> Simple' w LensPart' s a Source

Creates a monomorphic partial lens

partial' :: (s -> Maybe a) -> (a -> s -> s) -> Simple LensPart s a Source

polyPartial :: Monad w => (s -> Either (w t) (a, b -> w t)) -> LensPart' w s t a b Source

Creates a polymorphic partial lense

polyPartial' :: (s -> Either t (a, b -> t)) -> LensPart s t a b Source

fromLens :: (Functor w, Monad w) => Lens s s a a -> Lens s t a b -> Lens' w s t a b Source

Generate a reference from a simple lens from Lens

fromTraversal :: (Applicative w, Monad w) => Traversal s s a a -> Traversal s t a b -> Traversal' w s t a b Source

Generate a reference from a simple lens from Lens

filtered :: (Applicative w, Monad w, MonadPlus r) => (a -> Bool) -> SimpleRef w r a a Source

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

filteredTrav :: (Applicative w, Monad w) => (a -> Bool) -> Simple' w Traversal' a a Source

Filters a traversal

filteredPartial :: (Applicative w, Monad w) => (a -> Bool) -> Simple' w LensPart' a a Source

Filters a partial lens

iso :: Monad w => (a -> b) -> (b -> a) -> Simple' w Lens' a b Source

Generate a lens from a pair of inverse functions

iso' :: (a -> b) -> (b -> a) -> Simple Lens a b Source

References for simple data structures

just :: Monad w => LensPart' w (Maybe a) (Maybe b) a b Source

A partial lens to access the value that may not exist

right :: Monad w => LensPart' w (Either a b) (Either a c) b c Source

A partial lens to access the right option of an Either

right' :: LensPart (Either a b) (Either a c) b c Source

left :: Monad w => LensPart' w (Either a c) (Either b c) a b Source

A partial lens to access the left option of an Either

left' :: LensPart (Either a c) (Either b c) a b Source

anyway :: Monad w => Lens' w (Either a a) (Either b b) a b Source

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

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

both :: Monad w => Traversal' w (a, a) (b, b) a b Source

References both elements of a tuple

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

_head :: Monad w => Simple' w LensPart' [a] a Source

References the head of a list

_tail :: Monad w => Simple' w LensPart' [a] [a] Source

References the tail of a list

class Association e where Source

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

Minimal complete definition

element

Associated Types

type AssocIndex e :: * Source

type AssocElem e :: * Source

Instances

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

Stateful references

mvar :: SimpleRef IO IO (MVar a) a Source

Access a value inside an MVar. Writing should only be used for initial assignment or parts of the program will block infinitely. Reads and updates are done in sequence, always using consistent data.

mvarNow :: SimpleRef IO (MaybeT IO) (MVar a) a Source

Access the current value inside an MVar. Never blocks.

ioref :: SimpleRef IO IO (IORef a) a Source

Access the value of an IORef.

state :: SimpleRef (State s) (State s) a s Source

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