State and Maybe and monad transformers

Greetings All, I am writing code using a BankersDequeue from Data.Dequeue. I’d like to wrap the push and pop operations in a state monad for the standard reason, to avoid passing the dequeue around between function calls, and regard it as state instead, which it is. Wishing to avoid throwing a runtime error if the queue is empty (for the general case of queues) I have written a reduction of the concept using a crude stack to experiment, which uses State and Maybe. I notice that there are very few examples of using State and Maybe together. My questions are: Is this a faulty design pattern? Should this be done with monad transformers? Are there examples to be found of using State with Maybe as a monad transformer combination? Why is this pattern relatively rare, it seems? Is this program on the right track? Andrew — snip module Main where import Control.Monad.State type Stack = [Int] popIt :: Stack -> (Maybe Int, Stack) popIt [] = (Nothing, []) popIt (x:xs) = (Just x, xs) pop :: State Stack (Maybe Int) pop = state popIt push :: Int -> State Stack (Maybe ()) push a = state $ \xs -> (Just (), a:xs) main = do let a = evalState (do push 3 push 2 push 1 pop pop a <- pop return a ) [] print a — snip

Andrew,
It looks like you're quickly going to hit a point where MaybeT is helpful
to you.
https://hackage.haskell.org/package/transformers-0.4.3.0/docs/Control-Monad-...
This gives you a trick to ignore the fact that you're getting a maybe and
make MaybeT terminate the computation early if there was nothing on the
stack to make further computations with.
It will involve making the leap from simple monads to transformers though,
which can be tricky but is worthwhile in the long run.
There is a fairly succinct explanation of all of this, here:
https://wiki.haskell.org/Monad_Transformers_Tutorial
It's just based on IO rather than State, but that makes little difference
to the concept.
Typing this out in a rush at work, so apologies in advance if this doesn't
make any sense. ;)
Cheers,
Ben
On Wed, 30 Sep 2015 at 14:22 Andrew Bernard
Greetings All,
I am writing code using a BankersDequeue from Data.Dequeue. I’d like to wrap the push and pop operations in a state monad for the standard reason, to avoid passing the dequeue around between function calls, and regard it as state instead, which it is. Wishing to avoid throwing a runtime error if the queue is empty (for the general case of queues) I have written a reduction of the concept using a crude stack to experiment, which uses State and Maybe. I notice that there are very few examples of using State and Maybe together. My questions are: Is this a faulty design pattern? Should this be done with monad transformers? Are there examples to be found of using State with Maybe as a monad transformer combination? Why is this pattern relatively rare, it seems? Is this program on the right track?
Andrew
— snip
module Main where
import Control.Monad.State
type Stack = [Int]
popIt :: Stack -> (Maybe Int, Stack) popIt [] = (Nothing, []) popIt (x:xs) = (Just x, xs)
pop :: State Stack (Maybe Int) pop = state popIt
push :: Int -> State Stack (Maybe ()) push a = state $ \xs -> (Just (), a:xs)
main = do let a = evalState (do push 3 push 2 push 1 pop pop a <- pop return a ) [] print a
— snip
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
participants (2)
-
Andrew Bernard
-
Ben Kolera