[Haskell-cafe] Impossible class instance?

Emil Axelsson emax at chalmers.se
Mon May 16 12:19:38 CEST 2011


Hello!

At the end of this message is a program with a simple expression type, 
and a class `ToExpr` that generalizes expressions to arbitrary Haskell 
types. Every node in `Expr` is annotated with some abstract information. 
The program raises the following type error:

test.hs:13:5:
     Couldn't match type `(,) a' with `(,) (a, a)'
     Inaccessible code in the instance declaration
     In the instance declaration for `ToExpr (a, b)'

It seems that the mere existence of the constraint

   info (a,b) ~ (info a, info b)

causes this error. I was hoping that this constraint would make it 
possible to construct the value (ia,ib) in the class instance, which is 
otherwise not allowed.

Note: I don't want to make `info` an associated type. The idea is to 
make this work with any type function `info` that fulfills the above 
constraint.

Is there any way to make this work?

/ Emil


--------------------

{-# LANGUAGE UndecidableInstances #-}

data Expr info a
   where
     Int  :: info a     -> Int -> Expr info a
     Pair :: info (a,b) -> Expr info a -> Expr info b -> Expr info (a,b)

getInfo :: Expr info a -> info a
getInfo (Int info _)    = info
getInfo (Pair info _ _) = info

class ToExpr a
   where
     type Internal a
     toExpr :: a -> Expr info (Internal a)

instance
     ( ToExpr a
     , ToExpr b
     , info (a,b) ~ (info a, info b)
     ) =>
       ToExpr (a,b)
   where
     type Internal (a,b) = (Internal a, Internal b)
     toExpr (a,b) = Pair (ia,ib) (toExpr a) (toExpr b)
       where
         ia = getInfo a
         ib = getInfo b





More information about the Haskell-Cafe mailing list