references-0.3.1.1: Selectors for reading and updating data.

Safe HaskellSafe
LanguageHaskell98

Control.Reference.Types

Contents

Description

This module defines the polymorphic types of the created references. The actual type of a reference can be different for every usage, the polymorphic type gives a lower bound on the actual one.

Synopsis

Documentation

type Simple t s a = t s s a a Source #

A monomorph Lens, Traversal, Partial, etc... Setting or updating does not change the type of the base.

type Getter r s t a b = Reference MU r MU MU s t a b Source #

type Setter w s t a b = Reference w MU MU MU s t a b Source #

Pure references

type Iso s t a b = forall w r w' r'. (RefMonads w r, RefMonads w' r') => Reference w r w' r' s t a b Source #

A two-way Reference that represents an isomorphism between two datatypes. Can be used to access the same data in two different representations.

type Prism s t a b = forall w r w' r'. (RefMonads w r, RefMonads w' r', MonadPlus r, Morph Maybe r, MonadPlus w', Morph Maybe w') => Reference w r w' r' s t a b Source #

A partial lens that can be turned to get a total lens.

type Lens s t a b = forall w r. RefMonads w r => Reference w r MU MU s t a b Source #

A Reference that can access a part of data that exists in the context. A Lens can have any read and write semantics that a Reference can have.

type RefPlus s t a b = forall w r. (RefMonads w r, MonadPlus r) => Reference w r MU MU s t a b Source #

A reference that may not have the accessed element, and that can look for the accessed element in multiple locations.

type Partial s t a b = forall w r. (Functor w, Applicative w, Monad w, Functor r, Applicative r, MonadPlus r, Morph Maybe r) => Reference w r MU MU s t a b Source #

Partial lens. A Reference that can access data that may not exist in the context. Every lens is a partial lens.

Any reference that is a partial lens should only perform the action given to its updateRef function if it can get a value (the value returned by getRef is not the lifted form of Nothing).

type Traversal s t a b = forall w r. (RefMonads w r, MonadPlus r, Morph Maybe r, Morph [] r) => Reference w r MU MU s t a b Source #

A reference that can access data that is available in a number of instances inside the contexts.

Any reference that is a Traversal should perform the action given to its updater in the exactly the same number of times that is the number of the values returned by it's getRef function.

References for IO

class (Morph IO w, Morph IO r, MorphControl IO w, MorphControl IO r) => IOMonads w r Source #

Instances

type IOLens s t a b = forall w r. (RefMonads w r, IOMonads w r) => Reference w r MU MU s t a b Source #

A reference that can access mutable data.

type IOPartial s t a b = forall w r. (RefMonads w r, IOMonads w r, MonadPlus r, Morph Maybe r) => Reference w r MU MU s t a b Source #

A reference that can access mutable data that may not exist in the context.

type IOTraversal s t a b = forall w r. (RefMonads w r, IOMonads w r, MonadPlus r, Morph Maybe r, Morph [] r) => Reference w r MU MU s t a b Source #

References for StateT

type StateLens st m s t a b = forall w r. (RefMonads w r, Morph (StateT st m) w, Morph (StateT st m) r) => Reference w r MU MU s t a b Source #

A reference that can access a value inside a StateT transformed monad.

type StatePartial st m s t a b = forall w r. (RefMonads w r, Morph (StateT st m) w, MonadPlus r, Morph Maybe r, Morph (StateT st m) r) => Reference w r MU MU s t a b Source #

A reference that can access a value inside a StateT transformed monad that may not exist.

type StateTraversal st m s t a b = forall w r. (RefMonads w r, Morph (StateT st m) w, MonadPlus r, Morph Maybe r, Morph [] r, Morph (StateT st m) r) => Reference w r MU MU s t a b Source #

A reference that can access a value inside a StateT transformed monad that may exist in multiple instances.

References for WriterT

type WriterLens st m s t a b = forall w r. (RefMonads w r, Morph (WriterT st m) w, Morph (WriterT st m) r) => Reference w r MU MU s t a b Source #

A reference that can access a value inside a WriterT transformed monad.

type WriterPartial st m s t a b = forall w r. (RefMonads w r, Morph (WriterT st m) w, MonadPlus r, Morph Maybe r, Morph (WriterT st m) r) => Reference w r MU MU s t a b Source #

A reference that can access a value inside a WriterT transformed monad that may not exist.

type WriterTraversal st m s t a b = forall w r. (RefMonads w r, Morph (WriterT st m) w, MonadPlus r, Morph Maybe r, Morph [] r, Morph (WriterT st m) r) => Reference w r MU MU s t a b Source #

A reference that can access a value inside a WriteT transformed monad that may exist in multiple instances.

References for ST

type STLens st s t a b = forall w r. (RefMonads w r, Morph (ST st) w, Morph (ST st) r) => Reference w r MU MU s t a b Source #

A reference that can access a value inside an ST transformed monad.

type STPartial st s t a b = forall w r. (RefMonads w r, Morph (ST st) w, MonadPlus r, Morph Maybe r, Morph (ST st) r) => Reference w r MU MU s t a b Source #

A reference that can access a value inside an ST transformed monad that may not exist.

type STTraversal st s t a b = forall w r. (RefMonads w r, Morph (ST st) w, MonadPlus r, Morph Maybe r, Morph [] r, Morph (ST st) r) => Reference w r MU MU s t a b Source #

A reference that can access a value inside an ST transformed monad that may exist in multiple instances.

class MorphControl m1 m2 where Source #

A class for representing calculation in a simpler monad.

pullBack . sink === id

Minimal complete definition

sink, pullBack

Associated Types

data MSt m1 m2 a :: * Source #

Methods

sink :: m2 a -> m1 (MSt m1 m2 a) Source #

pullBack :: m1 (MSt m1 m2 a) -> m2 a Source #

Instances

MorphControl IO IO Source # 

Associated Types

data MSt (IO :: * -> *) (IO :: * -> *) a :: * Source #

Methods

sink :: IO a -> IO (MSt IO IO a) Source #

pullBack :: IO (MSt IO IO a) -> IO a Source #

Monad m => MorphControl m (MU *) Source # 

Associated Types

data MSt (m :: * -> *) (MU * :: * -> *) a :: * Source #

Methods

sink :: MU * a -> m (MSt m (MU *) a) Source #

pullBack :: m (MSt m (MU *) a) -> MU * a Source #

Monad m => MorphControl m (ListT m) Source # 

Associated Types

data MSt (m :: * -> *) (ListT m :: * -> *) a :: * Source #

Methods

sink :: ListT m a -> m (MSt m (ListT m) a) Source #

pullBack :: m (MSt m (ListT m) a) -> ListT m a Source #

Monad m => MorphControl m (MaybeT m) Source # 

Associated Types

data MSt (m :: * -> *) (MaybeT m :: * -> *) a :: * Source #

Methods

sink :: MaybeT m a -> m (MSt m (MaybeT m) a) Source #

pullBack :: m (MSt m (MaybeT m) a) -> MaybeT m a Source #