Do notation for monad in function returning a different type - haskell

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)]

Related

Best way to apply arguments of mixed, possibly Applicative, types to a function

I'm fairly new to Haskell and functional programming and I have recently been learning about Functors, Applicatives and Monads. While I seem to understand the basics, I have trouble figuring out the best/most idiomatic way apply function arguments when the type of some arguments changes to an Applicative. Consider the following, simple code:
myfun :: Int -> Int -> Int -> Int
myfun a b c = a + b + c -- lets pretend this does something more complicated
a = 5
b = 10
c = 20
result = myfun a b c
Using myfun to calculate the result is fairly straightforward. However, as our requirements change, our inputs a, b and c may change to be i.e. Maybe Int or [Int] rather then Int. We can still use our unmodified myfun by doing one of the following:
result = myfun <$> a <*> b <*> c -- either like this
result = liftA3 myfun a b c -- or like that
However, in practice the arguments a, b and c may not always end up to be inside the same Applicative, and thus the two methods mentioned above would not work. What is the best way to still make the myfun function work without modifying it? Consider the following scenarios for a, b and c:
Some are Int, some are Maybe Int (result of the application would be Maybe Int)
Some are Maybe Int, some are Either String Int (result could be Maybe Int or Either String Int, with the semantics of short-circuiting the calculation if any argument is Nothing or Left)
Some are [Int], some are Maybe Int (result should be Maybe [Int], with the semantics of calculating all possible combinations as if all arguments were [Int], then wrapping that inside a Just, unless on of the Maybies are Nothing, in which case we short-circuit to Nothing)
Any insights are very much appreciated!
It depends on what you want to happen. There may not be any universal way to combine different monads. In general, you can often (always?) use a monad transformer when you truly need to combine different monads, but usually there are simpler solutions. That's the case with the specific combinations you mention.
In all of these specific cases, you can transform one of the monads into another. In the following, I'll give some examples of ways this could be done.
Some of these examples use functions from Data.Maybe, so I'll start with:
import Data.Maybe
It's not required in the first example, but will be in the second and third.
Some Int, some Maybe Int
If you have a combination of Int and Maybe Int values, the solution is straightforward. Just elevate the Int values to Maybe Int. You can use Just or pure for this. Here's an example using pure:
a1 = 5
b1 = Just 10
c1 = 20
result1 :: Maybe Int
result1 = myfun <$> pure a1 <*> b1 <*> pure c1
The result is Just 35.
Some Maybe Int, some Either String Int
You can repeat the trick with transforming one of the monads into the other. You can transform Maybe Int values to Either String Int values if you have a good String to use for Nothing cases. You can also transform Either String Int values to Maybe Int values by throwing away the String values.
Here's an example that transforms Maybe Int to Either String Int:
a2 = Just 5
b2 = Right 10
c2 = Left "Boo!"
result2 :: Either String Int
result2 = myfun <$> maybe (Left "No value") Right a2 <*> b2 <*> c2
This combination uses the maybe function from Data.Maybe. The result is Left "Boo!".
Some [Int], some Maybe Int
You can easily turn Maybe Int into [Int] using maybeToList:
a3 = [5, 10]
b3 = Nothing
c3 = Just 20
result3 :: [Int]
result3 = myfun <$> a3 <*> maybeToList b3 <*> maybeToList c3
The result of doing this is [] because Nothing transforms to [], and that's how Applicative works for lists. This may not be what you want, but I hope these examples can inspire you to come up with the compositions you'd like.
As mentioned in other answers, here perhaps it doesn't make much sense to preserve the distinctions between the Applictatives, it would be better to reduce them to a single one before applying them to myfun.
But sometimes it is convenient to preserve the distinctions. The good news is that Applicatives compose, meaning that the "nesting" of two or more Applicatives can always be given an Applicative instance.
For example, we could define a combined Applicative like this:
{-# LANGUAGE DerivingVia, TypeOperators #-}
import Data.Functor.Compose
newtype A a = A (Either String (Maybe [a]))
deriving (Functor,Applicative)
via Either String `Compose` Maybe `Compose` []
We are using -XDerivingVia in our own auxiliary datatype to avoid having to work with nested Compose newtypes, which would be a bit more cumbersome.
Applicative composition works "from the outer layer inwards". That is, if there's a Left somehwere, all the computation ends with a Left. If the outer layer succeeds, then we combine the inner Maybes, and if they all turn to be Just, we applicatively combine the inner lists.
We also need some tedious boilerplate: injection functions into our combined Applicative:
liftL1 :: Either String a -> A a
liftL1 = A . fmap (pure . pure)
liftL2 :: Maybe a -> A a
liftL2 = A . pure . fmap pure
liftL3 :: [a] -> A a
liftL3 = A . pure . pure
Putting it to work:
a = Right 5
b = Just 10
c = [20]
result = liftA3 myfun (liftL1 a) (liftL2 b) (liftL3 c)
Or, using -XApplicativeDo:
result = do
a <- liftL1 $ Right 5
b <- liftL2 $ Just 10
c <- liftL3 $ [20]
pure $ myfun a b c

How can I generate random numbers in Haskell without IO in a range?

I would like to generate random numbers in a range and the type signature to be Int -> Int. I've read multiple other posts but none of them suggested ways to return a type Int. I used System.IO.Unsafe in my code but it is not recommended to do so. Here's my code:
import System.IO.Unsafe
-- random number generator
rng :: Int -> Int
rng upper = unsafePerformIO $ randomRIO (0,upper-1)
Does anyone have any suggests on how to generate random Int in a range in Haskell?
Edit: It might be impossible to change IO Int -> Int so I converted my code to
-- random number generator
rng :: Int -> IO Int
rng upper = randomRIO (0,upper-1)
The reason why I need a rng is because I want to get random numbers within the range length of the list to get an index for an element of a list.
list !! rng (length list) but I'm getting the error Couldn't match expected type ‘Int’ with actual type ‘IO Int’ which is expected.
It's not a duplicate because 1. I want values in a range, 2. my rng does not return the same values. I'm new to Haskell and I don't know how to manipulate Monads. Any help is appreciated.
I the spirit of https://xkcd.com/221/, here's a “solution” without any IO:
rng :: Int -> Int
rng upper
| upper<=4 = upper
| otherwise = 4
So that gives you an “RFC 1149.5 compliant random number”. It's always four, unless that is outside the range.
What's the problem with this? Well, clearly it gives always the same number – and so it must be, because all Haskell functions must be functions, i.e. referentially transparent. OTOH, a random number generator is supposed to give different number each time you call it... it is thus not a function, and most other programming languages merely pretend it is a function with side-effect – because they have no proper means to express what side-effects are. Well, Haskell does have a proper means of expressing that, and it is the IO monad: you can have computations that depend on a side effect, but clearly these computations if you run them will then have that side-effect themselves.In that light, the signature Int -> IO Int does make sense for the function. (This is a function, but the result is an IO action and only executing that action gives you an Int.)
What's ugly about that is that IO Int could literally do anything in IO – it could, for instance, launch some missiles and give you back the number of casualities. More realistically, it could easily modify some file in you home directory. Whereas what you want is actually just a teeny tiny harmless side-effect, just enough to produce a new random number the next time. Usually, random number generators are anyways not really random but PRNGs, which keep a constant-size state variable that is updated in a random-looking way each time you pull a value. The next time, this state will be different and thus you get a different value, as desired. This state variable could be held in an IO-mutable location
import Data.IORef
type RandStV = Int
type RandSt = IORef RandStV
rng' :: RandSt -> Int -> IO Int
rng' rSt upper = do
x <- readIORef rSt
let x' = ((x * 1103515245) + 12345) `mod` 0x7fffffff -- https://sourceware.org/git/?p=glibc.git;a=blob;f=stdlib/random_r.c;hb=glibc-2.26#l362
writeIORef rSt x'
return $ x `mod` upper
...or, you could just explicitly pass the updated state along with the result
rng'' :: Int -> RandStV -> (RandStV, Int)
rng'' upper x =
let x' = ((x * 1103515245) + 12345) `mod` 0x7fffffff
in (x', x `mod` upper)
...or it could be passed around in a dedicated state monad, which is just another way of writing the passing-on of an updated variable:
type RandStM = State RandStV
rng''' :: Int -> RandStM Int
rng''' upper = do
x <- get
let x' = ((x * 1103515245) + 12345) `mod` 0x7fffffff
put x'
return $ x `mod` upper
See the random-fu package for useful helpers on such a random monad.
One mathematical way to interpret rng''' is to say it is a function that takes an upper bound as the argument and gives you back a distribution of numbers. The distribution is always the same, but it “contains” many numbers together with the probability of them occuring. Actually generating an integer means you're sampling from the distribution.
Haskell was not built to generate random numbers without using IO.
Your example, list !! rng (length list), doesn't work because rng returns IO Int and !! expects a Int.
Here is a function that uses your rng function to get a random element from a list:
-- Will crash on empty list
randomElementFromList :: [a] -> IO a
randomElementFromList list = do
r <- rng (length list)
return $ list !! r

simple function error "Variable not in scope" haskell

I have just started to code Haskell today, stuck on building function that takes an integer from user, multiply it by 3, adds one and checks if it is Even. returns the output as Boolean, true if even.
Sorry if the code is too faulty, I'm a Haskell newbie.
checkIfEven :: Int -> Bool
x <- readLn
let checkIfEven x = (even ((x*3)+1))
print checkIfEven
error:
Variable not in scope: checkIfEven :: Int -> Bool
I/O has to be handled explicitly in Haskell, as readLn is not a function; it's an IO action. It is simpler to start with a true function that takes the value to check as an argument:
checkIfEven :: Int -> Bool
checkIfEven x = even (x*3 + 1)
Note that the parentheses are not part of the call to even, but rather "grouping" the expression x * 3 + 1, as even x*3 + 1 is parsed as (even x) * 3 + 1.
Now that we have a pure function, we can apply it to a value input by the user.
program :: IO Bool
program = do
x <- readLn
return (checkIfEven (read x))
A few things to note:
<- is not an assignment operator; it's special syntax inside a do construct with "extracts" a value from (in this context) an IO action.
x will be a string, so you need to parse it to get an Int value for checkIfEven. read is a simple way to do that; we're ignoring the possibility that the user may enter a string that can not be parsed as an Int.
return doesn't return a value from a function (note we did not use it in the definition of checkIfEven. Rather, it "lifts" a value into a new IO action, has program has to be value of type IO Bool, not Bool.
Note that a do construct provides an imperative-looking way to work with IO actions. You can work directly with the underlying functions and values; in this case, we could have simply written
program = fmap (checkIfEven . read) readLn
The full explanation of how IO (and monads in general) work is beyond the scope of this question; hopefully, this will give you an idea of what to focus on as you study the topic further.

Haskell: How to use random integer from randomRIO in a function that returns a boolean

I am new to Haskell and i'm having a problem with using the IO Int from randomRIO function. My goal is to get a random Int value, say r, and to return True if r < x or false otherwise, but i don't know how to do it.
my function should look like:
randomCompare :: Int->Bool
randomCompare x
| x < r = True -- somehow i want to r <- randomRIO(start,end)
| otherwise = False
I know there is a designed intention with keeping IO vals in context for purity etc.. but i don't see why using a random number for a Boolean function should be "bad".
Thanks.
import System.Random(randomIO)
randomCompare :: Int -> IO Bool
randomCompare x = do
r <- randomIO
return $ x < r
IO is neither good nor bad, it just declares that your function has side effects. Here the side effect is modifying the state of the global random number generator, so that a subsequent call to randomIO will give another number (it wouldn't be random if it was constant !).
IO does force all calling functions to be IO too (the ones that want to use the IO Bool). However, if a calling function is IO only by consuming this IO Bool, if it has no other side effects, then you can separate it as a pure function f :: Bool -> SomeType and functorially apply it on the IO, ie
f <$> randomCompare i
So the IO monad only costs you to replace the ordinary function call $ by the functorial fmap, also noted <$>. Is it so much longer to type ?
If you absolutely want to leave the IO monad (why ?), you can also draw all the random values you need first, store them in a list, then apply pure functions on that list.

State Monad, sequences of random numbers and monadic code

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.

Resources