endo-0.3.0.1: Endomorphism utilities.

Copyright(c) 2015-2016, Peter Trško
LicenseBSD3
Maintainerpeter.trsko@gmail.com
Stabilityexperimental
PortabilityCPP, DeriveFoldable, DeriveFunctor, DeriveDataTypeable, DeriveGeneric, DeriveTraversable, FlexibleInstances, NoImplicitPrelude, TypeFamilies
Safe HaskellNone
LanguageHaskell2010

Data.Monoid.Endo.Apply

Contents

Description

ApplyEndo provides easier endomorphism evaluation in cases when there is an "obvious" default value.

Synopsis

ApplyEndo

newtype ApplyEndo t f a Source

There are cases when it is "obvious" what is the default value, which should be modified by the endomorphism. This type is a result of such endomorphism application and it uses phantom type t as distinguishing property, which decides what is the correct "default value".

Constructors

ApplyEndo 

Fields

applyEndo :: f a
 

Instances

Monad f => Monad (ApplyEndo t f) Source 
Functor f => Functor (ApplyEndo t f) Source 
Applicative f => Applicative (ApplyEndo t f) Source 
Foldable f => Foldable (ApplyEndo t f) Source 
Traversable f => Traversable (ApplyEndo t f) Source 
Generic1 (ApplyEndo t f) Source 
(Data (f a), Typeable (* -> *) f, Typeable * t, Typeable * a) => Data (ApplyEndo t f a) Source 
Generic (ApplyEndo t f a) Source 
MonadState s m => FromEndo (ApplyEndo Modify' m s) Source

Evaluates ApplyEndo in terms of state operation:

fromEndo (Endo f) = ApplyEndo . state $ \s ->
    let s' = f s in s' `seq` (s', s')
MonadState s m => FromEndo (ApplyEndo Modify m s) Source

Evaluates ApplyEndo in terms of state operation:

fromEndo e = ApplyEndo . state $ \s ->
    let s' = appEndo e s in (s', s')
MonadReader r m => FromEndo (ApplyEndo Reader m r) Source

Evaluates ApplyEndo in terms of asks operation:

fromEndo = ApplyEndo . asks . appEndo
(Applicative f, Default a) => FromEndo (ApplyEndo Def f a) Source 
(Applicative f, Monoid a) => FromEndo (ApplyEndo Mempty f a) Source 
type Rep1 (ApplyEndo t f) Source 
type Rep (ApplyEndo t f a) Source 
type EndoOperatedOn (ApplyEndo Modify' m s) = s Source 
type EndoOperatedOn (ApplyEndo Modify m s) = s Source 
type EndoOperatedOn (ApplyEndo Reader m r) = r Source 
type EndoOperatedOn (ApplyEndo Def f a) = a Source 
type EndoOperatedOn (ApplyEndo Mempty f a) = a Source 

apply :: Applicative f => a -> Endo a -> ApplyEndo t f a Source

Apply endomorphism using provided "default" value.

applyF :: Functor f => a -> f (Endo a) -> ApplyEndo t f a Source

Similar as apply, but expects Endo to be wrapped by a Functor.

ApplyEndo Mempty

data Mempty Source

Type tag identifying usage of mempty from Monoid.

applyMempty :: Monoid a => ApplyEndo Mempty f a -> f a Source

Constrained version of applyEndo. Usage example:

applyMempty . fromEndo :: (Applicative f, Monoid a) => Endo a -> f a

applyMempty_ :: Monoid a => ApplyEndo Mempty Identity a -> a Source

Same as applyMempty, but Applicative functor is specialized to Identity functor and evaluated.

Examples:

>>> fromEndoWith applyMempty_ $ foldEndo (+1) [(*10), (+42)] :: Int
421
>>> fromEndoWith applyMempty_ $ dualFoldEndo (+1) [(*10), (+42)] :: Int
52

joinApplyMempty :: (Monad m, Monoid a) => m (ApplyEndo Mempty m a) -> m a Source

Evaluates ApplyEndo in a Monad by joining it with the monad it contains. It can be also viewed as a variant of applyMempty defined as:

joinApplyMempty = (>>= applyMempty)

ApplyEndo Def

Apply endomorphism to a default value def from Default. See also following packages:

Both of those packages provide additional instances to Default type class.

data Def Source

Type tag identifying usage of def from Default.

applyDef :: (Applicative f, Default a) => ApplyEndo Def f a -> f a Source

Constrained version of applyEndo. Usage example:

applyDef . fromEndo :: (Applicative f, Default a) => Endo a -> f a

applyDef_ :: Default a => ApplyEndo Def Identity a -> a Source

Same as applyDef, but Applicative functor is specialized to Identity functor and evaluated.

Examples:

>>> fromEndoWith applyDef_ $ foldEndo (+1) [(*10), (+42)] :: Int
421
>>> fromEndoWith applyDef_ $ dualFoldEndo (+1) [(*10), (+42)] :: Int
52

joinApplyDef :: (Monad m, Default a) => m (ApplyEndo Def m a) -> m a Source

Evaluates ApplyEndo in a Monad by joining it with the monad it contains. It can be also viewed as a variant of applyDef defined as:

joinApplyDef = (>>= applyDef)

ApplyEndo Reader

data Reader Source

Type tag identifying usage of asks operation in FromEndo instance of ApplyEndo.

Instances

applyReader :: MonadReader r m => ApplyEndo Reader m r -> m r Source

Evaluates ApplyEndo in terms of asks operation.

This (->) r is a valid MonadReader instance, therefore, this is a valid use case:

>>> (applyReader . fromEndo $ foldEndo (*10) (+1)) 0 :: Int
10

applyReaderWith :: MonadReader r m => (m r -> a) -> ApplyEndo Reader m r -> a Source

Evaluates ApplyEndo in terms of asks operation and then evaluates the resalt using provided function.

This (->) r is a valid MonadReader instance, therefore, this is a valid use case:

>>> applyReaderWith ($ 0) . fromEndo $ foldEndo (*10) (+1) :: Int
10

joinApplyReader :: MonadReader r m => m (ApplyEndo Reader m r) -> m r Source

Evaluates ApplyEndo in a Monad by joining it with the monad it contains. It can be also viewed as a variant of applyReader defined as:

joinApplyReader = (>>= applyReader)

ApplyEndo Modify

data Modify Source

Type tag identifying usage of state operation in FromEndo instance of ApplyEndo.

Instances

Generic Modify Source 
MonadState s m => FromEndo (ApplyEndo Modify m s) Source

Evaluates ApplyEndo in terms of state operation:

fromEndo e = ApplyEndo . state $ \s ->
    let s' = appEndo e s in (s', s')
type Rep Modify Source 
type EndoOperatedOn (ApplyEndo Modify m s) = s Source 

applyModify :: MonadState s m => ApplyEndo Modify m s -> m s Source

Evaluates ApplyEndo in terms of state operation.

joinApplyModify :: MonadState s m => m (ApplyEndo Modify m s) -> m s Source

Evaluates ApplyEndo in a Monad by joining it with the monad it contains. It can be also viewed as a variant of applyModify defined as:

joinApplyModify = (>>= applyModify)

ApplyEndo Modify'

data Modify' Source

Same as Modify, but strictness is implied.

Instances

Generic Modify' Source 
MonadState s m => FromEndo (ApplyEndo Modify' m s) Source

Evaluates ApplyEndo in terms of state operation:

fromEndo (Endo f) = ApplyEndo . state $ \s ->
    let s' = f s in s' `seq` (s', s')
type Rep Modify' Source 
type EndoOperatedOn (ApplyEndo Modify' m s) = s Source 

applyModify' :: MonadState r m => ApplyEndo Modify' m () -> m () Source

Evaluates ApplyEndo in terms of state operation.

joinApplyModify' :: MonadState r m => m (ApplyEndo Modify' m r) -> m r Source

Evaluates ApplyEndo in a Monad by joining it with the monad it contains. It can be also viewed as a variant of applyModify' defined as:

joinApplyModify' = (>>= applyModify')