Re: #s causing errors when -cpp not given

2002-02-01 Thread Ian Lynagh

On Mon, Jan 28, 2002 at 05:25:29PM -, Simon Marlow wrote:
 
 You're right, it seems that our 'unlit' program (the filter used to
 convert a literate file into an illiterate one) leaves lines beginning
 with '#' in place.
 
 We could remove this, but I'm not sure how much code it would break.  We

As far as I can think the only code which should break is code like
this:

 module Main where

 (#) = (++)

 main = putStrLn x
   where { x = foo
# bar #
 baz }

(which in GHC prints foobarbaz) which deserves to be broken IMO!

 could also do this conditionally based on a flag to unlit which would be
 turned on if we're planning to CPP the file, but there's another
 problem: sometimes we use {-#OPTIONS -cpp#-} at the top of the file to
 indicate that cpp is to be used, so we don't know whether we're going to
 be cpp'ing until after we've unlitted the file :-(

I would advocate only allowing #s where code is allowed, but I fear that
ship has sailed  :-(
It would also be less simple with  being replaced by a space rather
than removed.


Ian


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: #s causing errors when -cpp not given

2002-01-28 Thread Simon Marlow

 I've just been looking at using cpp in Haskell scripts and I am rather
 confused. I can't see anything in the report which gives 
 special meaning
 to # in the surrounding text of literate scripts, yet if I put such
 things in (both cpp directives and random things) both nhc98 and ghc
 give me errors:
 
 $ rm Foo.{o,hi}; nhc98 -c Foo.lhs -o Foo.o 
 Unknown preprocessor directive at line 4 in file ./Foo.lhs
 ifdef QQ
 
 $ rm Foo.{o,hi}; ghc -c Foo.lhs -o Foo.o 
 Foo.lhs:4: parse error on input `#'
 
 Are ghc and nhc98 being incompatible with Haskell 98?

GHC has one small extension to Haskell 98 in this area: the lexical
analyser interprets directives line '# 99 Foo.hs' at the beginning of
a line in order to get line number and file clues when it is parsing the
output from CPP.  Apart from this, '#' should be interpreted exactly as
per the report (when -fglasgow-exts is off).

Could you send us the source?

Cheers,
Simon

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell