[GHC] #16018: Disabling core optimizations ignores code that would otherwise warn.

#16018: Disabling core optimizations ignores code that would otherwise warn. -------------------------------------+------------------------------------- Reporter: dmjio | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.2 Component: Compiler | Version: 8.4.3 Keywords: core, | Operating System: Unknown/Multiple optimizations, Wall | Architecture: x86 | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Given the below code snippet, {{{#!hs module Main where main :: IO () main = putStrLn "hey" data StopLight = Red | Green | Yellow deriving (Show, Eq) data Intersection = Intersection { light :: {-# UNPACK #-} !StopLight } deriving (Show, Eq) }}} The above code will warn with optimizations enabled (`ghc -Wall -O2 Main.hs`), message below: ''' Main.hs:13:5: warning: • Ignoring unusable UNPACK pragma on the first argument of ‘Intersection’ • In the definition of data constructor ‘Intersection’ In the data type declaration for ‘Intersection’ | 13 | = Intersection ''' Without optimizations, no warnings are emitted `ghc -Wall -O0 Main.hs`. The desired behavior should be a warning emitted in both cases. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16018 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16018: Disabling core optimizations ignores code that would otherwise warn. -------------------------------------+------------------------------------- Reporter: dmjio | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.2 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: core, | optimizations, Wall Operating System: Linux | Architecture: x86 Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dmjio): * os: Unknown/Multiple => Linux -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16018#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16018: Disabling core optimizations ignores code that would otherwise warn. -------------------------------------+------------------------------------- Reporter: dmjio | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.2 Component: Compiler | Version: 8.4.3 Resolution: | Keywords: core, | optimizations, Wall Operating System: Linux | Architecture: x86 Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Old description:
Given the below code snippet,
{{{#!hs module Main where
main :: IO () main = putStrLn "hey"
data StopLight = Red | Green | Yellow deriving (Show, Eq)
data Intersection = Intersection { light :: {-# UNPACK #-} !StopLight } deriving (Show, Eq) }}}
The above code will warn with optimizations enabled (`ghc -Wall -O2 Main.hs`), message below: ''' Main.hs:13:5: warning: • Ignoring unusable UNPACK pragma on the first argument of ‘Intersection’ • In the definition of data constructor ‘Intersection’ In the data type declaration for ‘Intersection’ | 13 | = Intersection '''
Without optimizations, no warnings are emitted `ghc -Wall -O0 Main.hs`.
The desired behavior should be a warning emitted in both cases.
New description: Given the below code snippet, {{{#!hs module Main where main :: IO () main = putStrLn "hey" data StopLight = Red | Green | Yellow deriving (Show, Eq) data Intersection = Intersection { light :: {-# UNPACK #-} !StopLight } deriving (Show, Eq) }}} The above code will warn with optimizations enabled (`ghc -Wall -O2 Main.hs`), message below: {{{ Main.hs:13:5: warning: • Ignoring unusable UNPACK pragma on the first argument of ‘Intersection’ • In the definition of data constructor ‘Intersection’ In the data type declaration for ‘Intersection’ | 13 | = Intersection }}} Without optimizations, no warnings are emitted `ghc -Wall -O0 Main.hs`. The desired behavior should be a warning emitted in both cases. -- Comment (by bgamari): I believe this may be similar to #9370. In short, whether we represent field unpackedness (and strictness) in the AST is determined by whether we have compiled with `-O`. More concretely, we drop the unpack pragma in `MkId.dataConSrcToImplBang` in the case of `-O0`. This is really an awful design and should be changed. As described in #9370, we should rather always include these sorts of pragmas in the AST and ignore them in the simplifier if optimisation is disabled. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16018#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC