Trying to find an alternative StateMonad

Hi All, I wanted to write the statemonad in a different way, because I want to track mutations to the state. And also to be able to undo an done or redo an undone mutation. Therefore I wrote a small dsl with an evaluator, which finds out the current state. The problem is, I don't know how to create a get and put function for my monad. I have a function which evaluate the state and gives back the current State. Can someone help me a bit along? I have the feeling I do something wrong, but I am not sure what. With kind regards, Edgar {-# LANGUAGE GADTs,DeriveFunctor #-} import Control.Monad import Data.Maybe data StateCmd a where Put :: a -> StateCmd a Undo :: StateCmd a Redo :: StateCmd a deriving (Show, Functor) newtype State s a = State { unState :: ([StateCmd s],a) } deriving Show joinState :: State s a -> State s b -> State s b joinState (State (xs, a)) (State (ys, b)) = State (xs ++ ys, b) instance Monad (State s) where return a = State $ ([], a) (>>=) = bindState -- m a -> ( a -> m b) -> m b bindState st@(State (_,a)) f = st `joinState` st' where st' = f a unPut :: StateCmd a -> Maybe a unPut (Put a) = Just a unPut _ = Nothing test = State $ ([Put 4, Undo, Redo, Undo, Put 5, Undo, Redo, Put 6, Undo, Redo, Undo], ()) getCurrent = fromJust.unPut.head.snd.(foldr current' ([],[])).reverse.fst.unState where current' x (ul,cl) = case x of Put n -> (ul, Put n : cl) Undo -> (head cl : ul, tail cl) Redo -> (tail ul, head ul : cl)

I think I already know, the monad is not a state monad, but a writer
monad. I have to implement the dsl in a state monad.
Sorry I was somewhat too fast sending to the list. But comments are of
course still welcome.
On 4/15/10, edgar klerks
Hi All,
I wanted to write the statemonad in a different way, because I want to track mutations to the state. And also to be able to undo an done or redo an undone mutation. Therefore I wrote a small dsl with an evaluator, which finds out the current state.
The problem is, I don't know how to create a get and put function for my monad. I have a function which evaluate the state and gives back the current State.
Can someone help me a bit along? I have the feeling I do something wrong, but I am not sure what.
With kind regards,
Edgar
{-# LANGUAGE GADTs,DeriveFunctor #-} import Control.Monad import Data.Maybe
data StateCmd a where Put :: a -> StateCmd a Undo :: StateCmd a Redo :: StateCmd a deriving (Show, Functor)
newtype State s a = State { unState :: ([StateCmd s],a) } deriving Show
joinState :: State s a -> State s b -> State s b joinState (State (xs, a)) (State (ys, b)) = State (xs ++ ys, b)
instance Monad (State s) where return a = State $ ([], a) (>>=) = bindState
-- m a -> ( a -> m b) -> m b bindState st@(State (_,a)) f = st `joinState` st' where st' = f a
unPut :: StateCmd a -> Maybe a unPut (Put a) = Just a unPut _ = Nothing
test = State $ ([Put 4, Undo, Redo, Undo, Put 5, Undo, Redo, Put 6, Undo, Redo, Undo], ())
getCurrent = fromJust.unPut.head.snd.(foldr current' ([],[])).reverse.fst.unState where current' x (ul,cl) = case x of Put n -> (ul, Put n : cl) Undo -> (head cl : ul, tail cl) Redo -> (tail ul, head ul : cl)
-- Flatliner ICT Service, Email: Edgar.klerks@gmail.com, Tel: +31727851429 Fax: +31848363080 Skype: edgar.klerks Website: flatlinerict.nl Adres: Koelmalaan 258, 1813JD, Alkmaar Nederland

Hi, Sorry I can't be of much help here, but I have a question though:
data StateCmd a where Put :: a -> StateCmd a Undo :: StateCmd a Redo :: StateCmd a deriving (Show, Functor)
I'm not familiar with the above syntax (data ... where). What does it do exactly? Patrick -- ===================== Patrick LeBoutillier Rosemère, Québec, Canada

It is GADTs (Generalized Algebric Data Types) Notation.
data StateCmd a where Put :: a -> StateCmd a Undo :: StateCmd a Redo :: StateCmd a
is same as
data StateCmd a = Put a | Undo | Redo
-nwn
On 15 April 2010 07:49, Patrick LeBoutillier
Hi,
Sorry I can't be of much help here, but I have a question though:
data StateCmd a where Put :: a -> StateCmd a Undo :: StateCmd a Redo :: StateCmd a deriving (Show, Functor)
I'm not familiar with the above syntax (data ... where). What does it do exactly?
Patrick
-- ===================== Patrick LeBoutillier Rosemère, Québec, Canada _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Am Donnerstag 15 April 2010 00:49:26 schrieb Patrick LeBoutillier:
Hi,
Sorry I can't be of much help here, but I have a question though:
data StateCmd a where Put :: a -> StateCmd a Undo :: StateCmd a Redo :: StateCmd a deriving (Show, Functor)
I'm not familiar with the above syntax (data ... where).
It's GADT syntax, read about it in the user's guide.
What does it do exactly?
That is exactly equivalent to data StateCmd a = Put a | Undo | Redo deriving (...) The coolness of GADTs is that you can have different constructors in your datatype for different type parameters: data Expr p where Plain :: a -> Expr a Add :: Num a => Expr a -> Expr a -> Expr a If :: Expr Bool -> Expr a -> Expr a -> Expr a And :: Expr Bool -> Expr Bool -> Expr Bool ... And you can pattern match on these constructors for different types in one function: eval :: Expr a -> a eval (Plain x) = x eval (Add e1 e2) = eval e1 + eval e2 eval (If eb t f) = if eval eb then eval t else eval f eval (And e1 e2) = eval e1 && eval e2 ...
Patrick

On 15 April 2010 00:15, Daniel Fischer
... And you can pattern match on these constructors for different types in one function:
eval :: Expr a -> a eval (Plain x) = x eval (Add e1 e2) = eval e1 + eval e2 eval (If eb t f) = if eval eb then eval t else eval f eval (And e1 e2) = eval e1 && eval e2 ...
but sadly you cannot have template haskell on them. sorry to distract the op's question, but i am in trouble with trying to use them both. see this* sad and lonely thread, if you want to know what i'm talking about. * http://www.haskell.org/pipermail/haskell-cafe/2010-April/076267.html -- Ozgur Akgun

Instead of keeping a list of Put/Undo/Redo commands, it may be easier to keep a pair of stacks of states, representing past states (which can be restored when you 'Undo') and "future" states (which are restored when you 'Redo'). That is, you can think of the state as a list of values with a "current" position; put and get operate on the current position, and undo/redo let you move back/forward in the list. (In other words - a list zipper!) In fact, you can find this code already implemented on the Haskell wiki: http://haskell.org/haskellwiki/New_monads/MonadUndo Doesn't look like it's on Hackage though. -Brent On Thu, Apr 15, 2010 at 12:15:09AM +0200, edgar klerks wrote:
Hi All,
I wanted to write the statemonad in a different way, because I want to track mutations to the state. And also to be able to undo an done or redo an undone mutation. Therefore I wrote a small dsl with an evaluator, which finds out the current state.
The problem is, I don't know how to create a get and put function for my monad. I have a function which evaluate the state and gives back the current State.
Can someone help me a bit along? I have the feeling I do something wrong, but I am not sure what.
With kind regards,
Edgar
{-# LANGUAGE GADTs,DeriveFunctor #-} import Control.Monad import Data.Maybe
data StateCmd a where Put :: a -> StateCmd a Undo :: StateCmd a Redo :: StateCmd a deriving (Show, Functor)
newtype State s a = State { unState :: ([StateCmd s],a) } deriving Show
joinState :: State s a -> State s b -> State s b joinState (State (xs, a)) (State (ys, b)) = State (xs ++ ys, b)
instance Monad (State s) where return a = State $ ([], a) (>>=) = bindState
-- m a -> ( a -> m b) -> m b bindState st@(State (_,a)) f = st `joinState` st' where st' = f a
unPut :: StateCmd a -> Maybe a unPut (Put a) = Just a unPut _ = Nothing
test = State $ ([Put 4, Undo, Redo, Undo, Put 5, Undo, Redo, Put 6, Undo, Redo, Undo], ())
getCurrent = fromJust.unPut.head.snd.(foldr current' ([],[])).reverse.fst.unState where current' x (ul,cl) = case x of Put n -> (ul, Put n : cl) Undo -> (head cl : ul, tail cl) Redo -> (tail ul, head ul : cl) _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (6)
-
Brent Yorgey
-
Daniel Fischer
-
edgar klerks
-
HASHIMOTO, Yusaku
-
Ozgur Akgun
-
Patrick LeBoutillier