State Monad, sequences of random numbers and monadic code - haskell

I'm trying to grasp the State Monad and with this purpose I wanted to write a monadic code that would generate a sequence of random numbers using a Linear Congruential Generator (probably not good, but my intention is just to learn the State Monad, not build a good RNG library).
The generator is just this (I want to generate a sequence of Bools for simplicity):
type Seed = Int
random :: Seed -> (Bool, Seed)
random seed = let (a, c, m) = (1664525, 1013904223, 2^32) -- some params for the LCG
seed' = (a*seed + c) `mod` m
in (even seed', seed') -- return True/False if seed' is even/odd
Don't worry about the numbers, this is just an update rule for the seed that (according to Numerical Recipes) should generate a pseudo-random sequence of Ints. Now, if I want to generate random numbers sequentially I'd do:
rand3Bools :: Seed -> ([Bool], Seed)
rand3Bools seed0 = let (b1, seed1) = random seed0
(b2, seed2) = random seed1
(b3, seed3) = random seed2
in ([b1,b2,b3], seed3)
Ok, so I could avoid this boilerplate by using a State Monad:
import Control.Monad.State
data Random {seed :: Seed, value :: Bool}
nextVal = do
Random seed val <- get
let seed' = updateSeed seed
val' = even seed'
put (Random seed' val')
return val'
updateSeed seed = let (a,b,m) = (1664525, 1013904223, 2^32) in (a*seed + c) `mod` m
And finally:
getNRandSt n = replicateM n nextVal
getNRand :: Int -> Seed -> [Bool]
getNRand n seed = evalState (getNRandStates n) (Random seed True)
Ok, this works fine and give me a list of n pseudo-random Bools for each given seed. But...
I can read what I've done (mainly based on this example: http://www.haskell.org/pipermail/beginners/2008-September/000275.html ) and replicate it to do other things. But I don't think I can understand what's really happening behind the do-notation and monadic functions (like replicateM).
Can anyone help me with some of this doubts?
1 - I've tried to desugar the nextVal function to understand what it does, but I couldn't. I can guess it extracts the current state, updates it and then pass the state ahead to the next computation, but this is just based on reading this do-sugar as if it was english.
How do I really desugar this function to the original >>= and return functions step-by-step?
2 - I couldn't grasp what exactly the put and get functions do. I can guess that they "pack" and "unpack" the state. But the mechanics behind the do-sugar is still elusive to me.
Well, any other general remarks about this code are very welcome. I sometimes fell with Haskell that I can create a code that works and do what I expect it to do, but I can't "follow the evaluation" as I'm accustomed to do with imperative programs.

The State monad does look kind of confusing at first; let's do as Norman Ramsey suggested, and walk through how to implement from scratch. Warning, this is pretty lengthy!
First, State has two type parameters: the type of the contained state data and the type of the final result of the computation. We'll use stateData and result respectively as type variables for them here. This makes sense if you think about it; the defining characteristic of a State-based computation is that it modifies a state while producing an output.
Less obvious is that the type constructor takes a function from a state to a modified state and result, like so:
newtype State stateData result = State (stateData -> (result, stateData))
So while the monad is called "State", the actual value wrapped by the the monad is that of a State-based computation, not the actual value of the contained state.
Keeping that in mind, we shouldn't be surprised to find that the function runState used to execute a computation in the State monad is actually nothing more than an accessor for the wrapped function itself, and could be defined like this:
runState (State f) = f
So what does it mean when you define a function that returns a State value? Let's ignore for a moment the fact that State is a monad, and just look at the underlying types. First, consider this function (which doesn't actually do anything with the state):
len2State :: String -> State Int Bool
len2State s = return ((length s) == 2)
If you look at the definition of State, we can see that here the stateData type is Int, and the result type is Bool, so the function wrapped by the data constructor must have the type Int -> (Bool, Int). Now, imagine a State-less version of len2State--obviously, it would have type String -> Bool. So how would you go about converting such a function into one returning a value that fits into a State wrapper?
Well, obviously, the converted function will need to take a second parameter, an Int representing the state value. It also needs to return a state value, another Int. Since we're not actually doing anything with the state in this function, let's just do the obvious thing--pass that int right on through. Here's a State-shaped function, defined in terms of the State-less version:
len2 :: String -> Bool
len2 s = ((length s) == 2)
len2State :: String -> (Int -> (Bool, Int))
len2State s i = (len2' s, i)
But that's kind of silly and redundant. Let's generalize the conversion so that we can pass in the result value, and turn anything into a State-like function.
convert :: Bool -> (Int -> (Bool, Int))
convert r d = (r, d)
len2 s = ((length s) == 2)
len2State :: String -> (Int -> (Bool, Int))
len2State s = convert (len2 s)
What if we want a function that changes the state? Obviously we can't build one with convert, since we wrote that to pass the state through. Let's keep it simple, and write a function to overwrite the state with a new value. What kind of type would it need? It'll need an Int for the new state value, and of course will have to return a function stateData -> (result, stateData), because that's what our State wrapper needs. Overwriting the state value doesn't really have a sensible result value outside the State computation, so our result here will just be (), the zero-element tuple that represents "no value" in Haskell.
overwriteState :: Int -> (Int -> ((), Int))
overwriteState newState _ = ((), newState)
That was easy! Now, let's actually do something with that state data. Let's rewrite len2State from above into something more sensible: we'll compare the string length to the current state value.
lenState :: String -> (Int -> (Bool, Int))
lenState s i = ((length s) == i, i)
Can we generalize this into a converter and a State-less function, like we did before? Not quite as easily. Our len function will need to take the state as an argument, but we don't want it to "know about" state. Awkward, indeed. However, we can write a quick helper function that handles everything for us: we'll give it a function that needs to use the state value, and it'll pass the value in and then package everything back up into a State-shaped function leaving len none the wiser.
useState :: (Int -> Bool) -> Int -> (Bool, Int)
useState f d = (f d, d)
len :: String -> Int -> Bool
len s i = (length s) == i
lenState :: String -> (Int -> (Bool, Int))
lenState s = useState (len s)
Now, the tricky part--what if we want to string these functions together? Let's say we want to use lenState on a string, then double the state value if the result is false, then check the string again, and finally return true if either check did. We have all the parts we need for this task, but writing it all out would be a pain. Can we make a function that automatically chains together two functions that each return State-like functions? Sure thing! We just need to make sure it takes as arguments two things: the State function returned by the first function, and a function that takes the prior function's result type as an argument. Let's see how it turns out:
chainStates :: (Int -> (result1, Int)) -> (result1 -> (Int -> (result2, Int))) -> (Int -> (result2, Int))
chainStates prev f d = let (r, d') = prev d
in f r d'
All this is doing is applying the first state function to some state data, then applying the second function to the result and the modified state data. Simple, right?
Now, the interesting part: Between chainStates and convert, we should almost be able to turn any combination of State-less functions into a State-enabled function! The only thing we need now is a replacement for useState that returns the state data as its result, so that chainStates can pass it along to the functions that don't know anything about the trick we're pulling on them. Also, we'll use lambdas to accept the result from the previous functions and give them temporary names. Okay, let's make this happen:
extractState :: Int -> (Int, Int)
extractState d = (d, d)
chained :: String -> (Int -> (Bool, Int))
chained str = chainStates extractState $ \state1 ->
let check1 = (len str state1) in
chainStates (overwriteState (
if check1
then state1
else state1 * 2)) $ \ _ ->
chainStates extractState $ \state2 ->
let check2 = (len str state2) in
convert (check1 || check2)
And try it out:
> chained "abcd" 2
(True, 4)
> chained "abcd" 3
(False, 6)
> chained "abcd" 4
(True, 4)
> chained "abcdef" 5
(False, 10)
Of course, we can't forget that State is actually a monad that wraps the State-like functions and keeps us away from them, so none of our nifty functions that we've built will help us with the real thing. Or will they? In a shocking twist, it turns out that the real State monad provides all the same functions, under different names:
runState (State s) = s
return r = State (convert r)
(>>=) s f = State (\d -> let (r, d') = (runState s) d in
runState (f r) d')
get = State extractState
put d = State (overwriteState d)
Note that >>= is almost identical to chainStates, but there was no good way to define it using chainStates. So, to wrap things up, we can rewrite the final example using the real State:
chained str = get >>= \state1 ->
let check1 = (len str state1) in
put (if check1
then state1 else state1 * 2) >>= \ _ ->
get >>= \state2 ->
let check2 = (len str state2) in
return (check1 || check2)
Or, all candied up with the equivalent do notation:
chained str = do
state1 <- get
let check1 = len str state1
_ <- put (if check1 then state1 else state1 * 2)
state2 <- get
let check2 = (len str state2)
return (check1 || check2)

First of all, your example is overly complicated because it doesn't need to store the val in the state monad; only the seed is the persistent state. Second, I think you will have better luck if instead of using the standard state monad, you re-implement all of the state monad and its operations yourself, with their types. I think you will learn more this way. Here are a couple of declarations to get you started:
data MyState s a = MyState (s -> (s, b))
get :: Mystate s s
put :: s -> Mystate s ()
Then you can write your own connectives:
unit :: a -> Mystate s a
bind :: Mystate s a -> (a -> Mystate s b) -> Mystate s b
Finally
data Seed = Seed Int
nextVal :: Mystate Seed Bool
As for your trouble desugaring, the do notation you are using is pretty sophisticated.
But desugaring is a line-at-a-time mechanical procedure. As near as I can make out, your code should desugar like this (going back to your original types and code, which I disagree with):
nextVal = get >>= \ Random seed val ->
let seed' = updateSeed seed
val' = even seed'
in put (Random seed' val') >>= \ _ -> return val'
In order to make the nesting structure a bit clearer, I've taken major liberties with the indentation.

You've got a couple great responses. What I do when working with the State monad is in my mind replace State s a with s -> (s,a) (after all, that's really what it is).
You then get a type for bind that looks like:
(>>=) :: (s -> (s,a)) ->
(a -> s -> (s,b)) ->
(s -> (s,b))
and you see that bind is just a specialized kind of function composition operator, like (.)
I wrote a blog/tutorial on the state monad here. It's probably not particularly good, but helped me grok things a little better by writing it.

Related

How and when to use State functor and State applicative?

I've seen the Maybe and Either functor (and applicative) used in code and that made sense, but I have a hard time coming up with an example of the State functor and applicative. Maybe they are not very useful and only exist because the State monad requires a functor and an applicative? There are plenty of explanations of their implementations out there but not any examples when they are used in code, so I'm looking for illustrations of how they might be useful on their own.
I can think of a couple of examples off the top of my head.
First, one common use for State is to manage a counter for the purpose of making some set of "identifiers" unique. So, the state itself is an Int, and the main primitive state operation is to retrieve the current value of the counter and increment it:
-- the state
type S = Int
newInt :: State S Int
newInt = state (\s -> (s, s+1))
The functor instance is then a succinct way of using the same counter for different types of identifiers, such as term- and type-level variables in some language:
type Prefix = String
data Var = Var Prefix Int
data TypeVar = TypeVar Prefix Int
where you generate fresh identifiers like so:
newVar :: Prefix -> State S Var
newVar s = Var s <$> newInt
newTypeVar :: Prefix -> State S TypeVar
newTypeVar s = TypeVar s <$> newInt
The applicative instance is helpful for writing expressions constructed from such unique identifiers. For example, I've used this approach pretty frequently when writing type checkers, which will often construct types with fresh variables, like so:
typeCheckAFunction = ...
let freshFunctionType = ArrowType <$> newTypeVar <*> newTypeVar
...
Here, freshFunctionType is a new a -> b style type with fresh type variables a and b that can be passed along to a unification step.
Second, another use of State is to manage a seed for random number generation. For example, if you want a low-quality but ultra-fast LCG generator for something, you can write:
lcg :: Word32 -> Word32
lcg x = (a * x + c)
where a = 1664525
c = 1013904223
-- monad for random numbers
type L = State Word32
randWord32 :: L Word32
randWord32 = state $ \s -> let s' = lcg s in (s', s')
The functor instance can be used to modify the Word32 output using a pure conversion function:
randUniform :: L Double
randUniform = toUnit <$> randWord32
where toUnit w = fromIntegral w / fromIntegral (maxBound `asTypeOf` w)
while the applicative instance can be used to write primitives that depend on multiple Word32 outputs:
randUniform2 :: L (Double, Double)
randUniform2 = (,) <$> randUniform <*> randUniform
and expressions that use your random numbers in a reasonably natural way:
-- area of a random triangle, say
a = areaOf <$> (Triangle <$> randUniform2 <*> randUniform2 <$> randUniform2)

Do notation for monad in function returning a different type

Is there a way to write do notation for a monad in a function which the return type isn't of said monad?
I have a main function doing most of the logic of the code, supplemented by another function which does some calculations for it in the middle. The supplementary function might fail, which is why it is returning a Maybe value. I'm looking to use the do notation for the returned values in the main function. Giving a generic example:
-- does some computation to two Ints which might fail
compute :: Int -> Int -> Maybe Int
-- actual logic
main :: Int -> Int -> Int
main x y = do
first <- compute x y
second <- compute (x+2) (y+2)
third <- compute (x+4) (y+4)
-- does some Int calculation to first, second and third
What I intend is for first, second, and third to have the actual Int values, taken out of the Maybe context, but doing the way above makes Haskell complain about not being able to match types of Maybe Int with Int.
Is there a way to do this? Or am I heading towards the wrong direction?
Pardon me if some terminology is wrongly used, I'm new to Haskell and still trying to wrap my head around everything.
EDIT
main has to return an Int, without being wrapped in Maybe, as there is another part of the code using the result of mainas Int. The results of a single compute might fail, but they should collectively pass (i.e. at least one would pass) in main, and what I'm looking for is a way to use do notation to take them out of Maybe, do some simple Int calculations to them (e.g. possibly treating any Nothing returned as 0), and return the final value as just Int.
Well the signature is in essence wrong. The result should be a Maybe Int:
main :: Int -> Int -> Maybe Int
main x y = do
first <- compute x y
second <- compute (x+2) (y+2)
third <- compute (x+4) (y+4)
return (first + second + third)
For example here we return (first + second + third), and the return will wrap these in a Just data constructor.
This is because your do block, implicitly uses the >>= of the Monad Maybe, which is defined as:
instance Monad Maybe where
Nothing >>=_ = Nothing
(Just x) >>= f = f x
return = Just
So that means that it will indeed "unpack" values out of a Just data constructor, but in case a Nothing comes out of it, then this means that the result of the entire do block will be Nothing.
This is more or less the convenience the Monad Maybe offers: you can make computations as a chain of succesful actions, and in case one of these fails, the result will be Nothing, otherwise it will be Just result.
You can thus not at the end return an Int instead of a Maybe Int, since it is definitely possible - from the perspective of the types - that one or more computations can return a Nothing.
You can however "post" process the result of the do block, if you for example add a "default" value that will be used in case one of the computations is Nothing, like:
import Data.Maybe(fromMaybe)
main :: Int -> Int -> Int
main x y = fromMaybe 0 $ do
first <- compute x y
second <- compute (x+2) (y+2)
third <- compute (x+4) (y+4)
return (first + second + third)
Here in case the do-block thus returns a Nothing, we replace it with 0 (you can of course add another value in the fromMaybe :: a -> Maybe a -> a as a value in case the computation "fails").
If you want to return the first element in a list of Maybes that is Just, then you can use asum :: (Foldable t, Alternative f) => t (f a) -> f a, so then you can write your main like:
-- first non-failing computation
import Data.Foldable(asum)
import Data.Maybe(fromMaybe)
main :: Int -> Int -> Int
main x y = fromMaybe 0 $ asum [
compute x y
compute (x+2) (y+2)
compute (x+4) (y+4)
]
Note that the asum can still contain only Nothings, so you still need to do some post-processing.
Willem's answer is basically perfect, but just to really drive the point home, let's think about what would happen if you could write something that allows you to return an int.
So you have the main function with type Int -> Int -> Int, let's assume an implementation of your compute function as follows:
compute :: Int -> Int -> Maybe Int
compute a 0 = Nothing
compute a b = Just (a `div` b)
Now this is basically a safe version of the integer division function div :: Int -> Int -> Int that returns a Nothing if the divisor is 0.
If you could write a main function as you like that returns an Int, you'd be able to write the following:
unsafe :: Int
unsafe = main 10 (-2)
This would make the second <- compute ... fail and return a Nothing but now you have to interpret your Nothing as a number which is not good. It defeats the whole purpose of using Maybe monad which captures failure safely. You can, of course, give a default value to Nothing as Willem described, but that's not always appropriate.
More generally, when you're inside a do block you should just think inside "the box" that is the monad and don't try to escape. In some cases like Maybe you might be able to do unMaybe with something like fromMaybe or maybe functions, but not in general.
I have two interpretations of your question, so to answer both of them:
Sum the Maybe Int values that are Just n to get an Int
To sum Maybe Ints while throwing out Nothing values, you can use sum with Data.Maybe.catMaybes :: [Maybe a] -> [a] to throw out Nothing values from a list:
sum . catMaybes $ [compute x y, compute (x+2) (y+2), compute (x+4) (y+4)]
Get the first Maybe Int value that's Just n as an Int
To get the first non-Nothing value, you can use catMaybes combined with listToMaybe :: [a] -> Maybe a to get Just the first value if there is one or Nothing if there isn't and fromMaybe :: a -> Maybe a -> a to convert Nothing to a default value:
fromMaybe 0 . listToMaybe . catMaybes $ [compute x y, compute (x+2) (y+2), compute (x+4) (y+4)]
If you're guaranteed to have at least one succeed, use head instead:
head . catMaybes $ [compute x y, compute (x+2) (y+2), compute (x+4) (y+4)]

confusion over the passing of State monad in Haskell

In Haskell the State is monad is passed around to extract and store state. And in the two following examples, both pass the State monad using >>, and a close verification (by function inlining and reduction) confirms that the state is indeed passed to the next step.
Yet this seems not very intuitive. So does this mean when I want to pass the State monad I just need >> (or the >>= and lambda expression \s -> a where s is not free in a)? Can anyone provide an intuitive explanation for this fact without bothering to reduce the function?
-- the first example
tick :: State Int Int
tick = get >>= \n ->
put (n+1) >>
return n
-- the second example
type GameValue = Int
type GameState = (Bool, Int)
playGame' :: String -> State GameState GameValue
playGame' [] = get >>= \(on, score) -> return score
playGame' (x: xs) = get >>= \(on, score) ->
case x of
'a' | on -> put (on, score+1)
'b' | on -> put (on, score-1)
'c' -> put (not on, score)
_ -> put (on, score)
>> playGame xs
Thanks a lot!
It really boils down to understanding that state is isomorphic to s -> (a, s). So any value "wrapped" in a monadic action is a result of applying a transformation to some state s (a stateful computation producing a).
Passing a state between two stateful computations
f :: a -> State s b
g :: b -> State s c
corresponds to composing them with >=>
f >=> g
or using >>=
\a -> f a >>= g
the result here is
a -> State s c
it is a stateful action that transforms some underlying state s in some way, it is allowed access to some a and it produces some c. So the entire transformation is allowed to depend on a and the value c is allowed to depend on some state s. This is exactly what you would want to express a stateful computation. The neat thing (and the sole purpose of expressing this machinery as a monad) is that you do not have to bother with passing the state around. But to understand how it is done, please refer to the definition of >>= on hackage), just ignore for a moment that it is a transformer rather than a final monad).
m >>= k = StateT $ \ s -> do
~(a, s') <- runStateT m s
runStateT (k a) s'
you can disregard the wrapping and unwrapping using StateT and runStateT, here m is in form s -> (a, s), k is of form a -> (s -> (b, s)), and you wish to produce a stateful transformation s -> (b, s). So the result is going to be a function of s, to produce b you can use k but you need a first, how do you produce a? you can take m and apply it to the state s, you get a modified state s' from the first monadic action m, and you pass that state into (k a) (which is of type s -> (b, s)). It is here that the state s has passed through m to become s' and be passed to k to become some final s''.
For you as a user of this mechanism, this remains hidden, and that is the neat thing about monads. If you want a state to evolve along some computation, you build your computation from small steps that you express as State-actions and you let do-notation or bind (>>=) to do the chaining/passing.
The sole difference between >>= and >> is that you either care or don't care about the non-state result.
a >> b
is in fact equivalent to
a >>= \_ -> b
so what ever value gets output by the action a, you throw it away (keeping only the modified state) and continue (pass the state along) with the other action b.
Regarding you examples
tick :: State Int Int
tick = get >>= \n ->
put (n+1) >>
return n
you can rewrite it in do-notation as
tick = do
n <- get
put (n + 1)
return n
while the first way of writing it makes it maybe more explicit what is passed how, the second way nicely shows how you do not have to care about it.
First get the current state and expose it (get :: s -> (s, s) in a simplified setting), the <- says that you do care about the value and you do not want to throw it away, the underlying state is also passed in the background without a change (that is how get works).
Then put :: s -> (s -> ((), s)), which is equivalent after dropping unnecessary parens to put :: s -> s -> ((), s), takes a value to replace the current state with (the first argument), and produces a stateful action whose result is the uninteresting value () which you drop (because you do not use <- or because you use >> instead of >>=). Due to put the underlying state has changed to n + 1 and as such it is passed on.
return does nothing to the underlying state, it only returns its argument.
To summarise, tick starts with some initial value s it updates it to s+1 internally and outputs s on the side.
The other example works exactly the same way, >> is only used there to throw away the () produced by put. But state gets passed around all the time.

How can I work in nested monads cleanly?

I'm writing an interpreter for a small language.
This language supports mutation, so its evaluator keeps track of a Store for all the variables (where type Store = Map.Map Address Value, type Address = Int, and data Value is a language-specific ADT).
It's also possible for computations to fail (e.g., dividing by zero), so the result has to be an Either String Value.
The type of my interpreter, then, is
eval :: Environment -> Expression -> State Store (Either String Value)
where type Environment = Map.Map Identifier Address keeps track of local bindings.
For example, interpreting a constant literal doesn't need to touch the store, and the result always succeeds, so
eval _ (LiteralExpression v) = return $ Right v
But when we apply a binary operator, we do need to consider the store.
For example, if the user evaluates (+ (x <- (+ x 1)) (x <- (+ x 1))) and x is initially 0, then the final result should be 3, and x should be 2 in the resulting store.
This leads to the case
eval env (BinaryOperator op l r) = do
lval <- eval env l
rval <- eval env r
return $ join $ liftM2 (applyBinop op) lval rval
Note that the do-notation is working within the State Store monad.
Furthermore, the use of return is monomorphic in State Store, while the uses of join and liftM2 are monomorphic in the Either String monad.
That is, here we use
(return . join) :: Either String (Either String Value) -> State Store (Either String Value)
and return . join is not a no-op.
(As is evident, applyBinop :: Identifier -> Value -> Value -> Either String Value.)
This seems confusing at best, and this is a relatively simple case.
The case of function application, for example, is considerably more complicated.
What useful best practices should I know about to keep my code readable—and writable?
EDIT: Here's a more typical example, which better showcases the ugliness.
The NewArrayC variant has parameters length :: Expression and element :: Expression (it creates an array of a given length with all elements initialized to a constant).
A simple example is (newArray 3 "foo"), which yields ["foo", "foo", "foo"], but we could also write (newArray (+ 1 2) (concat "fo" "oo")), because we can have arbitrary expressions in a NewArrayC.
But when we actually call
allocateMany :: Int -> Value -> State Store Address,
which takes the number of elements to allocate and the value for each slot, and returns the starting address, we need to unpack those values.
In the logic below, you can see that I'm duplicating a bunch of logic that should be built-in to the Either monad.
All the cases should just be binds.
eval env (NewArrayC len el) = do
lenVal <- eval env len
elVal <- eval env el
case lenVal of
Right (NumV lenNum) -> case elVal of
Right val -> do
addr <- allocateMany lenNum val
return $ Right $ ArrayV addr lenNum -- result data type
left -> return left
Right _ -> return $ Left "expected number in new-array length"
left -> return left
This is what monad transformers are for. There is a StateT transformer to add state to a stack, and an EitherT transformer to add Either-like failure to a stack; however, I prefer ExceptT (which adds Except-like failure), so I will give my discussion in terms of that. Since you want the stateful bit outermost, you should use ExceptT e (State s) as your monad.
type DSL = ExceptT String (State Store)
Note that the stateful operations can be spelled get and put, and these are polymorphic over all instances of MonadState; so that in particular they will work okay in our DSL monad. Similarly, the canonical way to raise an error is throwError, which is polymorphic over all instances of MonadError String; and in particular will work okay in our DSL monad.
So now we would write
eval :: Environment -> Expression -> DSL Value
eval _ (Literal v) = return v
eval e (Binary op l r) = liftM2 (applyBinop op) (eval e l) (eval e r)
You might also consider giving eval a more polymorphic type; it could return an (MonadError String m, MonadState Store m) => m Value instead of a DSL Value. In fact, for allocateMany, it's important that you give it a polymorphic type:
allocateMany :: MonadState Store m => Int -> Value -> m Address
There's two pieces of interest about this type: first, because it is polymorphic over all MonadState Store m instances, you can be just as sure that it only has stateful side effects as if it had the type Int -> Value -> State Store Address that you suggested. However, also because it is polymorphic, it can be specialized to return a DSL Address, so it can be used in (for example) eval. Your example eval code becomes this:
eval env (NewArrayC len el) = do
lenVal <- eval env len
elVal <- eval env el
case lenVal of
NumV lenNum -> allocateMany lenNum elVal
_ -> throwError "expected number in new-array length"
I think that's quite readable, really; nothing too extraneous there.

project euler 14 using the state monad

I'm trying to teach myself Haskell (again) by working through Project Euler. Question 14 (https://projecteuler.net/problem=14) is begging for dynamic programming and historically I've been vehemently anti-monad (on account of repeatedly failing to learn to use them well enough to make life easier instead of harder) so I'm trying to bite the bullet and use the State monad to memoize my code... it's not going well. I want to be clear, I've already solved the problem the easy/slow way, at this point I'm trying to learn something (ie Project Euler No. 14 Haskell is not what I'm looking for).
My code so far is:
collatzMemoCheck :: Int -> State (Map Int Int) Int
collatzMemoCheck n = state $ \s -> maybe (let (a, s') = runState (collatzFast n) s
in (a+1, Map.insert n (a+1) s'))
(\len -> (len, s))
(Map.lookup n s)
collatzFast :: Int -> State (Map Int Int) Int
collatzFast 1 = state $ \_ -> (1, Map.singleton 1 1)
collatzFast n
| even n = collatzMemoCheck (n `quot` 2)
| otherwise = collatzMemoCheck (3 * n + 1)
which works for individual queries in cabal repl, but for the life of me I can't figure out how to chain up the state of repeated calls to collatzFast. I want something like
-- DOES NOT WORK
allCollatzLengths = scanl (>>= collatzFast) (return Map.empty) [1..999999]
but I think this is inside out. Bind takes the result portion of the previous State computation and passes it to the next call, but I want it to take the state portion of the previous State computation and pass it to the next call.
Is there a right way to do this or have I painted myself into a corner? If I can't use >>=, what's the point of having a monad? ... or is there no point because this is a stupid approach? Help?
You might like
mapM :: Monad m => (a -> m b) -> [a] -> m [b]
In particular, mapM collatzFast :: [Int] -> State (Map Int Int) [Int].

Resources