deepcontrol-0.4.2.1: Provide more deeper level style of programming than the usual Control.xxx modules express

Copyright2013 Gabriel Gonzalez
(c) 2015 KONISHI Yohsuke
LicenseBSD-style (see the LICENSE file in the distribution)
Maintainerocean0yohsuke@gmail.com
Stabilityexperimental
Portability---
Safe HaskellSafe
LanguageHaskell2010

DeepControl.Monad.Morph

Contents

Description

This module enables you to program in Monad-Morphic style for more deeper level than the usual Control.Monad.Morph module expresses. You would realize exactly what more deeper level means by reading the example codes, which are attached on the page bottom.

Synopsis

Documentation

Level-1

trans-map

(|>|) :: (Monad m, MFunctor t) => (forall a. m a -> n a) -> t m b -> t n b infixl 2 Source #

Alias to hoist.

(|<|) :: (Monad m, MFunctor t) => t m b -> (forall a. m a -> n a) -> t n b infixr 2 Source #

Equivalent to (|>|) with the arguments flipped.

Level-2

trans-map

(|>>|) :: (Monad m, Monad (t2 m), MFunctor t1, MFunctor t2) => (forall a. m a -> n a) -> t1 (t2 m) b -> t1 (t2 n) b infixl 2 Source #

(|<<|) :: (Monad m, Monad (t2 m), MFunctor t1, MFunctor t2) => t1 (t2 m) b -> (forall a. m a -> n a) -> t1 (t2 n) b infixr 2 Source #

Level-3

trans-map

(|>>>|) :: (Monad m, Monad (t3 m), Monad (t2 (t3 m)), MFunctor t1, MFunctor t2, MFunctor t3) => (forall a. m a -> n a) -> t1 (t2 (t3 m)) b -> t1 (t2 (t3 n)) b infixl 2 Source #

(|<<<|) :: (Monad m, Monad (t3 m), Monad (t2 (t3 m)), MFunctor t1, MFunctor t2, MFunctor t3) => t1 (t2 (t3 m)) b -> (forall a. m a -> n a) -> t1 (t2 (t3 n)) b infixr 2 Source #

Level-4

trans-map

(|>>>>|) :: (Monad m, Monad (t4 m), Monad (t3 (t4 m)), Monad (t2 (t3 (t4 m))), MFunctor t1, MFunctor t2, MFunctor t3, MFunctor t4) => (forall a. m a -> n a) -> t1 (t2 (t3 (t4 m))) b -> t1 (t2 (t3 (t4 n))) b infixl 2 Source #

(|<<<<|) :: (Monad m, Monad (t4 m), Monad (t3 (t4 m)), Monad (t2 (t3 (t4 m))), MFunctor t1, MFunctor t2, MFunctor t3, MFunctor t4) => t1 (t2 (t3 (t4 m))) b -> (forall a. m a -> n a) -> t1 (t2 (t3 (t4 n))) b infixr 2 Source #

Level-5

trans-map

(|>>>>>|) :: (Monad m, Monad (t5 m), Monad (t4 (t5 m)), Monad (t3 (t4 (t5 m))), Monad (t2 (t3 (t4 (t5 m)))), MFunctor t1, MFunctor t2, MFunctor t3, MFunctor t4, MFunctor t5) => (forall a. m a -> n a) -> t1 (t2 (t3 (t4 (t5 m)))) b -> t1 (t2 (t3 (t4 (t5 n)))) b infixl 2 Source #

(|<<<<<|) :: (Monad m, Monad (t5 m), Monad (t4 (t5 m)), Monad (t3 (t4 (t5 m))), Monad (t2 (t3 (t4 (t5 m)))), MFunctor t1, MFunctor t2, MFunctor t3, MFunctor t4, MFunctor t5) => t1 (t2 (t3 (t4 (t5 m)))) b -> (forall a. m a -> n a) -> t1 (t2 (t3 (t4 (t5 n)))) b infixr 2 Source #

Level-2 example

Here is a monad-morph example, a level-2 monad-morph.

import DeepControl.Monad.Morph
import DeepControl.Monad.Trans.State
import DeepControl.Monad.Trans.Writer

-- i.e. :: StateT Int Identity ()
tick    :: State Int ()
tick = modify (+1)

tock                        ::                   StateT Int IO ()
tock = do
    generalize |>| tick     :: (Monad      m) => StateT Int m  ()  -- (|>|) is the level-1 trans-map function, analogous for (|$>) 
    lift $ putStrLn "Tock!" :: (MonadTrans t) => t          IO ()

-- λ> runStateT tock 0
-- Tock!
-- ((),1)

-- i.e. :: StateT Int (WriterT [Int] Identity) ()
save    :: StateT Int (Writer  [Int]) ()
save = do
    n <- get
    lift $ tell [n]

program ::                   StateT Int (WriterT [Int] IO) ()
program = replicateM_ 4 $ do
    lift |>| tock
        :: (MonadTrans t) => StateT Int (t             IO) ()
    generalize |>>| save                                         -- (|>>|) is the level-2 trans-map function, analogous for (|$>>)
        :: (Monad      m) => StateT Int (WriterT [Int] m ) ()

-- λ> execWriterT (runStateT program 0)
-- Tock!
-- Tock!
-- Tock!
-- Tock!
-- [1,2,3,4]