Hello, the following code doesn't compile

<snip>
module Matrix 
    where

import Control.Monad.ST
import Data.Array.ST
import Data.Array.Unboxed

type Block s = STUArray s Int Double
data MMatrix s = MMatrix Int Int (Block s)

newMatrix_ :: Int -> Int -> ST s (MMatrix s)
newMatrix_ m n = do b <- newArray_ (1, m*n) 
                    return (MMatrix m n b)

runMatrix = do _A <- newMatrix_ 3 3
               _B <- newMatrix_ 3 3 
               matMul _A _B
               return "Success"

main = show $ runST runMatrix

matMul :: MMatrix s -> MMatrix s -> ST s (MMatrix s)
--matMul a b = do let foo = 2*5
                --return a
matMul a b = do { let foo = 2*5; return a }
</snip>

under ghc 6.4.1, yielding the error message:

question.hs:25:41: parse error on input `<-'
Failed, modules loaded: none.

The offending is line the one containing "let foo = 2*5", which is a little
test I've done of let-clauses. Now, suppose instead that for the last function,
matMul, I replace the version that's commented out.  No errors! 

Could someone enlighten me as to why? I'm a bit confused, as I thought the two
forms are equivalent save for formatting...

This is on the back of a email discussion that I was reading about let-clauses, 
in which someone declared that they where better than where clauses for monadic
code. If anyone could comment on this, I'd appreciate it as well.

Many thanks in advance,
Martin
_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to