[GHC] #15708: Cross-module SPECIALZE pragmas aren't typechecked in -O0
GHC
ghc-devs at haskell.org
Fri Oct 5 13:35:10 UTC 2018
#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
More information about the ghc-tickets
mailing list