constrictor-0.1.2.0: strict versions of many things in base

Safe HaskellNone
LanguageHaskell2010

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.

Synopsis

Strict lifting 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 Control.Monad. The reason for this is that there is no way to hide the docs for re-exports with Haddocks.

In the common case that one might import Control.Monad, we recommend structuring imports like so:

import Control.Monad hiding ((<$!>))
import Constrictor

or

import Control.Monad
import Constrictor hiding ((<$!>))

There should be no unintended side effects introduced as a result of structuring one's imports in this way.

fmap' :: Monad m => (a -> b) -> m a -> m b infixl 4 Source #

This is fmap, but strict in its argument and result.

Note this is equivalent to <$!>, and is provided for convenience.

liftM' :: Monad m => (a -> b) -> m a -> m b infixl 4 Source #

This is liftM, but strict in its argument and result.

Note this is equivalent to <$!>, and is provided for convenience.

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 #

Strict version of mapM.

This is just traverse' specialised to Monad.

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.

foldrMapM' :: forall t b a m. (Foldable t, Monoid b, Monad m) => (a -> m b) -> t a -> m b Source #

Strict in the monoidal accumulator. Monoidal accumulation happens from left to right.