[GHC] #5821: SPECIALISE fails with a cryptic warning
GHC
ghc-devs at haskell.org
Thu Jan 8 21:02:29 UTC 2015
#5821: SPECIALISE fails with a cryptic warning
-------------------------------------+-------------------------------------
Reporter: rl | Owner: ezyang
Type: bug | Status: new
Priority: normal | Milestone: 7.10.1
Component: Compiler | Version: 7.5
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect | Unknown/Multiple
warning at compile-time | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Description changed by ezyang:
Old description:
> Example:
>
> {{{
> type family T a
> type instance T Int = Bool
>
> foo :: Num a => a -> T a
> foo = undefined
>
> {-# SPECIALISE foo :: Int -> Bool #-}
> }}}
>
> GHC produces this warning:
>
> {{{
> RULE left-hand side too complicated to desugar
> case cobox of _ { GHC.Types.Eq# cobox ->
> (foo @ Int $dNum)
> `cast` (<Int> -> cobox :: (Int -> T Int) ~# (Int -> Bool))
> }
> }}}
>
> Given that rewrite rules don't reliably work in the presence of type
> families, I somewhat suspect that GHC won't be able to generate a
> sensible specialisation here but it should produce a better diagnostic.
New description:
Example:
{{{
{-# LANGUAGE TypeFamilies #-}
module A where
type family T a
type instance T Int = Bool
foo :: Num a => a -> T a
foo = undefined
{-# SPECIALISE foo :: Int -> Bool #-}
}}}
GHC produces this warning:
{{{
RULE left-hand side too complicated to desugar
case cobox of _ { GHC.Types.Eq# cobox ->
(foo @ Int $dNum)
`cast` (<Int> -> cobox :: (Int -> T Int) ~# (Int -> Bool))
}
}}}
Given that rewrite rules don't reliably work in the presence of type
families, I somewhat suspect that GHC won't be able to generate a sensible
specialisation here but it should produce a better diagnostic.
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/5821#comment:10>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list