The flag -P for traditional gnu cpp (or --noline for stand-alone cpphs) should suppress the initial #line noise.

Does ghc still fail to recognise a module-start pragma, even if the only characters preceding it are whitespace?

I intended to give an example.

---- file foo.h ----
#if __GLASGOW_HASKELL__ == 604
#define PRAGMA(foo) {-# OPTIONS_GHC -X foo #-}
#else
#define PRAGMA(foo) {-# LANGUAGE foo #-}

---- file Bar.hs ----
#include "foo.h"
PRAGMA(MyLanguageOption)
module Bar where

---- result ----
$ ghc-6.8.2 -E -cpp -optP-P Bar.hs
$ cat Bar.hspp
{-# LINE 1 "Bar.hs" #-}



{-# LANGUAGE MyLanguageOption #-}
module Bar where

$ ghc-6.4.1 -E -cpp -optP-P Bar.hs
$ cat Bar.hspp

{-# OPTIONS_GHC -X MyLanguageOption #-}
module Bar where





_______________________________________________
Glasgow-haskell-users mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to