MonadCompose-0.9.0.0: Methods for composing monads.

Safe HaskellSafe
LanguageHaskell98

Control.Monad.Coproducts3

Description

This *is* monad coproducts (due to Luth and Ghani) unlike the other thing.

Synopsis

Documentation

data Free' f f2 t Source #

A modified free monad giving efficient access to the topmost layer; but otherwise using the machinery of the free monad f2.

Constructors

Free' 

Fields

Pure' t 
Instances
(Functor f, MonadFree f f2) => MonadFree f (Free' f f2) Source # 
Instance details

Defined in Control.Monad.Coproducts3

Methods

wrap :: f (Free' f f2 a) -> Free' f f2 a #

(Functor f, MonadFree f f2) => Monad (Free' f f2) Source # 
Instance details

Defined in Control.Monad.Coproducts3

Methods

(>>=) :: Free' f f2 a -> (a -> Free' f f2 b) -> Free' f f2 b #

(>>) :: Free' f f2 a -> Free' f f2 b -> Free' f f2 b #

return :: a -> Free' f f2 a #

fail :: String -> Free' f f2 a #

(Functor f, Functor f2) => Functor (Free' f f2) Source # 
Instance details

Defined in Control.Monad.Coproducts3

Methods

fmap :: (a -> b) -> Free' f f2 a -> Free' f f2 b #

(<$) :: a -> Free' f f2 b -> Free' f f2 a #

(Functor f, MonadFree f f2) => Applicative (Free' f f2) Source # 
Instance details

Defined in Control.Monad.Coproducts3

Methods

pure :: a -> Free' f f2 a #

(<*>) :: Free' f f2 (a -> b) -> Free' f f2 a -> Free' f f2 b #

liftA2 :: (a -> b -> c) -> Free' f f2 a -> Free' f f2 b -> Free' f f2 c #

(*>) :: Free' f f2 a -> Free' f f2 b -> Free' f f2 b #

(<*) :: Free' f f2 a -> Free' f f2 b -> Free' f f2 a #

(Show1 f, Show1 f2) => Show1 (Free' f f2) Source # 
Instance details

Defined in Control.Monad.Coproducts3

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Free' f f2 a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Free' f f2 a] -> ShowS #

(Show (f (f2 t)), Show (f2 t), Show t) => Show (Free' f f2 t) Source # 
Instance details

Defined in Control.Monad.Coproducts3

Methods

showsPrec :: Int -> Free' f f2 t -> ShowS #

show :: Free' f f2 t -> String #

showList :: [Free' f f2 t] -> ShowS #

toF2 :: MonadFree f m => Free' f m a -> m a Source #

A projection into the underlying free monad construction.

execCoproduct :: (EtaInverse f, EtaInverse f2, MonadFree (Sum f f2) f3) => Free (Sum f f2) t -> Free' (Sum f f2) f3 t Source #

Given a free construction construct a representation of the monad coproduct in a free mona; it picks out one representative element of each equivalence class in the defining quotient of the monad coproduct.