[GHC] #12040: Code that builds on 7.8.4 and 7.10.3 but fails with requiring UndecidableInstances on 8.0.1-rc4
GHC
ghc-devs at haskell.org
Thu May 19 19:23:35 UTC 2016
#12040: Code that builds on 7.8.4 and 7.10.3 but fails with requiring
UndecidableInstances on 8.0.1-rc4
-------------------------------------+-------------------------------------
Reporter: dmcclean | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.0.1
checker) |
Resolution: | Keywords:
Operating System: Linux | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by thomie):
* component: Compiler => Compiler (Type checker)
Comment:
Here is a reduced testcase, without any dependencies.
{{{#!hs
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
module T12040 where
import Data.Proxy
-- src/Numeric/Units/Dimensional/Variant.hs
data Variant = DQuantity
-- src/Numeric/Units/Dimensional/Internal.hs
class KnownVariant (v :: Variant) where
data Dimensional v :: Dimension -> * -> *
instance KnownVariant 'DQuantity where
newtype Dimensional 'DQuantity d a = Quantity a
type Quantity = Dimensional 'DQuantity
-- ' -- src/Numeric/Units/Dimensional/Dimensions/TypeLevel.hs
data Dimension = Dim -- TypeInt TypeInt TypeInt TypeInt TypeInt TypeInt
TypeInt
class HasDynamicDimension a where
class HasDynamicDimension a => HasDimension a where
type KnownDimension (d :: Dimension) = HasDimension (Proxy d)
-- src/Numeric/Units/Dimensional/Dynamic.hs
class Demotable (q :: * -> *) where
instance (KnownDimension d) => Demotable (Quantity d) where
}}}
{{{
$ ghc-7.10.3 T12040.hs -v0
# ok
$ ghc-8.0.1 T12040.hs -v0
T12040.hs:45:10: error:
• The constraint ‘KnownDimension d’
is no smaller than the instance head
(Use UndecidableInstances to permit this)
• In the instance declaration for ‘Demotable (Quantity d)’
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12040#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list