subhask-0.1.1.0: Type safe interface for programming in subcategories of Hask

Safe HaskellNone
LanguageHaskell2010

SubHask.Monad

Description

This module contains the Monad hierarchy of classes.

Synopsis

Documentation

class Category cat => Functor cat f where Source

Methods

fmap :: cat a b -> cat (f a) (f b) Source

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?

Methods

pure :: cat a (f a) Source

(<*>) :: f (cat a b) -> cat (f a) (f b) Source

class Then m where Source

This class is a hack. We can't include the (>>) operator in the Monad class because it doesn't depend on the underlying category.

Methods

(>>) :: m a -> m b -> m b infixl 1 Source

Instances

haskThen :: Monad Hask m => m a -> m b -> m b Source

A default implementation

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.

return :: Monad Hask m => a -> m a Source

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

Minimal complete definition

return_, join

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.

Instances

Monad OrdHask LexSet Source 
Monad Mon LexSet Source

FIXME: is there a more efficient implementation?

fail :: [Char] -> a Source

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.

mapM :: Monad Hask m => (a -> m b) -> [a] -> m [b] Source

mapM f is equivalent to sequence . map f.

mapM_ :: Monad Hask m => (a -> m b) -> [a] -> m () Source

mapM_ f is equivalent to sequence_ . map f.

filterM :: Monad Hask m => (a -> m Bool) -> [a] -> m [a] Source

This generalizes the list-based filter function.

forM :: Monad Hask m => [a] -> (a -> m b) -> m [b] Source

forM is mapM with its arguments flipped

forM_ :: Monad Hask m => [a] -> (a -> m b) -> m () Source

forM_ is mapM_ with its arguments flipped

forever :: Monad Hask m => m a -> m b Source

forever act repeats the action infinitely.

void :: Functor Hask f => f a -> f () Source

void value discards or ignores the result of evaluation, such as the return value of an IO action.

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.

zipWithM :: Monad Hask m => (a -> b -> m c) -> [a] -> [b] -> m [c] Source

The zipWithM function generalizes zipWith to arbitrary monads.

zipWithM_ :: Monad Hask m => (a -> b -> m c) -> [a] -> [b] -> m () Source

zipWithM_ is the extension of zipWithM which ignores the final result.

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

replicateM n act performs the action n 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.

unless :: Monad Hask m => Bool -> m () -> m () Source

The reverse of when.

liftM :: Monad Hask m => (a1 -> r) -> m a1 -> m r Source

Promote a function to a monad.

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).

liftM5 :: Monad Hask m => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r Source

Promote a function to a monad, scanning the monadic arguments from left to right (cf. liftM2).

ap :: Monad Hask m => m (a -> b) -> m a -> m b Source

In many situations, the liftM operations can be replaced by uses of ap, which promotes function application.

      return f `ap` x1 `ap` ... `ap` xn

is equivalent to

      liftMn f x1 x2 ... xn