Safe Haskell | None |
---|---|
Language | Haskell2010 |
Constrictor
Contents
Description
This library provides strict versions of many functions in base, as well as a few functions that do not have lazy versions that exist in base (see the section on Folds).
Many functions in this library have an increased constraint from Functor/Applicative to Monad in order to achieve strictness in their arguments and/or result.
- (<$!>) :: Monad m => (a -> b) -> m a -> m b
- fmap' :: Monad m => (a -> b) -> m a -> m b
- liftM' :: Monad m => (a -> b) -> m a -> m b
- liftM2' :: Monad m => (a -> b -> c) -> m a -> m b -> m c
- liftM3' :: Monad m => (a -> b -> c -> d) -> m a -> m b -> m c -> m d
- liftM4' :: Monad m => (a -> b -> c -> d -> e) -> m a -> m b -> m c -> m d -> m e
- liftM5' :: Monad m => (a -> b -> c -> d -> e -> f) -> m a -> m b -> m c -> m d -> m e -> m f
- ap' :: Monad m => m (a -> b) -> m a -> m b
- traverse' :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b)
- traverse'' :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b)
- mapM' :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b)
- foldrMap :: (Monoid m, Foldable t) => (a -> m) -> t a -> m
- foldlMap :: (Monoid m, Foldable t) => (a -> m) -> t a -> m
- foldrMap' :: (Monoid m, Foldable t) => (a -> m) -> t a -> m
- foldlMap' :: (Monoid m, Foldable t) => (a -> m) -> t a -> m
- foldlMapA :: forall t b a f. (Foldable t, Monoid b, Applicative f) => (a -> f b) -> t a -> f b
- foldrMapA :: forall t b a f. (Foldable t, Monoid b, Applicative f) => (a -> f b) -> t a -> f b
- foldlMapM' :: forall t b a m. (Foldable t, Monoid b, Monad m) => (a -> m b) -> t a -> m b
- foldrMapM' :: forall t b a m. (Foldable t, Monoid b, Monad m) => (a -> m b) -> t a -> m b
- newtype Ap f a = Ap {
- getAp :: f a
Strict 'lift-like' functions
(<$!>) :: Monad m => (a -> b) -> m a -> m b infixl 4 Source #
This is <$>
, but strict in its
argument and result.
This is re-defined in this module, and not
just re-exported from
.
The reason for this is that there is no way
to hide the docs for re-exports with Haddocks.Monad
In the common case that one might import
, we recommend structuring
imports like so:Monad
import Control.Monad hiding (($!)) import Constrictor
or
import Control.Monad import Constrictor hiding (($!))
There should be no side effects (i.e. naming/scoping conflicts) introduced as a result of structuring one's imports in this way.
liftM2' :: Monad m => (a -> b -> c) -> m a -> m b -> m c Source #
This is liftM2
, but strict in its
arguments and result.
liftM3' :: Monad m => (a -> b -> c -> d) -> m a -> m b -> m c -> m d Source #
This is liftM3
, but strict in its
arguments and result.
liftM4' :: Monad m => (a -> b -> c -> d -> e) -> m a -> m b -> m c -> m d -> m e Source #
This is liftM4
, but strict in its
arguments and result.
liftM5' :: Monad m => (a -> b -> c -> d -> e -> f) -> m a -> m b -> m c -> m d -> m e -> m f Source #
This is liftM5
, but strict in its
arguments and result.
ap' :: Monad m => m (a -> b) -> m a -> m b Source #
This is ap
, but strict in its
arguments and result.
traverse' :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) Source #
Strict version of traverse
.
traverse'' :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) Source #
Stricter version of traverse
.
mapM' :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) Source #
Folds
Lazy monoidal folds
foldrMap :: (Monoid m, Foldable t) => (a -> m) -> t a -> m Source #
Map each element of a foldable structure to a monoid, and combine the results. This function is right-associative.
Note that this is equivalent to foldMap
.
foldlMap :: (Monoid m, Foldable t) => (a -> m) -> t a -> m Source #
Map each element of a foldable structure to a monoid, and combine the results. This function is left-associative.
The operator is applied lazily. For a strict version, see
foldlMap'
.
Strict monoidal folds
foldrMap' :: (Monoid m, Foldable t) => (a -> m) -> t a -> m Source #
Map each element of a foldable structure to a monoid, and combine the results. This function is right-associative.
Note that this is equivalent to foldMap
,
but is strict.
foldlMap' :: (Monoid m, Foldable t) => (a -> m) -> t a -> m Source #
Map each element of a foldable structure to a monoid, and combine the results. This function is left-associative.
The operator is applied strictly. For a lazy version, see
foldlMap
.
Lazy applicative folds
foldlMapA :: forall t b a f. (Foldable t, Monoid b, Applicative f) => (a -> f b) -> t a -> f b Source #
Lazy in the monoidal accumulator. Monoidal accumulation happens from left to right.
foldrMapA :: forall t b a f. (Foldable t, Monoid b, Applicative f) => (a -> f b) -> t a -> f b Source #
Lazy in the monoidal accumulator. Monoidal accumulation happens from left to right.
Strict monadic folds
foldlMapM' :: forall t b a m. (Foldable t, Monoid b, Monad m) => (a -> m b) -> t a -> m b Source #
Strict in the monoidal accumulator. For monads strict in the left argument of bind, this will run in constant space. Monoidal accumulation happens from left to right.
Types
Wrapped applicative functor
A wrapped applicative functor. Please note that base 4.12.0.0 will include this type, and it will be removed from this library at that point.
Instances
Monad f => Monad (Ap f) Source # | |
Functor f => Functor (Ap f) Source # | |
MonadFix f => MonadFix (Ap f) Source # | |
MonadFail f => MonadFail (Ap f) Source # | |
Applicative f => Applicative (Ap f) Source # | |
Foldable f => Foldable (Ap f) Source # | |
Traversable f => Traversable (Ap f) Source # | |
Alternative f => Alternative (Ap f) Source # | |
MonadPlus f => MonadPlus (Ap f) Source # | |
Generic1 * (Ap f) Source # | |
Enum (f a) => Enum (Ap f a) Source # | |
Eq (f a) => Eq (Ap f a) Source # | |
Num (f a) => Num (Ap f a) Source # | |
Ord (f a) => Ord (Ap f a) Source # | |
Read (f a) => Read (Ap f a) Source # | |
Show (f a) => Show (Ap f a) Source # | |
Generic (Ap f a) Source # | |
(Applicative f, Semigroup a) => Semigroup (Ap f a) Source # | |
(Applicative f, Monoid a) => Monoid (Ap f a) Source # | |
type Rep1 * (Ap f) Source # | |
type Rep (Ap f a) Source # | |