[nhc-bugs] RE: Literate scripts not handled correctly

Simon Marlow simonmar@microsoft.com
Tue, 18 Sep 2001 12:21:58 +0100


> My understanding is that the following script:
>=20
> ----- cut here -----
>=20
> > foo :: Int -> Int
> > foo _ =3D 2
>=20
> \begin{code}
>=20
> bar :: Int -> Int
> bar _ =3D 1
>=20
> \end{code}
>=20
> ----- cut here -----
>=20
> should be valid and define foo and bar (although the report=20
> does say "It
> is not advisable to mix these two styles in the same file").
>=20
> However, in hugs:
> ERROR Q.lhs:7 - Syntax error in input (unexpected symbol "bar")

This is probably due to layout.  The unliterate version of the file
would be

 foo :: Int -> Int
 foo _ =3D 2

bar :: Int -> Int
bar _ =3D 1

so the occurrence of the token 'bar' at a column less than that of the
first 'foo' causes a close brace to be inserted by the layout system,
closing the top-level declaration group.

> Secondly, in the following script (which I think should define main
> according to the report):
>=20
> ----- cut here -----
>=20
>     \begin{code}
>=20
> module Main where
>=20
> main :: IO()
> main =3D putStrLn "Foo"
>=20
>     \end{code}
>=20
> ----- cut here -----
>=20
> hugs:
> ERROR W.lhs:12 - Empty script - perhaps you forgot the `>'s?
>=20
> % nhc98 -c -o W.o W.lhs
> Warning: Can not find main in module Main.
>=20
> ghc -c -o W.o W.lhs=20
> W.lhs line 11: unlit: missing \end{code}
>=20
> Interestingly it works in GHC if you remove the white space before the
> end but not before the begin.

Yes, it looks like GHC's unlit program removes whitespace when looking
for \begin{code}, but not for \end{code}.  The report isn't explicit
about whether whitespace is allowed on these lines, but I would tend to
the view that it isn't.

Cheers,
	Simon