Strangeness with FunDeps
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTSyntax #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FunctionalDependencies #-}
import GHC.TypeLits
data (:::) :: Symbol -> * -> * where
Field :: sy ::: t
class Replaced (sy :: Symbol) a b (xs :: [*]) (ys :: [*]) | sy a b xs -> ys, sy a b ys -> xs
instance Replaced sy a b ((sy ::: a) ': xs) ((sy ::: b) ': ys)
results in
Illegal instance declaration for [...]
Multiple uses of this instance may be inconsistent
with the functional dependencies of the class
The guess is that the FunDep Checker chokes on [*], as that error message doesn't make sense in this context.
What I'm trying to do is to express "xs is ys and ys is xs with a and b interchanged at sy", all in a single predicate because my current type family implementation needs two and explodes the inferred types.
Trac metadata
Trac field | Value |
---|---|
Version | 7.7 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |