
#8356: Strangeness with FunDeps ----------------------------+---------------------------------------------- Reporter: ksf | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects valid program Unknown/Multiple | Test Case: Difficulty: Unknown | Blocking: Blocked By: | Related Tickets: | ----------------------------+---------------------------------------------- {{{ {-# 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. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8356 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler