Quan Ta wrote:
I encountered this problem when trying to compile NewBinary with ghc-6.7 - here isolated it to a small test

$ cat Foo.hs
module Main where

main {- | num_bits == 0 = return ()
| num_bits < 0 = error "putBits cannot write negative numbers of bits" | num_bits > 8 = error "putBits cannot write more than 8 bits at a time"
        | otherwise    -} = do
    putStrLn "Testing parse"


ghc --make Foo.hs
[1 of 1] Compiling Main             ( Foo.hs, Foo.o )

Foo.hs:3:5:
    parse error on input `{- | num_bits == 0 = return ()
| num_bits < 0 = error "putBits cannot write negative numbers of bits" | num_bits > 8 = error "putBits cannot write more than 8 bits at a time"
        | otherwise    -}'
make: *** [Foo.exe] Error 1

There's a bug in the new Haddock support in the lexer that causes this. It's affecting one or two of the nfib programs too. I'll look into it.

Cheers,
        Simon

_______________________________________________
Cvs-ghc mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to