module DatatypesTermInstances where import Datatypes import TermRep {- Generated by DrIFT (Automatic class derivations for Haskell) -} {-# LINE 1 "Datatypes.hs" #-} {-* Generated by DrIFT : Look, but Don't Touch. *-} instance Term Type where explode (x::Type) = TermRep (toDyn x, f x, g x) where f (TVar aa) = [explode aa] f (Arrow ab ac) = [explode ab,explode ac] g (TVar _) xs = case TermRep.fArgs xs of [aa] -> toDyn ((TVar (TermRep.fDyn aa))::Type) ; _ -> error "Term explosion error." g (Arrow _ _) xs = case TermRep.fArgs xs of [ab,ac] -> toDyn ((Arrow (TermRep.fDyn ab) (TermRep.fDyn ac))::Type) ; _ -> error "Term explosion error." _tc_TypeTc = mkTyCon "Type" instance Typeable Type where typeOf x = mkTyConApp _tc_TypeTc [ ] instance Term Expr where explode (x::Expr) = TermRep (toDyn x, f x, g x) where f (Var aa) = [explode aa] f (Apply ab ac) = [explode ab,explode ac] f (Lambda ad ae af) = [explode ad,explode ae,explode af] g (Var _) xs = case TermRep.fArgs xs of [aa] -> toDyn ((Var (TermRep.fDyn aa))::Expr) ; _ -> error "Term explosion error." g (Apply _ _) xs = case TermRep.fArgs xs of [ab,ac] -> toDyn ((Apply (TermRep.fDyn ab) (TermRep.fDyn ac))::Expr) ; _ -> error "Term explosion error." g (Lambda _ _ _) xs = case TermRep.fArgs xs of [ad,ae,af] -> toDyn ((Lambda (TermRep.fDyn ad) (TermRep.fDyn ae) (TermRep.fDyn af))::Expr) ; _ -> error "Term explosion error." _tc_ExprTc = mkTyCon "Expr" instance Typeable Expr where typeOf x = mkTyConApp _tc_ExprTc [ ] -- Imported from other files :-