Skip to content

Instantly share code, notes, and snippets.

@Javran
Created October 29, 2014 03:02
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 Javran/d241ef0477a16439d442 to your computer and use it in GitHub Desktop.
Save Javran/d241ef0477a16439d442 to your computer and use it in GitHub Desktop.
{-# LANGUAGE Rank2Types #-}
import Control.Monad.State
import Control.Monad.Writer
import Data.Maybe
newtype Stack a = Stack (forall r. (a -> Stack a -> r) -> r -> r)
cons, push :: a -> Stack a -> Stack a
cons x (Stack f) = Stack (\g _ -> g x (Stack f))
push = cons
peek :: Stack a -> Maybe a
peek (Stack f) = f (\x _ -> Just x) Nothing
pop :: Stack a -> Maybe (Stack a)
pop (Stack f) = f (\_ xs -> Just xs) Nothing
toList :: Stack a -> [a]
toList (Stack f) = f (\x xs -> x: toList xs) []
fromList :: [a] -> Stack a
fromList [] = Stack (\_ nil -> nil)
fromList (x:xs) = Stack (\g _ -> g x (fromList xs))
stackManip :: StateT (Stack Int) (Writer [Int]) ()
stackManip = do
let doPush x = modify (push x)
doPop = do
x <- gets peek
lift . tell . maybeToList $ x
modify (fromJust . pop)
return x
doPush 1
void doPop
doPush 2
doPush 3
void doPop
void doPop
main :: IO ()
main = do
print (execWriter (execStateT stackManip (fromList [])))
print . toList . fromList $ "foo"
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment