Re: [Haskell-cafe] What is <-

That was my suspicion. So, you can't change horses (monads) in mid-stream.
A parallel question:
main = do ... -- in the IO monad
I know I can have other *do*s in main,
if foo
then do
.
.
else do
.
.
but must all these other *do*s also be in the same IO monad? What determines what monad a *do* is "in"? The first line after the *do*?
Thanks for your patience.
Michael
--- On Sun, 8/8/10, Henning Thielemann
How would I print each of these integers, one per line?
[1,2,3,4,5] >>= \x -> ?
You can't do this from inside the List monad, but you can easily do it from outside, since the result of a 'do' block in List monad is just a list. mapM_ print [1..5] or mapM_ print $ do x <- [1..] ... return (x+y+z)

On Sun, 8 Aug 2010, michael rice wrote:
That was my suspicion. So, you can't change horses (monads) in mid-stream.
A parallel question:
main = do ... -- in the IO monad
I know I can have other *do*s in main,
if foo then do . . else do . .
but must all these other *do*s also be in the same IO monad? What determines what monad a *do* is "in"? The first line after the *do*?
'do' is just syntactic sugar that is expanded to '>>=' and '>>' combinators. Determining the monad is the task of type inference. Since x, y and (if b then x else y) must have the same type, so if they are monadic actions, they are all of the same monad type.

michael rice wrote:
That was my suspicion. So, you can't change horses (monads) in mid-stream.
A parallel question:
main = do ... -- in the IO monad
I know I can have other *do*s in main,
if foo then do . . else do . .
but must all these other *do*s also be in the same IO monad?
Yes, if you write it like that, they have to. Let us take as an example (in the IO monad): f = do x <- getLine if null x then y else z Desugaring gives: f = getLine >>= (\x -> if null x then y else z) Since getLine :: IO String and (>>=) :: Monad m => m a -> (a -> m b) -> m b, we see that m = IO a = String So the type of (\x -> if null x then y else z) in the above expression will be String -> IO b. This means that the parameter x will be of type String, and "if null x then y else z" will be of type IO b. This implies that y and z both will be of type IO b. So if you write y and z as a do-block, this will be in the IO monad. However, there is no special rule that says "in an expression all do-blocks must have the same type". E.g., the following is a valid expression: do -- in the Maybe monad. return Nothing listToMaybe $ do -- in the [] monad. return 4 What
determines what monad a *do* is "in"? The first line after the *do*?
Type inference. E.g. f = do return [] will be of type Monad m => m [a]. There is nothing special about monads in this regard, only the "do"-notation is special: it is desugared as described elsewhere in the thread and in the Report. HTH, Jochem -- Jochem Berndsen | jochem@functor.nl
participants (3)
-
Henning Thielemann
-
Jochem Berndsen
-
michael rice