module SyntaxTermInstances where import Language.Haskell.Syntax import TermRep {- Generated by DrIFT (Automatic class derivations for Haskell) -} {-# LINE 1 "/usr/lib/hugs/libraries/Language/Haskell/Syntax.hs" #-} {-* Generated by DrIFT : Look, but Don't Touch. *-} instance Term SrcLoc where explode (x::SrcLoc) = TermRep (toDyn x, f x, g x) where f (SrcLoc aa ab ac) = [explode aa,explode ab,explode ac] g (SrcLoc _ _ _) xs = case TermRep.fArgs xs of [aa,ab,ac] -> toDyn ((SrcLoc (TermRep.fDyn aa) (TermRep.fDyn ab) (TermRep.fDyn ac))::SrcLoc) ; _ -> error "Term explosion error." -- _tc_SrcLocTc = mkTyCon "SrcLoc" -- instance Typeable SrcLoc where -- typeOf x = mkTyConApp _tc_SrcLocTc [ ] instance Term Module where explode (x::Module) = TermRep (toDyn x, f x, g x) where f (Module aa) = [explode aa] g (Module _) xs = case TermRep.fArgs xs of [aa] -> toDyn ((Module (TermRep.fDyn aa))::Module) ; _ -> error "Term explosion error." -- _tc_ModuleTc = mkTyCon "Module" -- instance Typeable Module where -- typeOf x = mkTyConApp _tc_ModuleTc [ ] instance Term HsSpecialCon where explode (x::HsSpecialCon) = TermRep (toDyn x, f x, g x) where f HsUnitCon = [] f HsListCon = [] f HsFunCon = [] f (HsTupleCon aa) = [explode aa] f HsCons = [] g HsUnitCon xs = case TermRep.fArgs xs of [] -> toDyn ((HsUnitCon)::HsSpecialCon) ; _ -> error "Term explosion error." g HsListCon xs = case TermRep.fArgs xs of [] -> toDyn ((HsListCon)::HsSpecialCon) ; _ -> error "Term explosion error." g HsFunCon xs = case TermRep.fArgs xs of [] -> toDyn ((HsFunCon)::HsSpecialCon) ; _ -> error "Term explosion error." g (HsTupleCon _) xs = case TermRep.fArgs xs of [aa] -> toDyn ((HsTupleCon (TermRep.fDyn aa))::HsSpecialCon) ; _ -> error "Term explosion error." g HsCons xs = case TermRep.fArgs xs of [] -> toDyn ((HsCons)::HsSpecialCon) ; _ -> error "Term explosion error." -- _tc_HsSpecialConTc = mkTyCon "HsSpecialCon" -- instance Typeable HsSpecialCon where -- typeOf x = mkTyConApp _tc_HsSpecialConTc [ ] instance Term HsQName where explode (x::HsQName) = TermRep (toDyn x, f x, g x) where f (Qual aa ab) = [explode aa,explode ab] f (UnQual ac) = [explode ac] f (Special ad) = [explode ad] g (Qual _ _) xs = case TermRep.fArgs xs of [aa,ab] -> toDyn ((Qual (TermRep.fDyn aa) (TermRep.fDyn ab))::HsQName) ; _ -> error "Term explosion error." g (UnQual _) xs = case TermRep.fArgs xs of [ac] -> toDyn ((UnQual (TermRep.fDyn ac))::HsQName) ; _ -> error "Term explosion error." g (Special _) xs = case TermRep.fArgs xs of [ad] -> toDyn ((Special (TermRep.fDyn ad))::HsQName) ; _ -> error "Term explosion error." -- _tc_HsQNameTc = mkTyCon "HsQName" -- instance Typeable HsQName where -- typeOf x = mkTyConApp _tc_HsQNameTc [ ] instance Term HsName where explode (x::HsName) = TermRep (toDyn x, f x, g x) where f (HsIdent aa) = [explode aa] f (HsSymbol ab) = [explode ab] g (HsIdent _) xs = case TermRep.fArgs xs of [aa] -> toDyn ((HsIdent (TermRep.fDyn aa))::HsName) ; _ -> error "Term explosion error." g (HsSymbol _) xs = case TermRep.fArgs xs of [ab] -> toDyn ((HsSymbol (TermRep.fDyn ab))::HsName) ; _ -> error "Term explosion error." -- _tc_HsNameTc = mkTyCon "HsName" -- instance Typeable HsName where -- typeOf x = mkTyConApp _tc_HsNameTc [ ] instance Term HsQOp where explode (x::HsQOp) = TermRep (toDyn x, f x, g x) where f (HsQVarOp aa) = [explode aa] f (HsQConOp ab) = [explode ab] g (HsQVarOp _) xs = case TermRep.fArgs xs of [aa] -> toDyn ((HsQVarOp (TermRep.fDyn aa))::HsQOp) ; _ -> error "Term explosion error." g (HsQConOp _) xs = case TermRep.fArgs xs of [ab] -> toDyn ((HsQConOp (TermRep.fDyn ab))::HsQOp) ; _ -> error "Term explosion error." -- _tc_HsQOpTc = mkTyCon "HsQOp" -- instance Typeable HsQOp where -- typeOf x = mkTyConApp _tc_HsQOpTc [ ] instance Term HsOp where explode (x::HsOp) = TermRep (toDyn x, f x, g x) where f (HsVarOp aa) = [explode aa] f (HsConOp ab) = [explode ab] g (HsVarOp _) xs = case TermRep.fArgs xs of [aa] -> toDyn ((HsVarOp (TermRep.fDyn aa))::HsOp) ; _ -> error "Term explosion error." g (HsConOp _) xs = case TermRep.fArgs xs of [ab] -> toDyn ((HsConOp (TermRep.fDyn ab))::HsOp) ; _ -> error "Term explosion error." -- _tc_HsOpTc = mkTyCon "HsOp" -- instance Typeable HsOp where -- typeOf x = mkTyConApp _tc_HsOpTc [ ] instance Term HsCName where explode (x::HsCName) = TermRep (toDyn x, f x, g x) where f (HsVarName aa) = [explode aa] f (HsConName ab) = [explode ab] g (HsVarName _) xs = case TermRep.fArgs xs of [aa] -> toDyn ((HsVarName (TermRep.fDyn aa))::HsCName) ; _ -> error "Term explosion error." g (HsConName _) xs = case TermRep.fArgs xs of [ab] -> toDyn ((HsConName (TermRep.fDyn ab))::HsCName) ; _ -> error "Term explosion error." -- _tc_HsCNameTc = mkTyCon "HsCName" -- instance Typeable HsCName where -- typeOf x = mkTyConApp _tc_HsCNameTc [ ] instance Term HsModule where explode (x::HsModule) = TermRep (toDyn x, f x, g x) where f (HsModule aa ab ac ad ae) = [explode aa,explode ab,explode ac,explode ad,explode ae] g (HsModule _ _ _ _ _) xs = case TermRep.fArgs xs of [aa,ab,ac,ad,ae] -> toDyn ((HsModule (TermRep.fDyn aa) (TermRep.fDyn ab) (TermRep.fDyn ac) (TermRep.fDyn ad) (TermRep.fDyn ae))::HsModule) ; _ -> error "Term explosion error." -- _tc_HsModuleTc = mkTyCon "HsModule" -- instance Typeable HsModule where -- typeOf x = mkTyConApp _tc_HsModuleTc [ ] instance Term HsExportSpec where explode (x::HsExportSpec) = TermRep (toDyn x, f x, g x) where f (HsEVar aa) = [explode aa] f (HsEAbs ab) = [explode ab] f (HsEThingAll ac) = [explode ac] f (HsEThingWith ad ae) = [explode ad,explode ae] f (HsEModuleContents af) = [explode af] g (HsEVar _) xs = case TermRep.fArgs xs of [aa] -> toDyn ((HsEVar (TermRep.fDyn aa))::HsExportSpec) ; _ -> error "Term explosion error." g (HsEAbs _) xs = case TermRep.fArgs xs of [ab] -> toDyn ((HsEAbs (TermRep.fDyn ab))::HsExportSpec) ; _ -> error "Term explosion error." g (HsEThingAll _) xs = case TermRep.fArgs xs of [ac] -> toDyn ((HsEThingAll (TermRep.fDyn ac))::HsExportSpec) ; _ -> error "Term explosion error." g (HsEThingWith _ _) xs = case TermRep.fArgs xs of [ad,ae] -> toDyn ((HsEThingWith (TermRep.fDyn ad) (TermRep.fDyn ae))::HsExportSpec) ; _ -> error "Term explosion error." g (HsEModuleContents _) xs = case TermRep.fArgs xs of [af] -> toDyn ((HsEModuleContents (TermRep.fDyn af))::HsExportSpec) ; _ -> error "Term explosion error." -- _tc_HsExportSpecTc = mkTyCon "HsExportSpec" -- instance Typeable HsExportSpec where -- typeOf x = mkTyConApp _tc_HsExportSpecTc [ ] instance Term HsImportDecl where explode (x::HsImportDecl) = TermRep (toDyn x, f x, g x) where f (HsImportDecl aa ab ac ad ae) = [explode aa,explode ab,explode ac,explode ad,explode ae] g (HsImportDecl _ _ _ _ _) xs = case TermRep.fArgs xs of [aa,ab,ac,ad,ae] -> toDyn ((HsImportDecl (TermRep.fDyn aa) (TermRep.fDyn ab) (TermRep.fDyn ac) (TermRep.fDyn ad) (TermRep.fDyn ae))::HsImportDecl) ; _ -> error "Term explosion error." -- _tc_HsImportDeclTc = mkTyCon "HsImportDecl" -- instance Typeable HsImportDecl where -- typeOf x = mkTyConApp _tc_HsImportDeclTc [ ] instance Term HsImportSpec where explode (x::HsImportSpec) = TermRep (toDyn x, f x, g x) where f (HsIVar aa) = [explode aa] f (HsIAbs ab) = [explode ab] f (HsIThingAll ac) = [explode ac] f (HsIThingWith ad ae) = [explode ad,explode ae] g (HsIVar _) xs = case TermRep.fArgs xs of [aa] -> toDyn ((HsIVar (TermRep.fDyn aa))::HsImportSpec) ; _ -> error "Term explosion error." g (HsIAbs _) xs = case TermRep.fArgs xs of [ab] -> toDyn ((HsIAbs (TermRep.fDyn ab))::HsImportSpec) ; _ -> error "Term explosion error." g (HsIThingAll _) xs = case TermRep.fArgs xs of [ac] -> toDyn ((HsIThingAll (TermRep.fDyn ac))::HsImportSpec) ; _ -> error "Term explosion error." g (HsIThingWith _ _) xs = case TermRep.fArgs xs of [ad,ae] -> toDyn ((HsIThingWith (TermRep.fDyn ad) (TermRep.fDyn ae))::HsImportSpec) ; _ -> error "Term explosion error." -- _tc_HsImportSpecTc = mkTyCon "HsImportSpec" -- instance Typeable HsImportSpec where -- typeOf x = mkTyConApp _tc_HsImportSpecTc [ ] instance Term HsAssoc where explode (x::HsAssoc) = TermRep (toDyn x, f x, g x) where f HsAssocNone = [] f HsAssocLeft = [] f HsAssocRight = [] g HsAssocNone xs = case TermRep.fArgs xs of [] -> toDyn ((HsAssocNone)::HsAssoc) ; _ -> error "Term explosion error." g HsAssocLeft xs = case TermRep.fArgs xs of [] -> toDyn ((HsAssocLeft)::HsAssoc) ; _ -> error "Term explosion error." g HsAssocRight xs = case TermRep.fArgs xs of [] -> toDyn ((HsAssocRight)::HsAssoc) ; _ -> error "Term explosion error." -- _tc_HsAssocTc = mkTyCon "HsAssoc" -- instance Typeable HsAssoc where -- typeOf x = mkTyConApp _tc_HsAssocTc [ ] instance Term HsDecl where explode (x::HsDecl) = TermRep (toDyn x, f x, g x) where f (HsTypeDecl aa ab ac ad) = [explode aa,explode ab,explode ac,explode ad] f (HsDataDecl ae af ag ah ai aj) = [explode ae,explode af,explode ag,explode ah,explode ai,explode aj] f (HsInfixDecl ak al am an) = [explode ak,explode al,explode am,explode an] f (HsNewTypeDecl ao ap aq ar as at) = [explode ao,explode ap,explode aq,explode ar,explode as,explode at] f (HsClassDecl au av aw ax ay) = [explode au,explode av,explode aw,explode ax,explode ay] f (HsInstDecl az aA aB aC aD) = [explode az,explode aA,explode aB,explode aC,explode aD] f (HsDefaultDecl aE aF) = [explode aE,explode aF] f (HsTypeSig aG aH aI) = [explode aG,explode aH,explode aI] f (HsFunBind aJ) = [explode aJ] f (HsPatBind aK aL aM aN) = [explode aK,explode aL,explode aM,explode aN] g (HsTypeDecl _ _ _ _) xs = case TermRep.fArgs xs of [aa,ab,ac,ad] -> toDyn ((HsTypeDecl (TermRep.fDyn aa) (TermRep.fDyn ab) (TermRep.fDyn ac) (TermRep.fDyn ad))::HsDecl) ; _ -> error "Term explosion error." g (HsDataDecl _ _ _ _ _ _) xs = case TermRep.fArgs xs of [ae,af,ag,ah,ai,aj] -> toDyn ((HsDataDecl (TermRep.fDyn ae) (TermRep.fDyn af) (TermRep.fDyn ag) (TermRep.fDyn ah) (TermRep.fDyn ai) (TermRep.fDyn aj))::HsDecl) ; _ -> error "Term explosion error." g (HsInfixDecl _ _ _ _) xs = case TermRep.fArgs xs of [ak,al,am,an] -> toDyn ((HsInfixDecl (TermRep.fDyn ak) (TermRep.fDyn al) (TermRep.fDyn am) (TermRep.fDyn an))::HsDecl) ; _ -> error "Term explosion error." g (HsNewTypeDecl _ _ _ _ _ _) xs = case TermRep.fArgs xs of [ao,ap,aq,ar,as,at] -> toDyn ((HsNewTypeDecl (TermRep.fDyn ao) (TermRep.fDyn ap) (TermRep.fDyn aq) (TermRep.fDyn ar) (TermRep.fDyn as) (TermRep.fDyn at))::HsDecl) ; _ -> error "Term explosion error." g (HsClassDecl _ _ _ _ _) xs = case TermRep.fArgs xs of [au,av,aw,ax,ay] -> toDyn ((HsClassDecl (TermRep.fDyn au) (TermRep.fDyn av) (TermRep.fDyn aw) (TermRep.fDyn ax) (TermRep.fDyn ay))::HsDecl) ; _ -> error "Term explosion error." g (HsInstDecl _ _ _ _ _) xs = case TermRep.fArgs xs of [az,aA,aB,aC,aD] -> toDyn ((HsInstDecl (TermRep.fDyn az) (TermRep.fDyn aA) (TermRep.fDyn aB) (TermRep.fDyn aC) (TermRep.fDyn aD))::HsDecl) ; _ -> error "Term explosion error." g (HsDefaultDecl _ _) xs = case TermRep.fArgs xs of [aE,aF] -> toDyn ((HsDefaultDecl (TermRep.fDyn aE) (TermRep.fDyn aF))::HsDecl) ; _ -> error "Term explosion error." g (HsTypeSig _ _ _) xs = case TermRep.fArgs xs of [aG,aH,aI] -> toDyn ((HsTypeSig (TermRep.fDyn aG) (TermRep.fDyn aH) (TermRep.fDyn aI))::HsDecl) ; _ -> error "Term explosion error." g (HsFunBind _) xs = case TermRep.fArgs xs of [aJ] -> toDyn ((HsFunBind (TermRep.fDyn aJ))::HsDecl) ; _ -> error "Term explosion error." g (HsPatBind _ _ _ _) xs = case TermRep.fArgs xs of [aK,aL,aM,aN] -> toDyn ((HsPatBind (TermRep.fDyn aK) (TermRep.fDyn aL) (TermRep.fDyn aM) (TermRep.fDyn aN))::HsDecl) ; _ -> error "Term explosion error." -- _tc_HsDeclTc = mkTyCon "HsDecl" -- instance Typeable HsDecl where -- typeOf x = mkTyConApp _tc_HsDeclTc [ ] instance Term HsMatch where explode (x::HsMatch) = TermRep (toDyn x, f x, g x) where f (HsMatch aa ab ac ad ae) = [explode aa,explode ab,explode ac,explode ad,explode ae] g (HsMatch _ _ _ _ _) xs = case TermRep.fArgs xs of [aa,ab,ac,ad,ae] -> toDyn ((HsMatch (TermRep.fDyn aa) (TermRep.fDyn ab) (TermRep.fDyn ac) (TermRep.fDyn ad) (TermRep.fDyn ae))::HsMatch) ; _ -> error "Term explosion error." -- _tc_HsMatchTc = mkTyCon "HsMatch" -- instance Typeable HsMatch where -- typeOf x = mkTyConApp _tc_HsMatchTc [ ] instance Term HsConDecl where explode (x::HsConDecl) = TermRep (toDyn x, f x, g x) where f (HsConDecl aa ab ac) = [explode aa,explode ab,explode ac] f (HsRecDecl ad ae af) = [explode ad,explode ae,explode af] g (HsConDecl _ _ _) xs = case TermRep.fArgs xs of [aa,ab,ac] -> toDyn ((HsConDecl (TermRep.fDyn aa) (TermRep.fDyn ab) (TermRep.fDyn ac))::HsConDecl) ; _ -> error "Term explosion error." g (HsRecDecl _ _ _) xs = case TermRep.fArgs xs of [ad,ae,af] -> toDyn ((HsRecDecl (TermRep.fDyn ad) (TermRep.fDyn ae) (TermRep.fDyn af))::HsConDecl) ; _ -> error "Term explosion error." -- _tc_HsConDeclTc = mkTyCon "HsConDecl" -- instance Typeable HsConDecl where -- typeOf x = mkTyConApp _tc_HsConDeclTc [ ] instance Term HsBangType where explode (x::HsBangType) = TermRep (toDyn x, f x, g x) where f (HsBangedTy aa) = [explode aa] f (HsUnBangedTy ab) = [explode ab] g (HsBangedTy _) xs = case TermRep.fArgs xs of [aa] -> toDyn ((HsBangedTy (TermRep.fDyn aa))::HsBangType) ; _ -> error "Term explosion error." g (HsUnBangedTy _) xs = case TermRep.fArgs xs of [ab] -> toDyn ((HsUnBangedTy (TermRep.fDyn ab))::HsBangType) ; _ -> error "Term explosion error." -- _tc_HsBangTypeTc = mkTyCon "HsBangType" -- instance Typeable HsBangType where -- typeOf x = mkTyConApp _tc_HsBangTypeTc [ ] instance Term HsRhs where explode (x::HsRhs) = TermRep (toDyn x, f x, g x) where f (HsUnGuardedRhs aa) = [explode aa] f (HsGuardedRhss ab) = [explode ab] g (HsUnGuardedRhs _) xs = case TermRep.fArgs xs of [aa] -> toDyn ((HsUnGuardedRhs (TermRep.fDyn aa))::HsRhs) ; _ -> error "Term explosion error." g (HsGuardedRhss _) xs = case TermRep.fArgs xs of [ab] -> toDyn ((HsGuardedRhss (TermRep.fDyn ab))::HsRhs) ; _ -> error "Term explosion error." -- _tc_HsRhsTc = mkTyCon "HsRhs" -- instance Typeable HsRhs where -- typeOf x = mkTyConApp _tc_HsRhsTc [ ] instance Term HsGuardedRhs where explode (x::HsGuardedRhs) = TermRep (toDyn x, f x, g x) where f (HsGuardedRhs aa ab ac) = [explode aa,explode ab,explode ac] g (HsGuardedRhs _ _ _) xs = case TermRep.fArgs xs of [aa,ab,ac] -> toDyn ((HsGuardedRhs (TermRep.fDyn aa) (TermRep.fDyn ab) (TermRep.fDyn ac))::HsGuardedRhs) ; _ -> error "Term explosion error." -- _tc_HsGuardedRhsTc = mkTyCon "HsGuardedRhs" -- instance Typeable HsGuardedRhs where -- typeOf x = mkTyConApp _tc_HsGuardedRhsTc [ ] instance Term HsQualType where explode (x::HsQualType) = TermRep (toDyn x, f x, g x) where f (HsQualType aa ab) = [explode aa,explode ab] g (HsQualType _ _) xs = case TermRep.fArgs xs of [aa,ab] -> toDyn ((HsQualType (TermRep.fDyn aa) (TermRep.fDyn ab))::HsQualType) ; _ -> error "Term explosion error." -- _tc_HsQualTypeTc = mkTyCon "HsQualType" -- instance Typeable HsQualType where -- typeOf x = mkTyConApp _tc_HsQualTypeTc [ ] instance Term HsType where explode (x::HsType) = TermRep (toDyn x, f x, g x) where f (HsTyFun aa ab) = [explode aa,explode ab] f (HsTyTuple ac) = [explode ac] f (HsTyApp ad ae) = [explode ad,explode ae] f (HsTyVar af) = [explode af] f (HsTyCon ag) = [explode ag] g (HsTyFun _ _) xs = case TermRep.fArgs xs of [aa,ab] -> toDyn ((HsTyFun (TermRep.fDyn aa) (TermRep.fDyn ab))::HsType) ; _ -> error "Term explosion error." g (HsTyTuple _) xs = case TermRep.fArgs xs of [ac] -> toDyn ((HsTyTuple (TermRep.fDyn ac))::HsType) ; _ -> error "Term explosion error." g (HsTyApp _ _) xs = case TermRep.fArgs xs of [ad,ae] -> toDyn ((HsTyApp (TermRep.fDyn ad) (TermRep.fDyn ae))::HsType) ; _ -> error "Term explosion error." g (HsTyVar _) xs = case TermRep.fArgs xs of [af] -> toDyn ((HsTyVar (TermRep.fDyn af))::HsType) ; _ -> error "Term explosion error." g (HsTyCon _) xs = case TermRep.fArgs xs of [ag] -> toDyn ((HsTyCon (TermRep.fDyn ag))::HsType) ; _ -> error "Term explosion error." -- _tc_HsTypeTc = mkTyCon "HsType" -- instance Typeable HsType where -- typeOf x = mkTyConApp _tc_HsTypeTc [ ] instance Term HsLiteral where explode (x::HsLiteral) = TermRep (toDyn x, f x, g x) where f (HsInt aa) = [explode aa] f (HsChar ab) = [explode ab] f (HsString ac) = [explode ac] f (HsFrac ad) = [explode ad] f (HsCharPrim ae) = [explode ae] f (HsStringPrim af) = [explode af] f (HsIntPrim ag) = [explode ag] f (HsFloatPrim ah) = [explode ah] f (HsDoublePrim ai) = [explode ai] g (HsInt _) xs = case TermRep.fArgs xs of [aa] -> toDyn ((HsInt (TermRep.fDyn aa))::HsLiteral) ; _ -> error "Term explosion error." g (HsChar _) xs = case TermRep.fArgs xs of [ab] -> toDyn ((HsChar (TermRep.fDyn ab))::HsLiteral) ; _ -> error "Term explosion error." g (HsString _) xs = case TermRep.fArgs xs of [ac] -> toDyn ((HsString (TermRep.fDyn ac))::HsLiteral) ; _ -> error "Term explosion error." g (HsFrac _) xs = case TermRep.fArgs xs of [ad] -> toDyn ((HsFrac (TermRep.fDyn ad))::HsLiteral) ; _ -> error "Term explosion error." g (HsCharPrim _) xs = case TermRep.fArgs xs of [ae] -> toDyn ((HsCharPrim (TermRep.fDyn ae))::HsLiteral) ; _ -> error "Term explosion error." g (HsStringPrim _) xs = case TermRep.fArgs xs of [af] -> toDyn ((HsStringPrim (TermRep.fDyn af))::HsLiteral) ; _ -> error "Term explosion error." g (HsIntPrim _) xs = case TermRep.fArgs xs of [ag] -> toDyn ((HsIntPrim (TermRep.fDyn ag))::HsLiteral) ; _ -> error "Term explosion error." g (HsFloatPrim _) xs = case TermRep.fArgs xs of [ah] -> toDyn ((HsFloatPrim (TermRep.fDyn ah))::HsLiteral) ; _ -> error "Term explosion error." g (HsDoublePrim _) xs = case TermRep.fArgs xs of [ai] -> toDyn ((HsDoublePrim (TermRep.fDyn ai))::HsLiteral) ; _ -> error "Term explosion error." -- _tc_HsLiteralTc = mkTyCon "HsLiteral" -- instance Typeable HsLiteral where -- typeOf x = mkTyConApp _tc_HsLiteralTc [ ] instance Term HsExp where explode (x::HsExp) = TermRep (toDyn x, f x, g x) where f (HsVar aa) = [explode aa] f (HsCon ab) = [explode ab] f (HsLit ac) = [explode ac] f (HsInfixApp ad ae af) = [explode ad,explode ae,explode af] f (HsApp ag ah) = [explode ag,explode ah] f (HsNegApp ai) = [explode ai] f (HsLambda aj ak al) = [explode aj,explode ak,explode al] f (HsLet am an) = [explode am,explode an] f (HsIf ao ap aq) = [explode ao,explode ap,explode aq] f (HsCase ar as) = [explode ar,explode as] f (HsDo at) = [explode at] f (HsTuple au) = [explode au] f (HsList av) = [explode av] f (HsParen aw) = [explode aw] f (HsLeftSection ax ay) = [explode ax,explode ay] f (HsRightSection az aA) = [explode az,explode aA] f (HsRecConstr aB aC) = [explode aB,explode aC] f (HsRecUpdate aD aE) = [explode aD,explode aE] f (HsEnumFrom aF) = [explode aF] f (HsEnumFromTo aG aH) = [explode aG,explode aH] f (HsEnumFromThen aI aJ) = [explode aI,explode aJ] f (HsEnumFromThenTo aK aL aM) = [explode aK,explode aL,explode aM] f (HsListComp aN aO) = [explode aN,explode aO] f (HsExpTypeSig aP aQ aR) = [explode aP,explode aQ,explode aR] f (HsAsPat aS aT) = [explode aS,explode aT] f HsWildCard = [] f (HsIrrPat aU) = [explode aU] g (HsVar _) xs = case TermRep.fArgs xs of [aa] -> toDyn ((HsVar (TermRep.fDyn aa))::HsExp) ; _ -> error "Term explosion error." g (HsCon _) xs = case TermRep.fArgs xs of [ab] -> toDyn ((HsCon (TermRep.fDyn ab))::HsExp) ; _ -> error "Term explosion error." g (HsLit _) xs = case TermRep.fArgs xs of [ac] -> toDyn ((HsLit (TermRep.fDyn ac))::HsExp) ; _ -> error "Term explosion error." g (HsInfixApp _ _ _) xs = case TermRep.fArgs xs of [ad,ae,af] -> toDyn ((HsInfixApp (TermRep.fDyn ad) (TermRep.fDyn ae) (TermRep.fDyn af))::HsExp) ; _ -> error "Term explosion error." g (HsApp _ _) xs = case TermRep.fArgs xs of [ag,ah] -> toDyn ((HsApp (TermRep.fDyn ag) (TermRep.fDyn ah))::HsExp) ; _ -> error "Term explosion error." g (HsNegApp _) xs = case TermRep.fArgs xs of [ai] -> toDyn ((HsNegApp (TermRep.fDyn ai))::HsExp) ; _ -> error "Term explosion error." g (HsLambda _ _ _) xs = case TermRep.fArgs xs of [aj,ak,al] -> toDyn ((HsLambda (TermRep.fDyn aj) (TermRep.fDyn ak) (TermRep.fDyn al))::HsExp) ; _ -> error "Term explosion error." g (HsLet _ _) xs = case TermRep.fArgs xs of [am,an] -> toDyn ((HsLet (TermRep.fDyn am) (TermRep.fDyn an))::HsExp) ; _ -> error "Term explosion error." g (HsIf _ _ _) xs = case TermRep.fArgs xs of [ao,ap,aq] -> toDyn ((HsIf (TermRep.fDyn ao) (TermRep.fDyn ap) (TermRep.fDyn aq))::HsExp) ; _ -> error "Term explosion error." g (HsCase _ _) xs = case TermRep.fArgs xs of [ar,as] -> toDyn ((HsCase (TermRep.fDyn ar) (TermRep.fDyn as))::HsExp) ; _ -> error "Term explosion error." g (HsDo _) xs = case TermRep.fArgs xs of [at] -> toDyn ((HsDo (TermRep.fDyn at))::HsExp) ; _ -> error "Term explosion error." g (HsTuple _) xs = case TermRep.fArgs xs of [au] -> toDyn ((HsTuple (TermRep.fDyn au))::HsExp) ; _ -> error "Term explosion error." g (HsList _) xs = case TermRep.fArgs xs of [av] -> toDyn ((HsList (TermRep.fDyn av))::HsExp) ; _ -> error "Term explosion error." g (HsParen _) xs = case TermRep.fArgs xs of [aw] -> toDyn ((HsParen (TermRep.fDyn aw))::HsExp) ; _ -> error "Term explosion error." g (HsLeftSection _ _) xs = case TermRep.fArgs xs of [ax,ay] -> toDyn ((HsLeftSection (TermRep.fDyn ax) (TermRep.fDyn ay))::HsExp) ; _ -> error "Term explosion error." g (HsRightSection _ _) xs = case TermRep.fArgs xs of [az,aA] -> toDyn ((HsRightSection (TermRep.fDyn az) (TermRep.fDyn aA))::HsExp) ; _ -> error "Term explosion error." g (HsRecConstr _ _) xs = case TermRep.fArgs xs of [aB,aC] -> toDyn ((HsRecConstr (TermRep.fDyn aB) (TermRep.fDyn aC))::HsExp) ; _ -> error "Term explosion error." g (HsRecUpdate _ _) xs = case TermRep.fArgs xs of [aD,aE] -> toDyn ((HsRecUpdate (TermRep.fDyn aD) (TermRep.fDyn aE))::HsExp) ; _ -> error "Term explosion error." g (HsEnumFrom _) xs = case TermRep.fArgs xs of [aF] -> toDyn ((HsEnumFrom (TermRep.fDyn aF))::HsExp) ; _ -> error "Term explosion error." g (HsEnumFromTo _ _) xs = case TermRep.fArgs xs of [aG,aH] -> toDyn ((HsEnumFromTo (TermRep.fDyn aG) (TermRep.fDyn aH))::HsExp) ; _ -> error "Term explosion error." g (HsEnumFromThen _ _) xs = case TermRep.fArgs xs of [aI,aJ] -> toDyn ((HsEnumFromThen (TermRep.fDyn aI) (TermRep.fDyn aJ))::HsExp) ; _ -> error "Term explosion error." g (HsEnumFromThenTo _ _ _) xs = case TermRep.fArgs xs of [aK,aL,aM] -> toDyn ((HsEnumFromThenTo (TermRep.fDyn aK) (TermRep.fDyn aL) (TermRep.fDyn aM))::HsExp) ; _ -> error "Term explosion error." g (HsListComp _ _) xs = case TermRep.fArgs xs of [aN,aO] -> toDyn ((HsListComp (TermRep.fDyn aN) (TermRep.fDyn aO))::HsExp) ; _ -> error "Term explosion error." g (HsExpTypeSig _ _ _) xs = case TermRep.fArgs xs of [aP,aQ,aR] -> toDyn ((HsExpTypeSig (TermRep.fDyn aP) (TermRep.fDyn aQ) (TermRep.fDyn aR))::HsExp) ; _ -> error "Term explosion error." g (HsAsPat _ _) xs = case TermRep.fArgs xs of [aS,aT] -> toDyn ((HsAsPat (TermRep.fDyn aS) (TermRep.fDyn aT))::HsExp) ; _ -> error "Term explosion error." g HsWildCard xs = case TermRep.fArgs xs of [] -> toDyn ((HsWildCard)::HsExp) ; _ -> error "Term explosion error." g (HsIrrPat _) xs = case TermRep.fArgs xs of [aU] -> toDyn ((HsIrrPat (TermRep.fDyn aU))::HsExp) ; _ -> error "Term explosion error." -- _tc_HsExpTc = mkTyCon "HsExp" -- instance Typeable HsExp where -- typeOf x = mkTyConApp _tc_HsExpTc [ ] instance Term HsPat where explode (x::HsPat) = TermRep (toDyn x, f x, g x) where f (HsPVar aa) = [explode aa] f (HsPLit ab) = [explode ab] f (HsPNeg ac) = [explode ac] f (HsPInfixApp ad ae af) = [explode ad,explode ae,explode af] f (HsPApp ag ah) = [explode ag,explode ah] f (HsPTuple ai) = [explode ai] f (HsPList aj) = [explode aj] f (HsPParen ak) = [explode ak] f (HsPRec al am) = [explode al,explode am] f (HsPAsPat an ao) = [explode an,explode ao] f HsPWildCard = [] f (HsPIrrPat ap) = [explode ap] g (HsPVar _) xs = case TermRep.fArgs xs of [aa] -> toDyn ((HsPVar (TermRep.fDyn aa))::HsPat) ; _ -> error "Term explosion error." g (HsPLit _) xs = case TermRep.fArgs xs of [ab] -> toDyn ((HsPLit (TermRep.fDyn ab))::HsPat) ; _ -> error "Term explosion error." g (HsPNeg _) xs = case TermRep.fArgs xs of [ac] -> toDyn ((HsPNeg (TermRep.fDyn ac))::HsPat) ; _ -> error "Term explosion error." g (HsPInfixApp _ _ _) xs = case TermRep.fArgs xs of [ad,ae,af] -> toDyn ((HsPInfixApp (TermRep.fDyn ad) (TermRep.fDyn ae) (TermRep.fDyn af))::HsPat) ; _ -> error "Term explosion error." g (HsPApp _ _) xs = case TermRep.fArgs xs of [ag,ah] -> toDyn ((HsPApp (TermRep.fDyn ag) (TermRep.fDyn ah))::HsPat) ; _ -> error "Term explosion error." g (HsPTuple _) xs = case TermRep.fArgs xs of [ai] -> toDyn ((HsPTuple (TermRep.fDyn ai))::HsPat) ; _ -> error "Term explosion error." g (HsPList _) xs = case TermRep.fArgs xs of [aj] -> toDyn ((HsPList (TermRep.fDyn aj))::HsPat) ; _ -> error "Term explosion error." g (HsPParen _) xs = case TermRep.fArgs xs of [ak] -> toDyn ((HsPParen (TermRep.fDyn ak))::HsPat) ; _ -> error "Term explosion error." g (HsPRec _ _) xs = case TermRep.fArgs xs of [al,am] -> toDyn ((HsPRec (TermRep.fDyn al) (TermRep.fDyn am))::HsPat) ; _ -> error "Term explosion error." g (HsPAsPat _ _) xs = case TermRep.fArgs xs of [an,ao] -> toDyn ((HsPAsPat (TermRep.fDyn an) (TermRep.fDyn ao))::HsPat) ; _ -> error "Term explosion error." g HsPWildCard xs = case TermRep.fArgs xs of [] -> toDyn ((HsPWildCard)::HsPat) ; _ -> error "Term explosion error." g (HsPIrrPat _) xs = case TermRep.fArgs xs of [ap] -> toDyn ((HsPIrrPat (TermRep.fDyn ap))::HsPat) ; _ -> error "Term explosion error." -- _tc_HsPatTc = mkTyCon "HsPat" -- instance Typeable HsPat where -- typeOf x = mkTyConApp _tc_HsPatTc [ ] instance Term HsPatField where explode (x::HsPatField) = TermRep (toDyn x, f x, g x) where f (HsPFieldPat aa ab) = [explode aa,explode ab] g (HsPFieldPat _ _) xs = case TermRep.fArgs xs of [aa,ab] -> toDyn ((HsPFieldPat (TermRep.fDyn aa) (TermRep.fDyn ab))::HsPatField) ; _ -> error "Term explosion error." -- _tc_HsPatFieldTc = mkTyCon "HsPatField" -- instance Typeable HsPatField where -- typeOf x = mkTyConApp _tc_HsPatFieldTc [ ] instance Term HsStmt where explode (x::HsStmt) = TermRep (toDyn x, f x, g x) where f (HsGenerator aa ab ac) = [explode aa,explode ab,explode ac] f (HsQualifier ad) = [explode ad] f (HsLetStmt ae) = [explode ae] g (HsGenerator _ _ _) xs = case TermRep.fArgs xs of [aa,ab,ac] -> toDyn ((HsGenerator (TermRep.fDyn aa) (TermRep.fDyn ab) (TermRep.fDyn ac))::HsStmt) ; _ -> error "Term explosion error." g (HsQualifier _) xs = case TermRep.fArgs xs of [ad] -> toDyn ((HsQualifier (TermRep.fDyn ad))::HsStmt) ; _ -> error "Term explosion error." g (HsLetStmt _) xs = case TermRep.fArgs xs of [ae] -> toDyn ((HsLetStmt (TermRep.fDyn ae))::HsStmt) ; _ -> error "Term explosion error." -- _tc_HsStmtTc = mkTyCon "HsStmt" -- instance Typeable HsStmt where -- typeOf x = mkTyConApp _tc_HsStmtTc [ ] instance Term HsFieldUpdate where explode (x::HsFieldUpdate) = TermRep (toDyn x, f x, g x) where f (HsFieldUpdate aa ab) = [explode aa,explode ab] g (HsFieldUpdate _ _) xs = case TermRep.fArgs xs of [aa,ab] -> toDyn ((HsFieldUpdate (TermRep.fDyn aa) (TermRep.fDyn ab))::HsFieldUpdate) ; _ -> error "Term explosion error." -- _tc_HsFieldUpdateTc = mkTyCon "HsFieldUpdate" -- instance Typeable HsFieldUpdate where -- typeOf x = mkTyConApp _tc_HsFieldUpdateTc [ ] instance Term HsAlt where explode (x::HsAlt) = TermRep (toDyn x, f x, g x) where f (HsAlt aa ab ac ad) = [explode aa,explode ab,explode ac,explode ad] g (HsAlt _ _ _ _) xs = case TermRep.fArgs xs of [aa,ab,ac,ad] -> toDyn ((HsAlt (TermRep.fDyn aa) (TermRep.fDyn ab) (TermRep.fDyn ac) (TermRep.fDyn ad))::HsAlt) ; _ -> error "Term explosion error." -- _tc_HsAltTc = mkTyCon "HsAlt" -- instance Typeable HsAlt where -- typeOf x = mkTyConApp _tc_HsAltTc [ ] instance Term HsGuardedAlts where explode (x::HsGuardedAlts) = TermRep (toDyn x, f x, g x) where f (HsUnGuardedAlt aa) = [explode aa] f (HsGuardedAlts ab) = [explode ab] g (HsUnGuardedAlt _) xs = case TermRep.fArgs xs of [aa] -> toDyn ((HsUnGuardedAlt (TermRep.fDyn aa))::HsGuardedAlts) ; _ -> error "Term explosion error." g (HsGuardedAlts _) xs = case TermRep.fArgs xs of [ab] -> toDyn ((HsGuardedAlts (TermRep.fDyn ab))::HsGuardedAlts) ; _ -> error "Term explosion error." -- _tc_HsGuardedAltsTc = mkTyCon "HsGuardedAlts" -- instance Typeable HsGuardedAlts where -- typeOf x = mkTyConApp _tc_HsGuardedAltsTc [ ] instance Term HsGuardedAlt where explode (x::HsGuardedAlt) = TermRep (toDyn x, f x, g x) where f (HsGuardedAlt aa ab ac) = [explode aa,explode ab,explode ac] g (HsGuardedAlt _ _ _) xs = case TermRep.fArgs xs of [aa,ab,ac] -> toDyn ((HsGuardedAlt (TermRep.fDyn aa) (TermRep.fDyn ab) (TermRep.fDyn ac))::HsGuardedAlt) ; _ -> error "Term explosion error." -- _tc_HsGuardedAltTc = mkTyCon "HsGuardedAlt" -- instance Typeable HsGuardedAlt where -- typeOf x = mkTyConApp _tc_HsGuardedAltTc [ ] -- Imported from other files :-