Skip to content

Instantly share code, notes, and snippets.

@StarOrpheus
Last active October 17, 2020 09:23
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 StarOrpheus/44dabdc72aae558f973131e217314b58 to your computer and use it in GitHub Desktop.
Save StarOrpheus/44dabdc72aae558f973131e217314b58 to your computer and use it in GitHub Desktop.
Monad & monad transformer complete example
import Control.Monad.Trans.State
import Control.Monad.Trans.Except
data StackState a = StackState
{ stackData :: [a]
, stackDoneOps :: Int
, stackOpsLimit :: Int
} deriving (Show)
newStackState :: Int -> StackState a
newStackState limit = StackState ([] :: [a]) 0 limit
push :: a -> State (StackState a) ()
push value = do
st <- get
let (StackState as ops lim) = st
put $ StackState (as ++ [value]) (ops + 1) lim
return ()
pop :: State (StackState a) a
pop = do
st <- get
let (StackState as ops lim) = st
let result = last as
put $ StackState (init as) (ops + 1) lim
return result
modifyingFunction :: StackState Int -> ((), StackState Int)
modifyingFunction = runState $ do
push 5
push 10
_ <- pop
return ()
calc :: StackState Int
calc =
let (_, state) = modifyingFunction (newStackState 5) in
state
main :: IO ()
main = do
let res = calc
print res
module Main where
import Control.Monad.Except
import Control.Monad.State
import Text.Pretty.Simple (pPrint)
data StackState a = StackState
{ stackData :: [a]
, stackDoneOps :: Int
, stackOpsLimit :: Int
} deriving (Show)
newStackState :: Int
-> StackState a
newStackState = StackState ([] :: [a]) 0
push :: a
-> ExceptT String (State (StackState a)) ()
push value = do
st <- get
let (StackState as ops lim) = st
let newOps = ops + 1
if newOps > lim then
throwError "Stack operation limit exceeded"
else do
put $ StackState (as ++ [value]) newOps lim
return ()
pop :: ExceptT String (State (StackState a)) a
pop = do
st <- get
let (StackState as ops lim) = st
if null as then
throwError "Stack empty!"
else do
let result = last as
put $ StackState (init as) (ops + 1) lim
return result
modifyingFunction :: StackState Int
-> (Either String (), StackState Int)
modifyingFunction = runState $ runExceptT $ do
push 5
pop
pop
_ <- pop
return ()
calc :: Either String (StackState Int)
calc =
let (result, state) = modifyingFunction (newStackState 3) in
case result of
Left err -> Left err
Right res -> Right state
main :: IO ()
main = do
let res = calc
pPrint res
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment