#3428: Wrong pragma parsing
--------------------+-------------------------------------------------------
Reporter:  boris    |          Owner:                   
    Type:  bug      |         Status:  new              
Priority:  normal   |      Component:  Compiler (Parser)
 Version:  6.10.2   |       Severity:  normal           
Keywords:  pragma   |       Testcase:                   
      Os:  Windows  |   Architecture:  x86              
--------------------+-------------------------------------------------------
 If I write the following code with pragma LANGUAGE and extension
 concatenated, ghci complains about unrecognized pragma but loads module.
 {{{
 {-# LANGUAGEExistentialQuantification #-}
 module TestHS where

 data ShowBox = forall s.Show s => SB s
 instance Show ShowBox where
   show (SB s) = show s

 list :: [ShowBox]
 list = [SB "sdf", SB 4, SB True, SB (Nothing::Maybe())]
 }}}

 If pragma is not recognized, the extension ExistentialQuantification
 should not be loaded and so file should not compile. Another strange thing
 is that when I :reload file in ghci it does not complain about pragma
 anymore. It is needed to close ghci and open it once again to see error
 about not recognized pragma.

 Also I think that if pragma concatenated with following information is
 legal it will give ambiguity for cases like adding pragma SPECIAL with
 existing pragma SPECIALIZE.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3428>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to