Skip to content

Instantly share code, notes, and snippets.

@sordina
Last active March 1, 2016 21:44
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save sordina/6f686baf4997da3e3d40 to your computer and use it in GitHub Desktop.
Save sordina/6f686baf4997da3e3d40 to your computer and use it in GitHub Desktop.
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE KindSignatures #-}
import Control.Category ((>>>), Category())
import Control.Arrow (Kleisli(..))
import Control.Monad.State (runState, modify, State)
-- Our composition is abstract
--
gen :: forall (cat :: * -> * -> *) a b c b1.
Category cat =>
cat a b -> cat b b1 -> cat b1 c -> cat a c
gen a b c = a >>> b >>> c
-- Our implementation, and implementation context can be swapped out
--
-- Here - Pure:
--
pipeline :: Int -> String
pipeline = gen a b c
where
a = (+1)
b = (+2)
c = show
-- Here - IO:
--
pipeline' :: Kleisli IO Int String
pipeline' = gen a b c
where
a = Kleisli $ return . (+1)
b = Kleisli $ \x -> print x >> return (x + 2)
c = Kleisli $ return . show
-- Here - State:
--
pipeline'' :: Kleisli (State Int) Int String
pipeline'' = gen a b c
where
a = tally (+1)
b = tally (+2)
c = tally show
tally f = Kleisli $ \x -> modify (+x) >> return (f x)
-- Execution differs:
--
main :: IO ()
main = do
return (pipeline 1) >>= print
(runKleisli pipeline' 2) >>= print
return (runState (runKleisli pipeline'' 3) 0) >>= print
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment