[Haskell-cafe] OPPS,
missing attachment (was Re: howto mix <- within do?
Daniel Fischer
daniel.is.fischer at web.de
Fri Oct 17 09:12:49 EDT 2008
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.
More information about the Haskell-Cafe
mailing list