
I'd add another parameter to the ExprType class and give an explicit
representation to your types.
data EType a where
EInt :: EType Int
EBool :: EType Bool
data TypeEq a b where Refl :: TypeEq x x
eqEType :: ExprType a -> ExprType b -> Maybe (TypeEq a b)
eqEType EInt EInt = Just Refl
eqEType EBool EBool = Just Refl
eqEType _ _ = Nothing
class ExprType a where
toExpr :: a -> Expr a
eType :: EType a
eTypeOf :: Expr a -> EType a
eTypeOf (Bin _) = EBool
eTypeOf (Num _) = EInt
eTypeOf (_ :+: _) = EInt
-- etc.
transform :: (ExprType a, ExprType b) => (Expr b -> Expr b) -> Expr a -> Expr a
transform = transform' eType
-- uses LANGUAGE PatternGuards
transform' :: EType b -> (Expr b -> Expr b) -> Expr a -> Expr a
transform' t f e | Just Refl <- eqEType t (eTypeOf e) = f e -- this
is the magic line
transform' t f (Bin b) = Bin b
tranfsorm' t f (Num i) = Num i
transform' t f (e1 :+: e2) = transform' t f e1 :+: transform' t f e2
-- etc.
The magic line checks if the type of the expression matches the type
of the function, and if so, applies it.
-- ryan
On Tue, Jul 27, 2010 at 8:28 AM, Ozgur Akgun
Café,
I've tried several things already, but I am not including any of them for now. My question is, how would you define the 'transform' function for a GADT, say the one in the linked gist: http://gist.github.com/492364 (also attached to this e-mail)
To be concise, I want 'transform' to apply the transformation function (its first parameter) to every immidiate child of its second parameter as long as the types match. Similar to what the 'tranform' function of Uniplate does for normal ADTs. (But just one level, so I guess it is more similar to the 'descend' of Uniplate. See http://hackage.haskell.org/packages/archive/uniplate/1.2.0.1/doc/html/Data-G...)
I think I got closest to a sensible solution using multi-param type classes, and defining many instances for different combinations of ExprType's but still there were problems.
Waiting for suggestions and/or insights.
Best, Ozgur Akgun
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe