deepcontrol
A Haskell library that provides much deeper level style of programming than the usual Control.Applicative and Control.Monad modules express.
Examples
This module enables you to program in applicative style for much deeper level than the usual Control.Applicative module expresses.
You would soon realize exactly what "much deeper level" means by reading the example codes below in order.
Prelude> :m DeepControl.Applicative
Level-0
bra-ket notation:
> (1+) |> 2
3
> 1 <| (+2)
3
> 1 <|(+)|> 2
3
> 1 <|(+)|> 2 <|(*)|> 3
9
> 1 <|(,)|> 2
(1,2)
Level-1
bra-ket notation:
> (1+) |$> [2]
[3]
> [1] <$| (+2)
[3]
> ("<"++)|$> ["a","b"] <$|(++">")
["<a>","<b>"]
> [(1+)] |*> [2]
[3]
> [1] <$|(+)|*> [2]
[3]
> [1] <$|(+)|*> [0,1,2]
[1,2,3]
> [0,1] <$|(+)|*> [2,3] <$|(+)|*> [4,5]
[6,7,7,8,7,8,8,9]
> filter (even <$|(&&)|*> (10>)) [1..100]
[2,4,6,8]
> filter (even <$|(&&)|*> (10>) <$|(&&)|*> (5<)) [1..100]
[6,8]
cover notation:
> :t (.*)
(.*) :: Applicative f => a -> f a
> (.*) 1 :: Maybe Int
Just 1
> (.*) 1 :: [Int]
[1]
> (.*) 1 :: Either () Int
Right 1
> foldr (\x acc -> x <$|(:)|*> acc) ((.*) []) [Just 1, Just 2, Just 3]
Just [1,2,3]
> foldr (\x acc -> x <$|(:)|*> acc) ((.*) []) [Just 1, Nothing, Just 3]
Nothing
cover-braket notation:
> :t (|*)
(|*) :: Applicative f => f (a -> b) -> a -> f b
> [(1+)] |* 2
[3]
> [1] <$|(+)|* 2
[3]
> (,) |$> ["a1","a2"] |* 'b'
[("a1",'b'),("a2",'b')]
> (,,) 'a' |$> ["b1","b2"] |* 'c'
[('a',"b1",'c'),('a',"b2",'c')]
> (,,,) 'a' |$> ["b1","b2"] |* 'c' |* 'd'
[('a',"b1",'c','d'),('a',"b2",'c','d')]
> (,,,) 'a' |$> ["b1","b2"] |* 'c' |*> ["d1","d2"]
[('a',"b1",'c',"d1"),('a',"b1",'c',"d2"),('a',"b2",'c',"d1"),('a',"b2",'c',"d2")]
> 1 *| [(+2)]
[3]
> 1 *| [(+)] |* 2
[3]
> 1 *|[(+),(-),(*),(^)]|* 2
[3,-1,2,1]
> 1 *|Just (,)|* 2
Just (1,2)
Level-2
bra-ket notation:
> (1+) |$>> [[2]]
[[3]]
> [[2]] <<$| (+1)
[[3]]
> [Just 1] <<$|(+)|*>> [Just 2]
[Just 3]
> [Just 1] <<$|(,)|*>> [Just 2]
[Just (1,2)]
> [[1]] <<$|(+)|*>> [[2]] <<$|(^)|*>> [[3]]
[[27]]
cover notation:
> :t (.**)
(.**) :: (Applicative f1, Applicative f2) => a -> f1 (f2 a)
> :t (-*)
(-*) :: (Applicative f1, Applicative f2) => f1 a -> f1 (f2 a)
> (.**) 1 :: Maybe [Int]
Just [1]
> (-*) (Just 1) :: Maybe [Int]
Just [1]
> (.*) [1] :: Maybe [Int]
Just [1]
> foldr (\n acc -> n <<$|(+)|*>> acc) ((.**) 0) [Right (Just 1), Right (Just 2), Right (Just 3)] :: Either () (Maybe Int)
Right (Just 6)
> foldr (\n acc -> n <<$|(+)|*>> acc) ((.**) 0) [Right (Just 1), Right Nothing, Right (Just 3)] :: Either () (Maybe Int)
Right Nothing
> foldr (\n acc -> n <<$|(+)|*>> acc) ((.**) 0) [Right (Just 1), Right Nothing, Left ()]
Left ()
cover-braket notation:
> :t (|**)
(|**) :: (Applicative f1, Applicative f2) => f1 (f2 (a -> b)) -> a -> f1 (f2 b)
> [Just 1] <<$|(+)|** 2
[Just 3]
> 1 **|(+)|$>> [Just 2]
[Just 3]
> 1 **|[Just (+)]|** 2
[Just 3]
> 1 **|[Just (+), Just (-), Just (*), Nothing]|** 2
[Just 3,Just (-1),Just 2,Nothing]
> :t (|-*)
(|-*) :: (Applicative f1, Applicative f2) => f1 (f2 (a -> b)) -> f1 a -> f1 (f2 b)
> :t (|*-)
(|*-) :: (Applicative f1, Applicative f2) => f1 (f2 (a -> b)) -> f2 a -> f1 (f2 b)
> [Just 1] <<$|(+)|-* [2]
[Just 3]
> [Just 1] <<$|(+)|*- Just 2
[Just 3]
> [1] -*|(+)|$>> [Just 2]
[Just 3]
> Just 1 *-|(+)|$>> [Just 2]
[Just 3]
> Just 1 *-|[Just (+)]|** 2
[Just 3]
> Just 1 *-|[Just (+)]|*- Just 2
[Just 3]
> [1] -*|[Just (+)]|*- Just 2
[Just 3]
> [1] -*|[Just (+), Just (-), Just (*), Nothing]|*- Just 2
[Just 3,Just (-1),Just 2,Nothing]
> [1,2] -*|[Just (+), Just (-), Just (*), Nothing]|*- Just 2
[Just 3,Just (-1),Just 2,Nothing,Just 4,Just 0,Just 4,Nothing]
Level-3, Level-4 and Level-5
Work well likewise.
This module enables you to program in Monad for much deeper level than the usual Control.Monad module expresses.
You would soon realize exactly what "much deeper level" means by reading the example codes below in order.
Level-0
import DeepControl.Monad ((>-))
plus :: Int -> Int -> Int
plus x y =
x >- \a ->
y >- \b ->
a + b
Identity, List, Maybe, Either, Except and Writer monads are sinkable monads.
Prelude> :m DeepControl.Traversable
> :t sink
sink :: (Applicative f, Traversable c) => c (f a) -> f (c a) -- synonym to 'sequenceA'
> sink $ Just [1]
[Just 1]
> sink2 $ Just (Right [1])
Right [Just 1]
> sink $ Right [Just 1]
[Right (Just 1)]
> sink2 $ Right [Just 1]
[Just (Right 1)]
So within these monads, deep-level bind functions can be made.
Level-2
import DeepControl.Applicative ((.**))
import DeepControl.Monad ((>>==))
listlist :: [[String]]
listlist = [["a","b"]] >>== \x ->
[[0],[1,2]] >>== \y ->
(.**) $ x ++ show y
import DeepControl.Applicative ((|$>), (.*), (.**))
import DeepControl.Monad ((>>), (>>==), (->~))
import Control.Monad.Writer
factorial :: Int ->
Maybe (Writer [Int] Int)
factorial n | n < 0 = Nothing
| n == 0 = (.*) $ tell [0] >> (.*) 1
| n > 0 = factorial (n-1) >>== \v ->
tell [v] ->~
(.**) (n * v)
Level-3
import DeepControl.Applicative ((|$>>), (.*), (.**), (.***))
import DeepControl.Monad ((>>), (>>>=), (>--~), (-->~))
import Control.Monad.Writer
factorial :: Int ->
IO (Maybe (Writer [Int] Int))
factorial n | n < 0 = (.*) Nothing
| n == 0 = (.**) $ tell [0] >> (.*) 1
| n > 0 = factorial (n-1) >>>= \v ->
print v >--~
tell [v] -->~
(.***) (n * v)
Level-4 and Level-5
Work well likewise.
SinkT
IdentityT, ListT, MaybeT, ExceptT and WriterT monadtranses are sinkable.
Prelude> :m DeepControl.Monad.Morph
> :t sinkT
sinkT
:: (Monad m, Traversable x,
DeepControl.Monad.Trans.MonadTrans_ x t, MMonad t, SinkT s) =>
s (t m) a -> t (s m) a
> :m + Control.Monad.Trans.List Control.Monad.Trans.Maybe
> :m + DeepControl.Monad.Trans.Identity DeepControl.Monad.Trans.Except DeepControl.Monad.Trans.Writer
> sinkT $ MaybeT (ListT (Right [Just 1]))
ListT (MaybeT (Right (Just [1])))
> sinkT $ MaybeT (ListT (ExceptT (Identity (Right [Just 1]))))
ListT (MaybeT (ExceptT (Identity (Right (Just [1])))))
> sinkT2 $ MaybeT (ListT (ExceptT (Identity (Right [Just 1]))))
ListT (ExceptT (MaybeT (Identity (Just (Right [1])))))
So within these monadtranses, deep-level trans-bind functions can be made.
Level-2
Here is a monad morph example how to use trans-map functions.
import DeepControl.Monad.Morph
import Control.Monad.Writer
import Control.Monad.State
tick :: State Int ()
tick = modify (+1)
tock :: StateT Int IO ()
tock = do
generalize |>| tick :: (Monad m) => StateT Int m ()
(|*|) $ putStrLn "Tock!" :: (MonadTrans t) => t IO ()
save :: StateT Int (Writer [Int]) ()
save = do
n <- get
(|*|) $ tell [n]
program :: StateT Int (WriterT [Int] IO) ()
program = replicateM_ 4 $ do
(|*|) |>| tock
:: (MonadTrans t) => StateT Int (t IO) ()
generalize |>>| save
:: (Monad m) => StateT Int (WriterT [Int] m ) ()
Here is a monad morph example how to use trans-cover and trans-bind functions.
import DeepControl.Monad.Morph ((|>=), (|>>=), (|*|), (|-*|))
import DeepControl.Monad.Trans.Except
import Control.Monad.Trans.Maybe
import Control.Exception (IOException, try)
-----------------------------------------------
check :: IO a ->
ExceptT IOException IO a
check io = ExceptT $ (try io)
viewFile :: IO ()
viewFile = do
str <- readFile "test.txt"
putStr str
program :: ExceptT IOException IO ()
program = (|*|) viewFile |>= check
calc_program :: IO (Either IOException ())
calc_program = runExceptT $ program
-----------------------------------------------
viewFile2 :: String ->
MaybeT IO ()
viewFile2 filename = do
guard (filename /= "")
str <- (|*|) $ readFile filename
(|*|) $ putStr str
program2 :: String ->
(ExceptT IOException (MaybeT IO)) ()
program2 filename =
(|*|) (viewFile2 filename) |>>= \x ->
(|-*|) $ check x
calc_program2 :: String -> IO (Maybe (Either IOException ()))
calc_program2 filename = runMaybeT . runExceptT $ program2 filename
Level-3, Level-4 and Level-5
Work well likewise.
Level-2
Here is a monad transformer example how to implement Ackermann function improved to stop within a certain limit of time, with ReaderT-IdentityT2-IO-Maybe monad, a level-2 monad-transformation.
import DeepControl.Applicative
import DeepControl.Traversable (sink)
import DeepControl.Monad ((>-))
import DeepControl.Monad.Morph ((|*|), (|>|))
import DeepControl.Monad.Trans (transfold2, untransfold2)
import DeepControl.Monad.Trans.Identity (Identity(..), IdentityT(..), IdentityT2(..))
import Control.Monad.Reader
import Control.Monad.Trans.Maybe
import System.Timeout (timeout)
type TimeLimit = Int
ackermannTimeLimit :: TimeLimit -> Int -> Int ->
IO (Maybe Int)
ackermannTimeLimit timelimit x y = timeout timelimit (ackermannIO x y)
where
ackermannIO :: Int -> Int -> IO Int
ackermannIO 0 n = (.*) $ n + 1
ackermannIO m n | m > 0 && n == 0 = ackermannIO (m-1) 1
| m > 0 && n > 0 = ackermannIO m (n-1) >>= ackermannIO (m-1)
ackermann :: Int -> Int ->
ReaderT TimeLimit (IdentityT2 IO Maybe) Int
ackermann x y = do
timelimit <- ask
(|*|) . IdentityT2 $ ackermannTimeLimit timelimit x y
calc_ackermann :: TimeLimit -> Int -> Int -> IO (Maybe Int)
calc_ackermann timelimit x y = ackermann x y >- \r -> runReaderT r timelimit
>- runIdentityT2
ackermann' :: Int -> Int ->
ReaderT TimeLimit (MaybeT IO) Int
ackermann' x y = (transfold2 . runIdentityT2) |>| ackermann x y
ackermann'' :: Int -> Int ->
ReaderT TimeLimit (IdentityT2 IO Maybe) Int
ackermann'' x y = (IdentityT2 . untransfold2) |>| ackermann' x y
Level-3, Level-4 and Level-5
Work well likewise.