howto mix <- within do?

The attached code produces error: <-- cut here -- runghc -dcore-lint do_with_assignment.proto.hs do_with_assignment.proto.hs:30:2: Couldn't match expected type `[]' against inferred type `IO' Expected type: [t] Inferred type: IO () In the expression: putStr "v0=" In a 'do' expression: putStr "v0="
-- cut here--
However, similar code here: http://www.nabble.com/List-as-input-p19987726.html apparently does work. Is there some compiler option I need to use? The compiler is ghc: ghc --version The Glorious Glasgow Haskell Compilation System, version 6.8.2

Every statement in a do-expression has to be in the same monad. You are mixing the list monad (v0 <- [999]) with the IO monad (putStr "v0="). Instead of v0 <- [999] try: let v0 = [999] Hope this helps, Martijn. Larry Evans wrote:
On 10/17/08 07:39, Larry Evans wrote:
The attached code produces error: <-- cut here -- [snip]
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Am Freitag, 17. Oktober 2008 14:42 schrieb Larry Evans:
On 10/17/08 07:39, Larry Evans wrote:
The attached code produces error: <-- cut here --
[snip] {- Purpose: Explore how to mix 'assignments' inside do. Motivation: Instead of: let { v0 = e0 ; v1 = e1 } in do { print v0 ; print v1 } which is hard to read, recode above as: do { v0 = e0 ; print v0 ; v1 = e1 ; print v1 }
That would have to be do let v0 = e0 print v0 let v1 = e1 print v1 or do v0 <- return e0 print v0 v1 <- return e1 print v1 (better (?): do print $ e0 print $ e1 )
which is easier to read and more intuitive for c++ programmers.
"intuitive for c++ programmers" is dangerous, the languages are very different, and one shouldn't gloss over that. The different syntax should help to not confound the languages.
Example_code_suggesting_should_work: http://www.nabble.com/List-as-input-p19987726.html -} module Main where import Data.List main = do { v0 <- [999] ; putStr "v0=" ; print v0 }
remember that in do value <- action statements -- using value (or not) action and statements must belong to the same monad. In your code above, the 'action' [999] has type Num a => [a], so the monad is [], but putStr "v0=" has type IO (), the monad is IO. So the binding v0 <- [999] and the statement putStr "v0=" can't appear in the same do-block. If what you want is "for every member of some list, do some monadic action", you need mapM/mapM_ resp forM(_): mapM(_) (\v -> putStr "v0=" >> print v) [999] or forM(_) [999] $ (putStr "v0=" >>) . print especially forM_ list $ \v -> do some actions with v looks pretty imperative.

On 10/17/08 08:12, Daniel Fischer wrote: Thanks very much Daniel.
Am Freitag, 17. Oktober 2008 14:42 schrieb Larry Evans:
On 10/17/08 07:39, Larry Evans wrote:
The attached code produces error: <-- cut here -- [snip] {- Purpose: Explore how to mix 'assignments' inside do. Motivation: Instead of: let { v0 = e0 ; v1 = e1 } in do { print v0 ; print v1 } which is hard to read, recode above as: do { v0 = e0 ; print v0 ; v1 = e1 ; print v1 }
That would have to be do let v0 = e0 print v0 let v1 = e1 print v1
or do v0 <- return e0 print v0 v1 <- return e1 print v1
(better (?): do print $ e0 print $ e1 )
At first, the |let v = e| combination looked best (less typing). However, my actual e0 was more complicated: array_complete [ Expr <== Op0 GramOne , Term <== Op0 GramOne , Factor <== Op0 GramOne ] where <== was a binary operator which just produced a tuple pair. I wanted to keep the expression on multiple lines because it's easier to read. The <== was defined to make the expression look more like grammar productions (the Op0 GramOne is not the final rhs. That's only for testing purposes.). Unfortunately, using let with the multiline rhs failed to compile (due, I guess, to some layout rules, which I find difficult to fathom). So, I tried the | v <- return e| combination. This worked although I had to surround e with parenthesis to enable compilation with multiple lines: ; gram_eqs::GramEqs ArithInp ArithVar <- return (array_complete [ Expr <== Op0 GramOne , Term <== Op0 GramOne , Factor <== Op0 GramOne ]) ; putStr "gram_eqs=" ; print gram_eqs I didn't use the last combination |print $ e0| because e1 may use v0. IOW: v0 <- return e0 v1 <- return ...v0...
which is easier to read and more intuitive for c++ programmers.
"intuitive for c++ programmers" is dangerous, the languages are very different, and one shouldn't gloss over that. The different syntax should help to not confound the languages.
OK, but I'm finding it very difficult to figure out how to do something that's very simple in c++: ; calculate e0 ; store e0 in v0 ; print v0 ; calculate e1 using possibly v0 ; store e1 in v1 ; print v1 However, apparently, in haskell, the operands on each side of the ';' must be "compatible". Hmmm, I remember seeing a translation of more complex haskell statments/expression to simpler ones... looking... http://haskell.org/onlinereport/exps.html#sect3.14 Mea culpa :( I should have read that first. Then a would have realized: (v0 <- e0) >> putStr "v0" would not have worked because, I guess: e0 >> putStr "v0" would not work. OOPS, sect3.14 has a specialization on the pattern p<-e. That specialization is harder to understand. I'll work on it :) [snip]
remember that in
do value <- action statements -- using value (or not)
action and statements must belong to the same monad. In your code above, the 'action' [999] has type Num a => [a], so the monad is [], but putStr "v0=" has type IO (), the monad is IO. So the binding v0 <- [999] and the statement putStr "v0=" can't appear in the same do-block.
If what you want is "for every member of some list, do some monadic action", you need mapM/mapM_ resp forM(_):
Nope. I just want to trace through various stages in translation of a language grammar(a set of "grammar equationss") to a corresponding set of equations defining the lookahead sets for that grammar. So, I want the do{...} to just be a sequence of (calculate value; print value} where calculate value may use previously calculated values). Thanks for you help. -regards, Larry

Am Freitag, 17. Oktober 2008 17:56 schrieb Larry Evans:
On 10/17/08 08:12, Daniel Fischer wrote:
At first, the |let v = e| combination looked best (less typing). However, my actual e0 was more complicated:
array_complete [ Expr <== Op0 GramOne , Term <== Op0 GramOne , Factor <== Op0 GramOne ]
where <== was a binary operator which just produced a tuple pair. I wanted to keep the expression on multiple lines because it's easier to read. The <== was defined to make the expression look more like grammar productions (the Op0 GramOne is not the final rhs. That's only for testing purposes.).
Unfortunately, using let with the multiline rhs failed to compile (due, I guess, to some layout rules, which I find difficult to fathom).
It would be no problem if you used only layout. The problem is that you used braces and semicolons for the do-block, but not for the let. You would have to write it like do { let { v0 = e0 } ; print v0 } , i.e. also use braces for the let block. If you write do { let v0 = e0 ; print v0 } it would be parsed as do { let { v0 = e0 ; print v0 } } Either braces and semicolons everywhere or all layout, anything else invites misparsings. HTH, Daniel

On Fri, Oct 17, 2008 at 1:39 PM, Larry Evans
do_with_assignment.proto.hs:30:2: Couldn't match expected type `[]' against inferred type `IO' Expected type: [t] Inferred type: IO () In the expression: putStr "v0=" In a 'do' expression: putStr "v0="
Prelude> let f = do { v <- [999] ; return () } Prelude> :t f f :: [()] Prelude> :t putStr "" putStr "" :: IO () So "v <- [999]" is in the list monad, but putStr is in the IO monad. The two cannot mix in that way. This looks like it might be homework so I'll refrain from saying any more for now. Good luck! D
participants (4)
-
Daniel Fischer
-
Dougal Stanton
-
Larry Evans
-
Martijn van Steenbergen