constrictor-0.1.0.1: strict versions of many things in base

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Constrictor

Contents

Synopsis

strict monadic functions

(<$!>) :: Monad m => (a -> b) -> m a -> m b infixl 4 #

Strict version of <$>.

Since: 4.8.0.0

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

Strict version of fmap.

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

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

Strict version of liftM.

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

liftM2' :: Monad m => (a -> b -> c) -> m a -> m b -> m c Source #

Strict version of liftM2.

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.

strict applicative functions

traverse' :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) Source #

Strict version of traverse.

Note the increased constraint from Functor to Applicative.

a wrapped applicative functor

newtype Ap f a Source #

Constructors

Ap 

Fields

Instances

Monad f => Monad (Ap f) Source # 

Methods

(>>=) :: Ap f a -> (a -> Ap f b) -> Ap f b #

(>>) :: Ap f a -> Ap f b -> Ap f b #

return :: a -> Ap f a #

fail :: String -> Ap f a #

Functor f => Functor (Ap f) Source # 

Methods

fmap :: (a -> b) -> Ap f a -> Ap f b #

(<$) :: a -> Ap f b -> Ap f a #

Applicative f => Applicative (Ap f) Source # 

Methods

pure :: a -> Ap f a #

(<*>) :: Ap f (a -> b) -> Ap f a -> Ap f b #

liftA2 :: (a -> b -> c) -> Ap f a -> Ap f b -> Ap f c #

(*>) :: Ap f a -> Ap f b -> Ap f b #

(<*) :: Ap f a -> Ap f b -> Ap f a #

Foldable f => Foldable (Ap f) Source # 

Methods

fold :: Monoid m => Ap f m -> m #

foldMap :: Monoid m => (a -> m) -> Ap f a -> m #

foldr :: (a -> b -> b) -> b -> Ap f a -> b #

foldr' :: (a -> b -> b) -> b -> Ap f a -> b #

foldl :: (b -> a -> b) -> b -> Ap f a -> b #

foldl' :: (b -> a -> b) -> b -> Ap f a -> b #

foldr1 :: (a -> a -> a) -> Ap f a -> a #

foldl1 :: (a -> a -> a) -> Ap f a -> a #

toList :: Ap f a -> [a] #

null :: Ap f a -> Bool #

length :: Ap f a -> Int #

elem :: Eq a => a -> Ap f a -> Bool #

maximum :: Ord a => Ap f a -> a #

minimum :: Ord a => Ap f a -> a #

sum :: Num a => Ap f a -> a #

product :: Num a => Ap f a -> a #

Traversable f => Traversable (Ap f) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Ap f a -> f (Ap f b) #

sequenceA :: Applicative f => Ap f (f a) -> f (Ap f a) #

mapM :: Monad m => (a -> m b) -> Ap f a -> m (Ap f b) #

sequence :: Monad m => Ap f (m a) -> m (Ap f a) #

Generic1 * (Ap f) Source # 

Associated Types

type Rep1 (Ap f) (f :: Ap f -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (Ap f) f a #

to1 :: Rep1 (Ap f) f a -> f a #

Eq (f a) => Eq (Ap f a) Source # 

Methods

(==) :: Ap f a -> Ap f a -> Bool #

(/=) :: Ap f a -> Ap f a -> Bool #

Ord (f a) => Ord (Ap f a) Source # 

Methods

compare :: Ap f a -> Ap f a -> Ordering #

(<) :: Ap f a -> Ap f a -> Bool #

(<=) :: Ap f a -> Ap f a -> Bool #

(>) :: Ap f a -> Ap f a -> Bool #

(>=) :: Ap f a -> Ap f a -> Bool #

max :: Ap f a -> Ap f a -> Ap f a #

min :: Ap f a -> Ap f a -> Ap f a #

Read (f a) => Read (Ap f a) Source # 

Methods

readsPrec :: Int -> ReadS (Ap f a) #

readList :: ReadS [Ap f a] #

readPrec :: ReadPrec (Ap f a) #

readListPrec :: ReadPrec [Ap f a] #

Show (f a) => Show (Ap f a) Source # 

Methods

showsPrec :: Int -> Ap f a -> ShowS #

show :: Ap f a -> String #

showList :: [Ap f a] -> ShowS #

Generic (Ap f a) Source # 

Associated Types

type Rep (Ap f a) :: * -> * #

Methods

from :: Ap f a -> Rep (Ap f a) x #

to :: Rep (Ap f a) x -> Ap f a #

(Applicative f, Semigroup a) => Semigroup (Ap f a) Source # 

Methods

(<>) :: Ap f a -> Ap f a -> Ap f a #

sconcat :: NonEmpty (Ap f a) -> Ap f a #

stimes :: Integral b => b -> Ap f a -> Ap f a #

(Applicative f, Monoid a) => Monoid (Ap f a) Source # 

Methods

mempty :: Ap f a #

mappend :: Ap f a -> Ap f a -> Ap f a #

mconcat :: [Ap f a] -> Ap f a #

type Rep1 * (Ap f) Source # 
type Rep1 * (Ap f) = D1 * (MetaData "Ap" "Control.Monad.Constrictor" "constrictor-0.1.0.1-8Sa6lDd2NHMLBQ4KTqGxx3" True) (C1 * (MetaCons "Ap" PrefixI True) (S1 * (MetaSel (Just Symbol "getAp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 * f)))
type Rep (Ap f a) Source # 
type Rep (Ap f a) = D1 * (MetaData "Ap" "Control.Monad.Constrictor" "constrictor-0.1.0.1-8Sa6lDd2NHMLBQ4KTqGxx3" True) (C1 * (MetaCons "Ap" PrefixI True) (S1 * (MetaSel (Just Symbol "getAp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f a))))

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 #

non-strict applicative folds for completeness

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.