[Haskell-cafe] Simple GADTs, type families and type classes combination with type error.

Serguey Zefirov sergueyz at gmail.com
Fri Jul 22 17:12:38 CEST 2011


Why does GHC complains on the code below ? (I'll explain in a second a
requirement to do just so)

I get errors with ghc 6.12.1 and 7.0.2.

---------------------------------------------------------------------------------------------------------------------
{-# LANGUAGE GADTs, TypeFamilies #-}

class CPU cpu where
	type CPUFunc cpu

data Expr cpu where
	EVar :: String -> Expr cpu
	EFunc :: CPU cpu => CPUFunc cpu -> Expr cpu

class CPU cpu => FuncVars cpu where
	funcVars :: CPUFunc cpu -> [String]

exprVars :: FuncVars cpu => Expr cpu -> [String]
exprVars (EVar v) = [v]
-- an offending line:
exprVars (EFunc f) = funcVars f
---------------------------------------------------------------------------------------------------------------------

I tried to split creation and analysis constraints. CPU required for
creation of expressions, FuncVars required for analysis. It all looks
nice but didn't work.

(In our real code EVar is slightly more complicated, featuring "Var
cpu" argument)

It looks like GHC cannot relate parameters "inside" and "outside" of
GADT constructor.

Not that I hesitate to add a method to a CPU class, but I think it is
not the right thing to do. So if I can split my task into two classes,
I will feel better.



More information about the Haskell-Cafe mailing list