Safe Haskell | None |
---|---|
Language | Haskell2010 |
SubHask.Monad
Description
This module contains the Monad hierarchy of classes.
- class Category cat => Functor cat f where
- fmap :: cat a b -> cat (f a) (f b)
- class Functor cat f => Applicative cat f where
- class Then m where
- (>>) :: m a -> m b -> m b
- haskThen :: Monad Hask m => m a -> m b -> m b
- mkThen :: forall proxy cat m a b. (Monad cat m, Cartesian cat, Concrete cat, ValidCategory cat a, ValidCategory cat (m b)) => proxy cat -> m a -> m b -> m b
- return :: Monad Hask m => a -> m a
- class (Then m, Functor cat m) => Monad cat m where
- fail :: [Char] -> a
- newtype Kleisli cat f a b = Kleisli (cat a (f b))
- sequence :: Monad Hask m => [m a] -> m [a]
- sequence_ :: Monad Hask m => [m a] -> m ()
- mapM :: Monad Hask m => (a -> m b) -> [a] -> m [b]
- mapM_ :: Monad Hask m => (a -> m b) -> [a] -> m ()
- filterM :: Monad Hask m => (a -> m Bool) -> [a] -> m [a]
- forM :: Monad Hask m => [a] -> (a -> m b) -> m [b]
- forM_ :: Monad Hask m => [a] -> (a -> m b) -> m ()
- forever :: Monad Hask m => m a -> m b
- void :: Functor Hask f => f a -> f ()
- mapAndUnzipM :: Monad Hask m => (a -> m (b, c)) -> [a] -> m ([b], [c])
- zipWithM :: Monad Hask m => (a -> b -> m c) -> [a] -> [b] -> m [c]
- zipWithM_ :: Monad Hask m => (a -> b -> m c) -> [a] -> [b] -> m ()
- foldM :: Monad Hask m => (a -> b -> m a) -> a -> [b] -> m a
- foldM_ :: Monad Hask m => (a -> b -> m a) -> a -> [b] -> m ()
- replicateM :: Monad Hask m => Int -> m a -> m [a]
- replicateM_ :: Monad Hask m => Int -> m a -> m ()
- when :: Monad Hask m => Bool -> m () -> m ()
- unless :: Monad Hask m => Bool -> m () -> m ()
- liftM :: Monad Hask m => (a1 -> r) -> m a1 -> m r
- liftM2 :: Monad Hask m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
- liftM3 :: Monad Hask m => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r
- liftM4 :: Monad Hask m => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r
- liftM5 :: Monad Hask m => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r
- ap :: Monad Hask m => m (a -> b) -> m a -> m b
Documentation
class Functor cat f => Applicative cat f where Source
FIXME: Not all monads can be made instances of Applicative in certain subcategories of hask.
For example, the OrdHask instance of Set requires an Ord constraint and a classical logic.
This means that we can't support Set (a -> b)
, which means no applicative instance.
There are reasonable solutions to this problem for Set (by storing functions differently), but are there other instances where Applicative is not a monad?
This class is a hack.
We can't include the (>>)
operator in the Monad
class because it doesn't depend on the underlying category.
mkThen :: forall proxy cat m a b. (Monad cat m, Cartesian cat, Concrete cat, ValidCategory cat a, ValidCategory cat (m b)) => proxy cat -> m a -> m b -> m b Source
This is the only current alternative to the Then
class for supporting (>>)
.
The problems with this implementation are:
1. All those ValidCategory constraints are ugly!
2. We've changed the signature of (>>)
in a way that's incompatible with do notation.
class (Then m, Functor cat m) => Monad cat m where Source
FIXME: right now, we're including any possibly relevant operator in this class; the main reason is that I don't know if there will be more efficient implementations for these in different categories
FIXME: think about do notation again
Methods
return_ :: ValidCategory cat a => cat a (m a) Source
join :: cat (m (m a)) (m a) Source
join ought to have a default implementation of:
join = (>>= id)
but "id" requires a ValidCategory constraint, so we can't use this default implementation.
(=<<) :: cat a (m b) -> cat (m a) (m b) infixr 1 Source
In Hask, most people think of monads in terms of the >>=
operator;
for our purposes, the reverse operator is more fundamental because it does not require the Concrete
constraint
(>>=) :: Concrete cat => m a -> cat a (m b) -> m b infixl 1 Source
The bind operator is used in desguaring do notation; unlike all the other operators, we're explicitly applying values to the arrows passed in; that's why we need the Concrete constraint
(<=<) :: cat b (m c) -> cat a (m b) -> cat a (m c) infixr 1 Source
Right-to-left Kleisli composition of monads. (
, with the arguments flipped>=>
)
(>=>) :: cat a (m b) -> cat b (m c) -> cat a (m c) infixl 1 Source
Left-to-right Kleisli composition of monads.
newtype Kleisli cat f a b Source
Every Monad has a unique Kleisli category
FIXME: should this be a GADT?
Constructors
Kleisli (cat a (f b)) |
Instances
Monad cat f => Category * (Kleisli * * * cat f) Source | |
type ValidCategory * (Kleisli * * * cat f) a = ValidCategory * cat a Source |
sequence :: Monad Hask m => [m a] -> m [a] Source
Evaluate each action in the sequence from left to right, and collect the results.
sequence_ :: Monad Hask m => [m a] -> m () Source
Evaluate each action in the sequence from left to right, and ignore the results.
filterM :: Monad Hask m => (a -> m Bool) -> [a] -> m [a] Source
This generalizes the list-based filter
function.
mapAndUnzipM :: Monad Hask m => (a -> m (b, c)) -> [a] -> m ([b], [c]) Source
The mapAndUnzipM
function maps its first argument over a list, returning
the result as a pair of lists. This function is mainly used with complicated
data structures or a state-transforming monad.
foldM :: Monad Hask m => (a -> b -> m a) -> a -> [b] -> m a Source
The foldM
function is analogous to foldl
, except that its result is
encapsulated in a monad. Note that foldM
works from left-to-right over
the list arguments. This could be an issue where (
and the `folded
function' are not commutative.>>
)
foldM f a1 [x1, x2, ..., xm]
==
do a2 <- f a1 x1 a3 <- f a2 x2 ... f am xm
If right-to-left evaluation is required, the input list should be reversed.
foldM_ :: Monad Hask m => (a -> b -> m a) -> a -> [b] -> m () Source
Like foldM
, but discards the result.
replicateM :: Monad Hask m => Int -> m a -> m [a] Source
performs the action replicateM
n actn
times,
gathering the results.
replicateM_ :: Monad Hask m => Int -> m a -> m () Source
Like replicateM
, but discards the result.
when :: Monad Hask m => Bool -> m () -> m () Source
Conditional execution of monadic expressions. For example,
when debug (putStr "Debugging\n")
will output the string Debugging\n
if the Boolean value debug
is True
,
and otherwise do nothing.
liftM2 :: Monad Hask m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r Source
Promote a function to a monad, scanning the monadic arguments from left to right. For example,
liftM2 (+) [0,1] [0,2] = [0,2,1,3] liftM2 (+) (Just 1) Nothing = Nothing
liftM3 :: Monad Hask m => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r Source
Promote a function to a monad, scanning the monadic arguments from
left to right (cf. liftM2
).
liftM4 :: Monad Hask m => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r Source
Promote a function to a monad, scanning the monadic arguments from
left to right (cf. liftM2
).