[GHC] #15593: QuantifiedConstraints: trouble with type family
GHC
ghc-devs at haskell.org
Sun Sep 2 11:38:56 UTC 2018
#15593: QuantifiedConstraints: trouble with type family
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.5
Keywords: | Operating System: Unknown/Multiple
QuantifiedConstraints, |
ConstraintKinds |
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
{{{#!hs
{-# Language KindSignatures, TypeFamilies, QuantifiedConstraints,
FlexibleInstances #-}
import Data.Kind
data TreeF a b = T0 | T1 a | T2 b b
-- from Data.Reify
class MuRef (a :: Type) where
type DeRef a :: Type -> Type
class (forall xx. DeRef (tree xx) ~ TreeF xx) => MuRef1 tree
instance (forall xx. DeRef (tree xx) ~ TreeF xx) => MuRef1 tree
}}}
fails with
{{{
$ ~/code/qc-ghc/inplace/bin/ghc-stage2 --interactive -ignore-dot-ghci
351.hs
GHCi, version 8.5.20180128: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling Main ( 351.hs, interpreted )
351.hs:12:10: error:
• Couldn't match type ‘DeRef (tree xx)’ with ‘TreeF xx’
arising from the superclasses of an instance declaration
• In the instance declaration for ‘MuRef1 tree’
|
12 | instance (forall xx. DeRef (tree xx) ~ TreeF xx) => MuRef1 tree
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Failed, no modules loaded.
Prelude>
}}}
----
What I want to write:
{{{#!hs
{-# Language KindSignatures, TypeFamilies, QuantifiedConstraints,
FlexibleInstances, DataKinds, TypeInType, MultiParamTypeClasses,
UndecidableInstances, AllowAmbiguousTypes #-}
import Data.Kind
-- from Data.Reify
class MuRef (a :: Type) where
type DeRef a :: Type -> Type
type T = Type
type TT = T -> T
type TTT = T -> TT
class (forall xx. (MuRef (f xx), DeRef (f xx) ~ deRef1 f xx)) => MuRef1
(f :: TT) (deRef1 :: TT -> TTT)
instance (forall xx. (MuRef (f xx), DeRef (f xx) ~ deRef1 f xx)) => MuRef1
(f :: TT) (deRef1 :: TT -> TTT)
}}}
where I am trying to capture
[https://hackage.haskell.org/package/folds-0.7.4/docs/src/Data-Fold-
Internal.html MuRef1 & DeRef1]
{{{#!hs
class MuRef1 (f :: TT) where
type DeRef1 f :: TTT
muRef1 :: proxy (f a) -> Dict (MuRef (f a), DeRef (f a) ~ DeRef1 f a)
}}}
----
Workarounds: I think splitting the class alias & quantification does the
job (I haven't tested it but it compiles), I want to know if the first two
programs are meant to compile or not
{{{#!hs
{-# Language KindSignatures, TypeFamilies, QuantifiedConstraints,
FlexibleInstances, DataKinds, TypeInType, MultiParamTypeClasses,
UndecidableInstances, AllowAmbiguousTypes, FlexibleContexts #-}
-- ..
class (MuRef (f xx), DeRef (f xx) ~ deRef1 f xx) => MuRef1_ f deRef1 xx
instance (MuRef (f xx), DeRef (f xx) ~ deRef1 f xx) => MuRef1_ f deRef1 xx
class (forall xx. cls xx) => Forall cls
instance (forall xx. cls xx) => Forall cls
class Forall (MuRef1_ f deRef1) => MuRef1 f deRef1
instance Forall (MuRef1_ f deRef1) => MuRef1 f deRef1
}}}
or as a regular type/constraint synonym (at the loss of partial
application)
{{{#!hs
type MuRef1 f deRef1 = (forall xx. (MuRef (f xx), DeRef (f xx) ~ deRef1 f
xx))
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15593>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list