Portability | non-portable |
---|---|
Stability | experimental |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | None |
- type Action m s a = forall f r. Effective m r f => (a -> f a) -> s -> f s
- act :: Monad m => (s -> m a) -> IndexPreservingAction m s a
- acts :: IndexPreservingAction m (m a) a
- perform :: Monad m => Acting m a s a -> s -> m a
- performs :: (Profunctor p, Monad m) => Over p (Effect m e) s t a b -> p a e -> s -> m e
- liftAct :: (MonadTrans trans, Monad m) => Acting m a s a -> IndexPreservingAction (trans m) s a
- (^!) :: Monad m => s -> Acting m a s a -> m a
- (^!!) :: Monad m => s -> Acting m [a] s a -> m [a]
- (^!?) :: Monad m => s -> Acting m (Leftmost a) s a -> m (Maybe a)
- type IndexedAction i m s a = forall p f r. (Indexable i p, Effective m r f) => p a (f a) -> s -> f s
- iact :: Monad m => (s -> m (i, a)) -> IndexedAction i m s a
- iperform :: Monad m => IndexedActing i m (i, a) s a -> s -> m (i, a)
- iperforms :: Monad m => IndexedActing i m e s a -> (i -> a -> e) -> s -> m e
- (^@!) :: Monad m => s -> IndexedActing i m (i, a) s a -> m (i, a)
- (^@!!) :: Monad m => s -> IndexedActing i m [(i, a)] s a -> m [(i, a)]
- (^@!?) :: Monad m => s -> IndexedActing i m (Leftmost (i, a)) s a -> m (Maybe (i, a))
- type MonadicFold m s a = forall f r. (Effective m r f, Applicative f) => (a -> f a) -> s -> f s
- type IndexedMonadicFold i m s a = forall p f r. (Indexable i p, Effective m r f, Applicative f) => p a (f a) -> s -> f s
- type Acting m r s a = LensLike (Effect m r) s s a a
- type IndexedActing i m r s a = Over (Indexed i) (Effect m r) s s a a
- class (Monad m, Functor f, Contravariant f) => Effective m r f | f -> m r
Composable Actions
act :: Monad m => (s -> m a) -> IndexPreservingAction m s aSource
acts :: IndexPreservingAction m (m a) aSource
liftAct :: (MonadTrans trans, Monad m) => Acting m a s a -> IndexPreservingAction (trans m) s aSource
(^!) :: Monad m => s -> Acting m a s a -> m aSource
Perform an Action
.
>>>
["hello","world"]^!folded.act putStrLn
hello world
(^!!) :: Monad m => s -> Acting m [a] s a -> m [a]Source
Perform a MonadicFold
and collect all of the results in a list.
>>>
["ab","cd","ef"]^!!folded.acts
["ace","acf","ade","adf","bce","bcf","bde","bdf"]
(^!?) :: Monad m => s -> Acting m (Leftmost a) s a -> m (Maybe a)Source
Perform a MonadicFold
and collect the leftmost result.
Note: this still causes all effects for all elements.
>>>
[Just 1, Just 2, Just 3]^!?folded.acts
Just (Just 1)>>>
[Just 1, Nothing]^!?folded.acts
Nothing
Indexed Actions
type IndexedAction i m s a = forall p f r. (Indexable i p, Effective m r f) => p a (f a) -> s -> f sSource
An IndexedAction
is an IndexedGetter
enriched with access to a Monad
for side-effects.
Every Getter
can be used as an Action
.
You can compose an Action
with another Action
using (.
) from the Prelude
.
iact :: Monad m => (s -> m (i, a)) -> IndexedAction i m s aSource
Construct an IndexedAction
from a monadic side-effect.
iperform :: Monad m => IndexedActing i m (i, a) s a -> s -> m (i, a)Source
Perform an IndexedAction
.
iperform
≡flip
(^@!
)
iperforms :: Monad m => IndexedActing i m e s a -> (i -> a -> e) -> s -> m eSource
Perform an IndexedAction
and modify the result.
(^@!) :: Monad m => s -> IndexedActing i m (i, a) s a -> m (i, a)Source
Perform an IndexedAction
.
(^@!!) :: Monad m => s -> IndexedActing i m [(i, a)] s a -> m [(i, a)]Source
Obtain a list of all of the results of an IndexedMonadicFold
.
(^@!?) :: Monad m => s -> IndexedActing i m (Leftmost (i, a)) s a -> m (Maybe (i, a))Source
Perform an IndexedMonadicFold
and collect the Leftmost
result.
Note: this still causes all effects for all elements.
Folds with Effects
type MonadicFold m s a = forall f r. (Effective m r f, Applicative f) => (a -> f a) -> s -> f sSource
A MonadicFold
is a Fold
enriched with access to a Monad
for side-effects.
Every Fold
can be used as a MonadicFold
, that simply ignores the access to the Monad
.
You can compose a MonadicFold
with another MonadicFold
using (.
) from the Prelude
.
type IndexedMonadicFold i m s a = forall p f r. (Indexable i p, Effective m r f, Applicative f) => p a (f a) -> s -> f sSource
An IndexedMonadicFold
is an IndexedFold
enriched with access to a Monad
for side-effects.
Every IndexedFold
can be used as an IndexedMonadicFold
, that simply ignores the access to the Monad
.
You can compose an IndexedMonadicFold
with another IndexedMonadicFold
using (.
) from the Prelude
.
Implementation Details
type IndexedActing i m r s a = Over (Indexed i) (Effect m r) s s a aSource
Used to evaluate an IndexedAction
.
class (Monad m, Functor f, Contravariant f) => Effective m r f | f -> m rSource
An Effective
Functor
ignores its argument and is isomorphic to a Monad
wrapped around a value.
That said, the Monad
is possibly rather unrelated to any Applicative
structure.