Re: [GHC] #5401: LANGUAGE pragma parser nit

2012-10-25 Thread GHC
#5401: LANGUAGE pragma parser nit
--+-
Reporter:  nwf|   Owner:  igloo
Type:  bug|  Status:  new  
Priority:  normal |   Milestone:  7.6.2
   Component:  Compiler (Parser)  | Version:  7.0.3
Keywords: |  Os:  Linux
Architecture:  x86_64 (amd64) | Failure:  GHC rejects valid program
  Difficulty:  Unknown|Testcase:   
   Blockedby: |Blocking:   
 Related: |  
--+-
Changes (by igloo):

  * difficulty:  = Unknown


Old description:

 A language pragma like

 {-# LANGUAGE
 TypeOperators,
 FlexibleContexts #-}

 parses just fine but

 {-# LANGUAGE
 TypeOperators,
 FlexibleContexts
 #-}

 doesn't, saying:

 Cannot parse LANGUAGE pragma
 Expecting comma-separated list of language options,
 each starting with a capital letter

 An OPTIONS pragma, on the other hand, accepts either format without
 complaint.

New description:

 A language pragma like
 {{{
 {-# LANGUAGE
 TypeOperators,
 FlexibleContexts #-}
 }}}
 parses just fine but
 {{{
 {-# LANGUAGE
 TypeOperators,
 FlexibleContexts
 #-}
 }}}
 doesn't, saying:
 {{{
 Cannot parse LANGUAGE pragma
 Expecting comma-separated list of language options,
 each starting with a capital letter
 }}}
 An OPTIONS pragma, on the other hand, accepts either format without
 complaint.

--

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5401#comment:4
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #5401: LANGUAGE pragma parser nit

2011-11-23 Thread GHC
#5401: LANGUAGE pragma parser nit
--+-
Reporter:  nwf|Owner:  igloo
Type:  bug|   Status:  new  
Priority:  normal |Milestone:  7.6.1
   Component:  Compiler (Parser)  |  Version:  7.0.3
Keywords: | Testcase:   
   Blockedby: |   Difficulty:   
  Os:  Linux  | Blocking:   
Architecture:  x86_64 (amd64) |  Failure:  GHC rejects valid program
--+-
Changes (by igloo):

  * owner:  = igloo
  * milestone:  = 7.6.1


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5401#comment:2
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #5401: LANGUAGE pragma parser nit

2011-08-13 Thread GHC
#5401: LANGUAGE pragma parser nit
---+
Reporter:  nwf |   Owner:   
Type:  bug |  Status:  new  
Priority:  normal  |   Component:  Compiler (Parser)
 Version:  7.0.3   |Keywords:   
Testcase:  |   Blockedby:   
  Os:  Linux   |Blocking:   
Architecture:  x86_64 (amd64)  | Failure:  GHC rejects valid program
---+

Comment(by daniel.is.fischer):

 The user's guide says
 {{{
 The layout rule applies in pragmas, so the closing #-} should start in a
 column to the right of the opening {-#.
 }}}
 The language report doesn't mention any such restrictions though, so
 perhaps it should be listed in Bugs and infelicities (supposing the parse
 can't easily be changed to accept the `#-}` anywhere).

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5401#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs