[Haskell-cafe] Re: Comparing GADTs for Eq and Ord

Tom Hawkins tomahawkins at gmail.com
Wed Sep 17 00:12:29 EDT 2008


Thanks for all the input.  It helped me arrive at the following
solution.  I took the strategy of converting the parameterized type
into an unparameterized type which can be easily compared for Eq and
Ord.  The unparameterized type enumerates the possible Const types
with help from an auxiliary type class.

-- The primary Expr type.
data Expr a where
  Const :: ExprConst a => a -> Expr a
  Equal :: Expr a -> Expr a -> Expr Bool

-- An "untyped" Expr used to compute Eq and Ord of the former.
-- Note each type of constant is enumerated.
data UExpr
  = UConstBool   Bool
  | UConstInt    Int
  | UConstFloat  Float
  | UEqual UExpr UExpr
  deriving (Eq, Ord)

-- A type class to assist in converting Expr to UExpr.
class    ExprConst a     where uexprConst :: a -> UExpr
instance ExprConst Bool  where uexprConst = UConstBool
instance ExprConst Int   where uexprConst = UConstInt
instance ExprConst Float where uexprConst = UConstFloat

-- The conversion function.
uexpr :: Expr a -> UExpr
uexpr (Const a) = uexprConst a
uexpr (Equal a b) = UEqual (uexpr a) (uexpr b)

-- Finally the implementation of Eq and Ord for Expr.
instance Eq  (Expr a) where a == b = uexpr a == uexpr b
instance Ord (Expr a) where compare a b = compare (uexpr a) (uexpr b)


More information about the Haskell-Cafe mailing list