Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
The most generic definitions for folding function applications.
- class Converter (conv :: * -> * -> Constraint) where
- class (Converter conv, Infer conv p r f) => FoldlApp (conv :: * -> * -> Constraint) (p :: *) (r :: *) (f :: *) where
- class (Converter conv, Infer conv p r f) => FoldrApp (conv :: * -> * -> Constraint) (p :: *) (r :: *) (f :: *)
- class Applicative m => Monad (m :: * -> *)
- foldlMApp :: forall conv m p r f. (Monad m, FoldlApp conv p (m r) f) => (r -> p -> m r) -> r -> f
- foldrApp :: forall conv p r f. FoldrApp conv p r f => (p -> r -> r) -> r -> f
- foldrMApp :: forall conv m p r f. (Monad m, FoldrApp conv p (m r) f) => (p -> r -> m r) -> r -> f
Documentation
class Converter (conv :: * -> * -> Constraint) where Source #
Class of constraints which feature a function to convert a value of one type to a value of another.
class (Converter conv, Infer conv p r f) => FoldlApp (conv :: * -> * -> Constraint) (p :: *) (r :: *) (f :: *) where Source #
Class defining left-associative folds of function applications. No other instances need be defined.
class (Converter conv, Infer conv p r f) => FoldrApp (conv :: * -> * -> Constraint) (p :: *) (r :: *) (f :: *) Source #
Class defining right-associative folds of function applications. No other instances need be defined.
foldrAppImpl
class Applicative m => Monad (m :: * -> *) #
The Monad
class defines the basic operations over a monad,
a concept from a branch of mathematics known as category theory.
From the perspective of a Haskell programmer, however, it is best to
think of a monad as an abstract datatype of actions.
Haskell's do
expressions provide a convenient syntax for writing
monadic expressions.
Instances of Monad
should satisfy the following laws:
Furthermore, the Monad
and Applicative
operations should relate as follows:
The above laws imply:
and that pure
and (<*>
) satisfy the applicative functor laws.
The instances of Monad
for lists, Maybe
and IO
defined in the Prelude satisfy these laws.
Monad [] | Since: 2.1 |
Monad Maybe | Since: 2.1 |
Monad IO | Since: 2.1 |
Monad NonEmpty | Since: 4.9.0.0 |
Monad Dual | Since: 4.8.0.0 |
Monad Sum | Since: 4.8.0.0 |
Monad Product | Since: 4.8.0.0 |
Monad First | |
Monad Last | |
Monad Seq | |
Monoid a => Monad ((,) a) | Since: 4.9.0.0 |
Monad m => Monad (WrappedMonad m) | |
ArrowApply a => Monad (ArrowMonad a) | Since: 2.1 |
Monad (State s) | |
Monad f => Monad (Alt * f) | |
(Applicative f, Monad f) => Monad (WhenMissing f x) | Equivalent to |
Monad ((->) LiftedRep LiftedRep r) | Since: 2.1 |
(Monad f, Applicative f) => Monad (WhenMatched f x y) | Equivalent to |
(Applicative f, Monad f) => Monad (WhenMissing f k x) | Equivalent to |
(Monad f, Applicative f) => Monad (WhenMatched f k x y) | Equivalent to |
foldlMApp :: forall conv m p r f. (Monad m, FoldlApp conv p (m r) f) => (r -> p -> m r) -> r -> f Source #
Monadic left-associative fold of function applications.