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

aditya siram aditya.siram at gmail.com
Fri Jul 22 18:15:48 CEST 2011


I just had a problem closely related to this on StackOverflow [1]
which was explained beautifully by cammcann.

The problem is that because "type CPUFunc cpu" is located inside the
definition of the class "CPU" it creates the illusion that they are
somehow tied together where "CPUFunc" is somehow in the "CPU"
namespace. It isn't. "CPUFunc" is actually defined globally and the
compiler would complain if you tried to create a CPUFunc type anywhere
else in your code.

The solution is the make "CPUFunc" a brand new datatype by changing
"type CPUFunc cpu" to "data CPUFunc cpu" .

-deech


[1] http://stackoverflow.com/questions/6663547/writing-a-function-polymorphic-in-a-type-family

On Fri, Jul 22, 2011 at 10:12 AM, Serguey Zefirov <sergueyz at gmail.com> wrote:
> 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.
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



More information about the Haskell-Cafe mailing list