[GHC] #13918: No "warning: [-Wunrecognised-pragmas] Unrecognised pragma" when there is no name of pragmas

#13918: No "warning: [-Wunrecognised-pragmas] Unrecognised pragma" when there is no name of pragmas -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect Unknown/Multiple | error/warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{ module Qwer where a = ({-# LANGUAGE #-}) main :: IO () main = print (if True then () else ()) }}} if {{{a = ({-# #-})}}} then GHC compiles with a warning\\ {{{ qwer.hs:3:6: warning: [-Wunrecognised-pragmas] Unrecognised pragma | 3 | a = ({-# #-}) | ^^^ Ok, modules loaded: Qwer. }}} if you write {{{a = ({-# LANGUAGE #-})}}} without writing the name GHC compiles the file without specifying a warning.\\ {{{ *Qwer> :l qwer.hs [1 of 1] Compiling Qwer ( qwer.hs, interpreted ) Ok, modules loaded: Qwer. }}} GHCi, version 8.2.0.20170507 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13918 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13918: No "warning: [-Wunrecognised-pragmas] Unrecognised pragma" when there is no name of pragmas -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by j.waldmann): What do think is the error here? An individual language pragma begins with the keyword LANGUAGE and is followed by a comma-separated list of named language features https://www.haskell.org/onlinereport/haskell2010/haskellch12.html#x19-191000... This list can be empty (it does not say otherwise), so `{-# LANGUAGE #-}` is fine. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13918#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13918: No "warning: [-Wunrecognised-pragmas] Unrecognised pragma" when there is no name of pragmas -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): Replying to [[span(style=color: #FF0000, j.waldmann )]]\\
This list can be empty\\ About LANGUAGE pragma, Can you quote the reference manual in which you read this sentence, please, and show me the page?
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13918#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13918: No "warning: [-Wunrecognised-pragmas] Unrecognised pragma" when there is no name of pragmas -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari):
About LANGUAGE pragma, Can you quote the reference manual in which you read this sentence, please, and show me the page?
It's never said terribly explicitly, that being said I think it's pretty reasonable to assume for syntactic consistency. That being said, I am a bit surprised that a LANGUAGE pragma is accepted here at all. Afterall, it's a file pragma and therefore should only occur before the `module` declaration. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13918#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13918: No "warning: [-Wunrecognised-pragmas] Unrecognised pragma" when there is no name of pragmas -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): I have opened #13921 to track the `LANGUAGE` pragma placement infelicity. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13918#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

An implementation is not required to respect any pragma, although pragmas that are not recognised by the implementation should be ignored.\\ Hello Ben,\\ Did you take a look at ticket {{{#13917}}}? He talks about the same thing from a different angle. Maybe this is interesting for the continuation of
#13918: No "warning: [-Wunrecognised-pragmas] Unrecognised pragma" when there is no name of pragmas -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): Replying to [[span(style=color: #FF0000, bgamari )]]\\ From ticket #13921\\ the ticket that you opened?(i.e ticket #13921) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13918#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC