Skip to content

Instantly share code, notes, and snippets.

@elefthei
Last active January 14, 2021 04:41
Show Gist options
  • Save elefthei/f0b370d438774823b15311d5a194e40c to your computer and use it in GitHub Desktop.
Save elefthei/f0b370d438774823b15311d5a194e40c to your computer and use it in GitHub Desktop.
Monad Transformers in Haskell examples
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
import Control.Monad.State.Lazy
-- Inner Monad (Bar)
data BarState = BarState { bars :: [Char] }
newtype Bar a = Bar (State BarState a) deriving (Functor, Applicative, Monad, MonadState BarState)
class Monad m => MonadBar m where
liftBar :: Bar a -> m a
instance MonadBar Bar where
liftBar = id
instance (MonadBar m) => MonadBar (StateT s m) where
liftBar = lift . liftBar
-- Middle Monad (Foo, parametrized with multiple parameters)
data FooState t v c = FooState {
vals :: [v]
, types :: [t]
, conf :: c
}
newtype Foo t v c a = Foo (StateT (FooState t v c) Bar a) deriving (Functor, Applicative, Monad, MonadState (FooState t v c), MonadBar)
class Monad m => MonadFoo t v c m | m -> v, m -> t, m -> c where
liftFoo :: Foo t v c a -> m a
instance MonadFoo t v c (Foo t v c) where
liftFoo = id
instance (MonadFoo t v c m) => MonadFoo t v c (StateT s m) where
liftFoo = lift . liftFoo
-- Top monad, C
data CState = CState { words :: [String] }
newtype C a = C (StateT CState (Foo Int Int Bool) a) deriving (Functor, Applicative, Monad, MonadState CState, MonadFoo Int Int Bool)
getNthVal :: Int -> C (Maybe Int)
getNthVal n = nth n <$> liftFoo . gets $ vals
where nth 0 (h : _ ) = Just h
nth n (_ : ts) = nth (n - 1) ts
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment