Skip to content

Instantly share code, notes, and snippets.

@bond15
Last active October 15, 2020 17:08
Show Gist options
  • Save bond15/c18d4a729b8ff549a37c05869999f747 to your computer and use it in GitHub Desktop.
Save bond15/c18d4a729b8ff549a37c05869999f747 to your computer and use it in GitHub Desktop.
module MonadTransformers where
import Text.Read (readMaybe)
import Control.Monad (ap, liftM )
import GHC.Base(returnIO)
-- maybe monad
-- short circuit semantics
ex1 :: Maybe Int
ex1 = do
_ <- Just 4
_ <- Nothing
return 7 -- results in Nothing
-- IO monad
-- access the environment
ex2 :: IO String
ex2 = do
s <- getLine
_ <- putStrLn s
return s
-- example using both monads
-- IO for reading
-- Maybe for possible parse failures
getNum :: IO (Maybe Int)
getNum = do
n1 <- getLine
return $ readMaybe n1
addNums :: IO (Maybe Int)
addNums = do
putStrLn "read first num"
n1 <- getNum
putStrLn "read second num"
n2 <- getNum
putStrLn "add nums"
return $ case (n1,n2) of -- here we have to unwrap n1 and n2 from Maybe
((Just a),(Just b)) -> Just $ a + b
_ -> Nothing
-- addNums does not fail fast..
-- combine IO and Maybe into a monad that can interact with the environment but also have fail fast semantics
newtype MaybeT m a = MaybeT { runMaybeT :: m (Maybe a)}
instance Monad m => Functor (MaybeT m) where
fmap = liftM
-- liftM is like fmap but for monads
-- ex) liftM (\x -> "foo") (Just 7) ---> (Just "foo")
instance Monad m => Applicative (MaybeT m) where
pure = return
(<*>) = ap
instance Monad m => Monad (MaybeT m) where
return = MaybeT . return . Just -- lift a value into Maybe, then lift it into 'm', then apply MaybeT constructor
-- x : MaybeT m a
-- f : a -> MaybeT m a
x >>= f = MaybeT $ do
maybe_value <- runMaybeT x -- extract m (Maybe a)
case maybe_value of
Nothing -> return Nothing -- fail fast
Just value -> runMaybeT $ f value -- keep processing
-- helpers (influenced by scala cats)
lift = MaybeT . (liftM Just) -- m a -> m (Maybe a)
fromMaybe = MaybeT . returnIO
getNum' :: MaybeT IO Int
getNum' = do
s <- lift getLine
n <- fromMaybe $ readMaybe s
return n
addNums' :: MaybeT IO Int
addNums' = do
lift $ putStrLn "get first num"
n1 <- getNum'
lift $ putStrLn "get second num"
n2 <- getNum'
lift $ putStrLn "add nums"
return $ n1 + n2
-- Fail fast semantics AND unpacks values from BOTH monads
ex3 :: IO (Maybe Int)
ex3 = runMaybeT addNums'
test :: MaybeT IO Int
test = lift $ returnIO $ returnIO $ returnIO 7
-- does not typecheck GOOD!!!
-- Expected type: MaybeT IO Int
-- Actual type: MaybeT IO (IO (IO a0))
-- scala
-- val test: OptionT[IO,Unit] = OptionT.liftF[IO,Unit](IO(IO(IO(()))))
-- ^^^^ typechecks BAD!!
-- Update: This is because of value discarding: https://underscore.io/blog/posts/2016/11/24/value-discard.html#:~:text=Section%206.26.,term%20%7B%20e%3B%20()%20%7D%20.&text=Note%20that%20this%20is%20happening,Unit%20as%20our%20target%20type.
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment