[GHC] #15708: Cross-module SPECIALZE pragmas aren't typechecked in -O0

#15708: Cross-module SPECIALZE pragmas aren't typechecked in -O0 -------------------------------------+------------------------------------- Reporter: regnat | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC accepts Unknown/Multiple | invalid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- If a module defines a `SPECIALIZE` pragma for a value defined in another module, then the signature of this pragma won't be typecheck by `ghc -O0` (but it will be if the `SPECIALIZE` pragma is in the same module as the value). For example, given {{{#!hs -- Foo.hs module Foo where foo :: a -> a foo = id ---------- -- Bar.hs module Bar where import Foo {-# SPECIALIZE foo :: Int -> Bool #-} }}} running `ghc --make Bar.hs` will run fine, while `ghc --make -O2 Bar.hs` will complain: {{{ Bar.hs:5:1: error: • Couldn't match type ‘Bool’ with ‘Int’ Expected type: Int -> Int Actual type: Int -> Bool • In the SPECIALISE pragma {-# SPECIALIZE foo :: Int -> Bool #-} | 5 | {-# SPECIALIZE foo :: Int -> Bool #-} | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ }}} Tested on ghc 8.6.1 and 8.4.3 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15708 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15708: Cross-module SPECIALZE pragmas aren't typechecked in -O0 -------------------------------------+------------------------------------- Reporter: regnat | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.6.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Currently that's by-design: without -O we just treat SPECIALISE pragmas as comments. Could easily be changed if that what our users wanted: we could type check the pragma and then discard it (because we are doing -O0). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15708#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15708: Cross-module SPECIALZE pragmas aren't typechecked in -O0 -------------------------------------+------------------------------------- Reporter: regnat | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.6.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by regnat):
without -O we just treat SPECIALISE pragmas as comments.
That seems not to be exactly the case in practice: if the SPECIALISE pragma is in the same module as the definition then I get an error. Regardless of that, I find this a bit surprising: I would have expected that as much as possible whether a program is valid or not doesn't depend on the optimization level (which obviously isn't possible to guaranty in the general case because of things like the RULE pragma, but as you mentioned this doesn't cost much to check). Or do I overlook another good reason for not typechecking these pragmas? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15708#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC