{-# LANGUAGE ConstraintKinds #-}{-# LANGUAGE DeriveDataTypeable #-}{-# LANGUAGE FlexibleContexts #-}{-# LANGUAGE FlexibleInstances #-}{-# LANGUAGE FunctionalDependencies #-}{-# LANGUAGE MultiParamTypeClasses #-}{-# LANGUAGE TypeFamilies #-}{-# LANGUAGE DataKinds #-}{-# LANGUAGE StandaloneDeriving #-}{-# LANGUAGE PatternSynonyms #-}{-# LANGUAGE UndecidableInstances #-}-- Note [Pass sensitive types]-- in module PlaceHoldermoduleHsExtensionwhere-- This module captures the type families to precisely identify the extension-- points for HsSynimportGhcPrelude importData.Datahiding(Fixity)importPlaceHolder importName importRdrName importVar importOutputable importSrcLoc (Located )importData.Kind{- Note [Trees that grow] ~~~~~~~~~~~~~~~~~~~~~~ See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow The hsSyn AST is reused across multiple compiler passes. We also have the Template Haskell AST, and the haskell-src-exts one (outside of GHC) Supporting multiple passes means the AST has various warts on it to cope with the specifics for the phases, such as the 'ValBindsOut', 'ConPatOut', 'SigPatOut' etc. The growable AST will allow each of these variants to be captured explicitly, such that they only exist in the given compiler pass AST, as selected by the type parameter to the AST. In addition it will allow tool writers to define their own extensions to capture additional information for the tool, in a natural way. A further goal is to provide a means to harmonise the Template Haskell and haskell-src-exts ASTs as well. -}-- | used as place holder in TTG valuesdataNoExt =NoExt deriving(Data,Eq,Ord)instanceOutputable NoExt whereppr _=text "NoExt"-- | Used when constructing a term with an unused extension point.noExt::NoExt noExt =NoExt -- | Used as a data type index for the hsSyn ASTdataGhcPass (c ::Pass )derivinginstanceEq(GhcPass c )derivinginstanceTypeablec =>Data(GhcPass c )dataPass =Parsed |Renamed |Typechecked deriving(Data)-- Type synonyms as a shorthand for taggingtypeGhcPs =GhcPass 'Parsed -- Old 'RdrName' type paramtypeGhcRn =GhcPass 'Renamed -- Old 'Name' type paramtypeGhcTc =GhcPass 'Typechecked -- Old 'Id' type para,typeGhcTcId =GhcTc -- Old 'TcId' type param-- | Maps the "normal" id type for a given passtypefamilyIdP p typeinstanceIdP GhcPs =RdrName typeinstanceIdP GhcRn =Name typeinstanceIdP GhcTc =Id typeLIdP p =Located (IdP p )-- | Marks that a field uses the GhcRn variant even when the pass-- parameter is GhcTc. Useful for storing HsTypes in HsExprs, say, because-- HsType GhcTc should never occur.typefamilyNoGhcTc (p ::Type)where-- this way, GHC can figure out that the result is a GhcPassNoGhcTc(GhcPass pass )=GhcPass (NoGhcTcPass pass )NoGhcTcother =other typefamilyNoGhcTcPass (p ::Pass )::Pass whereNoGhcTcPass'Typechecked ='Renamed NoGhcTcPassother =other -- =====================================================================-- Type families for the HsBinds extension points-- HsLocalBindsLR type familiestypefamilyXHsValBinds x x' typefamilyXHsIPBinds x x' typefamilyXEmptyLocalBinds x x' typefamilyXXHsLocalBindsLR x x' typeForallXHsLocalBindsLR (c ::*->Constraint)(x ::*)(x' ::*)=(c (XHsValBinds x x' ),c (XHsIPBinds x x' ),c (XEmptyLocalBinds x x' ),c (XXHsLocalBindsLR x x' ))-- ValBindsLR type familiestypefamilyXValBinds x x' typefamilyXXValBindsLR x x' typeForallXValBindsLR (c ::*->Constraint)(x ::*)(x' ::*)=(c (XValBinds x x' ),c (XXValBindsLR x x' ))-- HsBindsLR type familiestypefamilyXFunBind x x' typefamilyXPatBind x x' typefamilyXVarBind x x' typefamilyXAbsBinds x x' typefamilyXPatSynBind x x' typefamilyXXHsBindsLR x x' typeForallXHsBindsLR (c ::*->Constraint)(x ::*)(x' ::*)=(c (XFunBind x x' ),c (XPatBind x x' ),c (XVarBind x x' ),c (XAbsBinds x x' ),c (XPatSynBind x x' ),c (XXHsBindsLR x x' ))-- ABExport type familiestypefamilyXABE x typefamilyXXABExport x typeForallXABExport (c ::*->Constraint)(x ::*)=(c (XABE x ),c (XXABExport x ))-- PatSynBind type familiestypefamilyXPSB x x' typefamilyXXPatSynBind x x' typeForallXPatSynBind (c ::*->Constraint)(x ::*)(x' ::*)=(c (XPSB x x' ),c (XXPatSynBind x x' ))-- HsIPBinds type familiestypefamilyXIPBinds x typefamilyXXHsIPBinds x typeForallXHsIPBinds (c ::*->Constraint)(x ::*)=(c (XIPBinds x ),c (XXHsIPBinds x ))-- IPBind type familiestypefamilyXCIPBind x typefamilyXXIPBind x typeForallXIPBind (c ::*->Constraint)(x ::*)=(c (XCIPBind x ),c (XXIPBind x ))-- Sig type familiestypefamilyXTypeSig x typefamilyXPatSynSig x typefamilyXClassOpSig x typefamilyXIdSig x typefamilyXFixSig x typefamilyXInlineSig x typefamilyXSpecSig x typefamilyXSpecInstSig x typefamilyXMinimalSig x typefamilyXSCCFunSig x typefamilyXCompleteMatchSig x typefamilyXXSig x typeForallXSig (c ::*->Constraint)(x ::*)=(c (XTypeSig x ),c (XPatSynSig x ),c (XClassOpSig x ),c (XIdSig x ),c (XFixSig x ),c (XInlineSig x ),c (XSpecSig x ),c (XSpecInstSig x ),c (XMinimalSig x ),c (XSCCFunSig x ),c (XCompleteMatchSig x ),c (XXSig x ))-- FixitySig type familiestypefamilyXFixitySig x typefamilyXXFixitySig x typeForallXFixitySig (c ::*->Constraint)(x ::*)=(c (XFixitySig x ),c (XXFixitySig x ))-- =====================================================================-- Type families for the HsDecls extension points-- HsDecl type familiestypefamilyXTyClD x typefamilyXInstD x typefamilyXDerivD x typefamilyXValD x typefamilyXSigD x typefamilyXDefD x typefamilyXForD x typefamilyXWarningD x typefamilyXAnnD x typefamilyXRuleD x typefamilyXSpliceD x typefamilyXDocD x typefamilyXRoleAnnotD x typefamilyXXHsDecl x typeForallXHsDecl (c ::*->Constraint)(x ::*)=(c (XTyClD x ),c (XInstD x ),c (XDerivD x ),c (XValD x ),c (XSigD x ),c (XDefD x ),c (XForD x ),c (XWarningD x ),c (XAnnD x ),c (XRuleD x ),c (XSpliceD x ),c (XDocD x ),c (XRoleAnnotD x ),c (XXHsDecl x ))-- --------------------------------------- HsGroup type familiestypefamilyXCHsGroup x typefamilyXXHsGroup x typeForallXHsGroup (c ::*->Constraint)(x ::*)=(c (XCHsGroup x ),c (XXHsGroup x ))-- --------------------------------------- SpliceDecl type familiestypefamilyXSpliceDecl x typefamilyXXSpliceDecl x typeForallXSpliceDecl (c ::*->Constraint)(x ::*)=(c (XSpliceDecl x ),c (XXSpliceDecl x ))-- --------------------------------------- TyClDecl type familiestypefamilyXFamDecl x typefamilyXSynDecl x typefamilyXDataDecl x typefamilyXClassDecl x typefamilyXXTyClDecl x typeForallXTyClDecl (c ::*->Constraint)(x ::*)=(c (XFamDecl x ),c (XSynDecl x ),c (XDataDecl x ),c (XClassDecl x ),c (XXTyClDecl x ))-- --------------------------------------- TyClGroup type familiestypefamilyXCTyClGroup x typefamilyXXTyClGroup x typeForallXTyClGroup (c ::*->Constraint)(x ::*)=(c (XCTyClGroup x ),c (XXTyClGroup x ))-- --------------------------------------- FamilyResultSig type familiestypefamilyXNoSig x typefamilyXCKindSig x -- Clashes with XKindSig abovetypefamilyXTyVarSig x typefamilyXXFamilyResultSig x typeForallXFamilyResultSig (c ::*->Constraint)(x ::*)=(c (XNoSig x ),c (XCKindSig x ),c (XTyVarSig x ),c (XXFamilyResultSig x ))-- --------------------------------------- FamilyDecl type familiestypefamilyXCFamilyDecl x typefamilyXXFamilyDecl x typeForallXFamilyDecl (c ::*->Constraint)(x ::*)=(c (XCFamilyDecl x ),c (XXFamilyDecl x ))-- --------------------------------------- HsDataDefn type familiestypefamilyXCHsDataDefn x typefamilyXXHsDataDefn x typeForallXHsDataDefn (c ::*->Constraint)(x ::*)=(c (XCHsDataDefn x ),c (XXHsDataDefn x ))-- --------------------------------------- HsDerivingClause type familiestypefamilyXCHsDerivingClause x typefamilyXXHsDerivingClause x typeForallXHsDerivingClause (c ::*->Constraint)(x ::*)=(c (XCHsDerivingClause x ),c (XXHsDerivingClause x ))-- --------------------------------------- ConDecl type familiestypefamilyXConDeclGADT x typefamilyXConDeclH98 x typefamilyXXConDecl x typeForallXConDecl (c ::*->Constraint)(x ::*)=(c (XConDeclGADT x ),c (XConDeclH98 x ),c (XXConDecl x ))-- --------------------------------------- FamEqn type familiestypefamilyXCFamEqn x p r typefamilyXXFamEqn x p r typeForallXFamEqn (c ::*->Constraint)(x ::*)(p ::*)(r ::*)=(c (XCFamEqn x p r ),c (XXFamEqn x p r ))-- --------------------------------------- ClsInstDecl type familiestypefamilyXCClsInstDecl x typefamilyXXClsInstDecl x typeForallXClsInstDecl (c ::*->Constraint)(x ::*)=(c (XCClsInstDecl x ),c (XXClsInstDecl x ))-- --------------------------------------- ClsInstDecl type familiestypefamilyXClsInstD x typefamilyXDataFamInstD x typefamilyXTyFamInstD x typefamilyXXInstDecl x typeForallXInstDecl (c ::*->Constraint)(x ::*)=(c (XClsInstD x ),c (XDataFamInstD x ),c (XTyFamInstD x ),c (XXInstDecl x ))-- --------------------------------------- DerivDecl type familiestypefamilyXCDerivDecl x typefamilyXXDerivDecl x typeForallXDerivDecl (c ::*->Constraint)(x ::*)=(c (XCDerivDecl x ),c (XXDerivDecl x ))-- --------------------------------------- DerivStrategy type familytypefamilyXViaStrategy x -- --------------------------------------- DefaultDecl type familiestypefamilyXCDefaultDecl x typefamilyXXDefaultDecl x typeForallXDefaultDecl (c ::*->Constraint)(x ::*)=(c (XCDefaultDecl x ),c (XXDefaultDecl x ))-- --------------------------------------- DefaultDecl type familiestypefamilyXForeignImport x typefamilyXForeignExport x typefamilyXXForeignDecl x typeForallXForeignDecl (c ::*->Constraint)(x ::*)=(c (XForeignImport x ),c (XForeignExport x ),c (XXForeignDecl x ))-- --------------------------------------- RuleDecls type familiestypefamilyXCRuleDecls x typefamilyXXRuleDecls x typeForallXRuleDecls (c ::*->Constraint)(x ::*)=(c (XCRuleDecls x ),c (XXRuleDecls x ))-- --------------------------------------- RuleDecl type familiestypefamilyXHsRule x typefamilyXXRuleDecl x typeForallXRuleDecl (c ::*->Constraint)(x ::*)=(c (XHsRule x ),c (XXRuleDecl x ))-- --------------------------------------- RuleBndr type familiestypefamilyXCRuleBndr x typefamilyXRuleBndrSig x typefamilyXXRuleBndr x typeForallXRuleBndr (c ::*->Constraint)(x ::*)=(c (XCRuleBndr x ),c (XRuleBndrSig x ),c (XXRuleBndr x ))-- --------------------------------------- WarnDecls type familiestypefamilyXWarnings x typefamilyXXWarnDecls x typeForallXWarnDecls (c ::*->Constraint)(x ::*)=(c (XWarnings x ),c (XXWarnDecls x ))-- --------------------------------------- AnnDecl type familiestypefamilyXWarning x typefamilyXXWarnDecl x typeForallXWarnDecl (c ::*->Constraint)(x ::*)=(c (XWarning x ),c (XXWarnDecl x ))-- --------------------------------------- AnnDecl type familiestypefamilyXHsAnnotation x typefamilyXXAnnDecl x typeForallXAnnDecl (c ::*->Constraint)(x ::*)=(c (XHsAnnotation x ),c (XXAnnDecl x ))-- --------------------------------------- RoleAnnotDecl type familiestypefamilyXCRoleAnnotDecl x typefamilyXXRoleAnnotDecl x typeForallXRoleAnnotDecl (c ::*->Constraint)(x ::*)=(c (XCRoleAnnotDecl x ),c (XXRoleAnnotDecl x ))-- =====================================================================-- Type families for the HsExpr extension pointstypefamilyXVar x typefamilyXUnboundVar x typefamilyXConLikeOut x typefamilyXRecFld x typefamilyXOverLabel x typefamilyXIPVar x typefamilyXOverLitE x typefamilyXLitE x typefamilyXLam x typefamilyXLamCase x typefamilyXApp x typefamilyXAppTypeE x typefamilyXOpApp x typefamilyXNegApp x typefamilyXPar x typefamilyXSectionL x typefamilyXSectionR x typefamilyXExplicitTuple x typefamilyXExplicitSum x typefamilyXCase x typefamilyXIf x typefamilyXMultiIf x typefamilyXLet x typefamilyXDo x typefamilyXExplicitList x typefamilyXRecordCon x typefamilyXRecordUpd x typefamilyXExprWithTySig x typefamilyXArithSeq x typefamilyXSCC x typefamilyXCoreAnn x typefamilyXBracket x typefamilyXRnBracketOut x typefamilyXTcBracketOut x typefamilyXSpliceE x typefamilyXProc x typefamilyXStatic x typefamilyXArrApp x typefamilyXArrForm x typefamilyXTick x typefamilyXBinTick x typefamilyXTickPragma x typefamilyXEWildPat x typefamilyXEAsPat x typefamilyXEViewPat x typefamilyXELazyPat x typefamilyXWrap x typefamilyXXExpr x typeForallXExpr (c ::*->Constraint)(x ::*)=(c (XVar x ),c (XUnboundVar x ),c (XConLikeOut x ),c (XRecFld x ),c (XOverLabel x ),c (XIPVar x ),c (XOverLitE x ),c (XLitE x ),c (XLam x ),c (XLamCase x ),c (XApp x ),c (XAppTypeE x ),c (XOpApp x ),c (XNegApp x ),c (XPar x ),c (XSectionL x ),c (XSectionR x ),c (XExplicitTuple x ),c (XExplicitSum x ),c (XCase x ),c (XIf x ),c (XMultiIf x ),c (XLet x ),c (XDo x ),c (XExplicitList x ),c (XRecordCon x ),c (XRecordUpd x ),c (XExprWithTySig x ),c (XArithSeq x ),c (XSCC x ),c (XCoreAnn x ),c (XBracket x ),c (XRnBracketOut x ),c (XTcBracketOut x ),c (XSpliceE x ),c (XProc x ),c (XStatic x ),c (XArrApp x ),c (XArrForm x ),c (XTick x ),c (XBinTick x ),c (XTickPragma x ),c (XEWildPat x ),c (XEAsPat x ),c (XEViewPat x ),c (XELazyPat x ),c (XWrap x ),c (XXExpr x ))-- ---------------------------------------------------------------------typefamilyXUnambiguous x typefamilyXAmbiguous x typefamilyXXAmbiguousFieldOcc x typeForallXAmbiguousFieldOcc (c ::*->Constraint)(x ::*)=(c (XUnambiguous x ),c (XAmbiguous x ),c (XXAmbiguousFieldOcc x ))-- ----------------------------------------------------------------------typefamilyXPresent x typefamilyXMissing x typefamilyXXTupArg x typeForallXTupArg (c ::*->Constraint)(x ::*)=(c (XPresent x ),c (XMissing x ),c (XXTupArg x ))-- ---------------------------------------------------------------------typefamilyXTypedSplice x typefamilyXUntypedSplice x typefamilyXQuasiQuote x typefamilyXSpliced x typefamilyXXSplice x typeForallXSplice (c ::*->Constraint)(x ::*)=(c (XTypedSplice x ),c (XUntypedSplice x ),c (XQuasiQuote x ),c (XSpliced x ),c (XXSplice x ))-- ---------------------------------------------------------------------typefamilyXExpBr x typefamilyXPatBr x typefamilyXDecBrL x typefamilyXDecBrG x typefamilyXTypBr x typefamilyXVarBr x typefamilyXTExpBr x typefamilyXXBracket x typeForallXBracket (c ::*->Constraint)(x ::*)=(c (XExpBr x ),c (XPatBr x ),c (XDecBrL x ),c (XDecBrG x ),c (XTypBr x ),c (XVarBr x ),c (XTExpBr x ),c (XXBracket x ))-- ---------------------------------------------------------------------typefamilyXCmdTop x typefamilyXXCmdTop x typeForallXCmdTop (c ::*->Constraint)(x ::*)=(c (XCmdTop x ),c (XXCmdTop x ))-- -------------------------------------typefamilyXMG x b typefamilyXXMatchGroup x b typeForallXMatchGroup (c ::*->Constraint)(x ::*)(b ::*)=(c (XMG x b ),c (XXMatchGroup x b ))-- -------------------------------------typefamilyXCMatch x b typefamilyXXMatch x b typeForallXMatch (c ::*->Constraint)(x ::*)(b ::*)=(c (XCMatch x b ),c (XXMatch x b ))-- -------------------------------------typefamilyXCGRHSs x b typefamilyXXGRHSs x b typeForallXGRHSs (c ::*->Constraint)(x ::*)(b ::*)=(c (XCGRHSs x b ),c (XXGRHSs x b ))-- -------------------------------------typefamilyXCGRHS x b typefamilyXXGRHS x b typeForallXGRHS (c ::*->Constraint)(x ::*)(b ::*)=(c (XCGRHS x b ),c (XXGRHS x b ))-- -------------------------------------typefamilyXLastStmt x x' b typefamilyXBindStmt x x' b typefamilyXApplicativeStmt x x' b typefamilyXBodyStmt x x' b typefamilyXLetStmt x x' b typefamilyXParStmt x x' b typefamilyXTransStmt x x' b typefamilyXRecStmt x x' b typefamilyXXStmtLR x x' b typeForallXStmtLR (c ::*->Constraint)(x ::*)(x' ::*)(b ::*)=(c (XLastStmt x x' b ),c (XBindStmt x x' b ),c (XApplicativeStmt x x' b ),c (XBodyStmt x x' b ),c (XLetStmt x x' b ),c (XParStmt x x' b ),c (XTransStmt x x' b ),c (XRecStmt x x' b ),c (XXStmtLR x x' b ))-- ---------------------------------------------------------------------typefamilyXCmdArrApp x typefamilyXCmdArrForm x typefamilyXCmdApp x typefamilyXCmdLam x typefamilyXCmdPar x typefamilyXCmdCase x typefamilyXCmdIf x typefamilyXCmdLet x typefamilyXCmdDo x typefamilyXCmdWrap x typefamilyXXCmd x typeForallXCmd (c ::*->Constraint)(x ::*)=(c (XCmdArrApp x ),c (XCmdArrForm x ),c (XCmdApp x ),c (XCmdLam x ),c (XCmdPar x ),c (XCmdCase x ),c (XCmdIf x ),c (XCmdLet x ),c (XCmdDo x ),c (XCmdWrap x ),c (XXCmd x ))-- ---------------------------------------------------------------------typefamilyXParStmtBlock x x' typefamilyXXParStmtBlock x x' typeForallXParStmtBlock (c ::*->Constraint)(x ::*)(x' ::*)=(c (XParStmtBlock x x' ),c (XXParStmtBlock x x' ))-- ---------------------------------------------------------------------typefamilyXApplicativeArgOne x typefamilyXApplicativeArgMany x typefamilyXXApplicativeArg x typeForallXApplicativeArg (c ::*->Constraint)(x ::*)=(c (XApplicativeArgOne x ),c (XApplicativeArgMany x ),c (XXApplicativeArg x ))-- =====================================================================-- Type families for the HsImpExp extension points-- TODO-- =====================================================================-- Type families for the HsLit extension points-- We define a type family for each extension point. This is based on prepending-- 'X' to the constructor name, for ease of reference.typefamilyXHsChar x typefamilyXHsCharPrim x typefamilyXHsString x typefamilyXHsStringPrim x typefamilyXHsInt x typefamilyXHsIntPrim x typefamilyXHsWordPrim x typefamilyXHsInt64Prim x typefamilyXHsWord64Prim x typefamilyXHsInteger x typefamilyXHsRat x typefamilyXHsFloatPrim x typefamilyXHsDoublePrim x typefamilyXXLit x -- | Helper to apply a constraint to all extension points. It has one-- entry per extension point type family.typeForallXHsLit (c ::*->Constraint)(x ::*)=(c (XHsChar x ),c (XHsCharPrim x ),c (XHsDoublePrim x ),c (XHsFloatPrim x ),c (XHsInt x ),c (XHsInt64Prim x ),c (XHsIntPrim x ),c (XHsInteger x ),c (XHsRat x ),c (XHsString x ),c (XHsStringPrim x ),c (XHsWord64Prim x ),c (XHsWordPrim x ),c (XXLit x ))typefamilyXOverLit x typefamilyXXOverLit x typeForallXOverLit (c ::*->Constraint)(x ::*)=(c (XOverLit x ),c (XXOverLit x ))-- =====================================================================-- Type families for the HsPat extension pointstypefamilyXWildPat x typefamilyXVarPat x typefamilyXLazyPat x typefamilyXAsPat x typefamilyXParPat x typefamilyXBangPat x typefamilyXListPat x typefamilyXTuplePat x typefamilyXSumPat x typefamilyXConPat x typefamilyXViewPat x typefamilyXSplicePat x typefamilyXLitPat x typefamilyXNPat x typefamilyXNPlusKPat x typefamilyXSigPat x typefamilyXCoPat x typefamilyXXPat x typeForallXPat (c ::*->Constraint)(x ::*)=(c (XWildPat x ),c (XVarPat x ),c (XLazyPat x ),c (XAsPat x ),c (XParPat x ),c (XBangPat x ),c (XListPat x ),c (XTuplePat x ),c (XSumPat x ),c (XViewPat x ),c (XSplicePat x ),c (XLitPat x ),c (XNPat x ),c (XNPlusKPat x ),c (XSigPat x ),c (XCoPat x ),c (XXPat x ))-- =====================================================================-- Type families for the HsTypes type familiestypefamilyXHsQTvs x typefamilyXXLHsQTyVars x typeForallXLHsQTyVars (c ::*->Constraint)(x ::*)=(c (XHsQTvs x ),c (XXLHsQTyVars x ))-- -------------------------------------typefamilyXHsIB x b typefamilyXXHsImplicitBndrs x b typeForallXHsImplicitBndrs (c ::*->Constraint)(x ::*)(b ::*)=(c (XHsIB x b ),c (XXHsImplicitBndrs x b ))-- -------------------------------------typefamilyXHsWC x b typefamilyXXHsWildCardBndrs x b typeForallXHsWildCardBndrs (c ::*->Constraint)(x ::*)(b ::*)=(c (XHsWC x b ),c (XXHsWildCardBndrs x b ))-- -------------------------------------typefamilyXForAllTy x typefamilyXQualTy x typefamilyXTyVar x typefamilyXAppTy x typefamilyXAppKindTy x typefamilyXFunTy x typefamilyXListTy x typefamilyXTupleTy x typefamilyXSumTy x typefamilyXOpTy x typefamilyXParTy x typefamilyXIParamTy x typefamilyXStarTy x typefamilyXKindSig x typefamilyXSpliceTy x typefamilyXDocTy x typefamilyXBangTy x typefamilyXRecTy x typefamilyXExplicitListTy x typefamilyXExplicitTupleTy x typefamilyXTyLit x typefamilyXWildCardTy x typefamilyXXType x -- | Helper to apply a constraint to all extension points. It has one-- entry per extension point type family.typeForallXType (c ::*->Constraint)(x ::*)=(c (XForAllTy x ),c (XQualTy x ),c (XTyVar x ),c (XAppTy x ),c (XAppKindTy x ),c (XFunTy x ),c (XListTy x ),c (XTupleTy x ),c (XSumTy x ),c (XOpTy x ),c (XParTy x ),c (XIParamTy x ),c (XStarTy x ),c (XKindSig x ),c (XSpliceTy x ),c (XDocTy x ),c (XBangTy x ),c (XRecTy x ),c (XExplicitListTy x ),c (XExplicitTupleTy x ),c (XTyLit x ),c (XWildCardTy x ),c (XXType x ))-- ---------------------------------------------------------------------typefamilyXUserTyVar x typefamilyXKindedTyVar x typefamilyXXTyVarBndr x typeForallXTyVarBndr (c ::*->Constraint)(x ::*)=(c (XUserTyVar x ),c (XKindedTyVar x ),c (XXTyVarBndr x ))-- ---------------------------------------------------------------------typefamilyXConDeclField x typefamilyXXConDeclField x typeForallXConDeclField (c ::*->Constraint)(x ::*)=(c (XConDeclField x ),c (XXConDeclField x ))-- ---------------------------------------------------------------------typefamilyXCFieldOcc x typefamilyXXFieldOcc x typeForallXFieldOcc (c ::*->Constraint)(x ::*)=(c (XCFieldOcc x ),c (XXFieldOcc x ))-- =====================================================================-- Type families for the HsImpExp type familiestypefamilyXCImportDecl x typefamilyXXImportDecl x typeForallXImportDecl (c ::*->Constraint)(x ::*)=(c (XCImportDecl x ),c (XXImportDecl x ))-- -------------------------------------typefamilyXIEVar x typefamilyXIEThingAbs x typefamilyXIEThingAll x typefamilyXIEThingWith x typefamilyXIEModuleContents x typefamilyXIEGroup x typefamilyXIEDoc x typefamilyXIEDocNamed x typefamilyXXIE x typeForallXIE (c ::*->Constraint)(x ::*)=(c (XIEVar x ),c (XIEThingAbs x ),c (XIEThingAll x ),c (XIEThingWith x ),c (XIEModuleContents x ),c (XIEGroup x ),c (XIEDoc x ),c (XIEDocNamed x ),c (XXIE x ))-- --------------------------------------- =====================================================================-- End of Type family definitions-- =====================================================================-- ------------------------------------------------------------------------ | Conversion of annotations from one type index to another. This is required-- where the AST is converted from one pass to another, and the extension values-- need to be brought along if possible. So for example a 'SourceText' is-- converted via 'id', but needs a type signature to keep the type checker-- happy.classConvertable a b |a->bwhereconvert ::a ->b instanceConvertable a a whereconvert =id-- | A constraint capturing all the extension points that can be converted via-- @instance Convertable a a@typeConvertIdX a b =(XHsDoublePrima ~XHsDoublePrim b ,XHsFloatPrima ~XHsFloatPrim b ,XHsRata ~XHsRat b ,XHsIntegera ~XHsInteger b ,XHsWord64Prima ~XHsWord64Prim b ,XHsInt64Prima ~XHsInt64Prim b ,XHsWordPrima ~XHsWordPrim b ,XHsIntPrima ~XHsIntPrim b ,XHsInta ~XHsInt b ,XHsStringPrima ~XHsStringPrim b ,XHsStringa ~XHsString b ,XHsCharPrima ~XHsCharPrim b ,XHsChara ~XHsChar b ,XXLita ~XXLit b )-- ------------------------------------------------------------------------ Note [OutputableX]-- ~~~~~~~~~~~~~~~~~~---- is required because the type family resolution-- process cannot determine that all cases are handled for a `GhcPass p`-- case where the cases are listed separately.---- So---- type instance XXHsIPBinds (GhcPass p) = NoExt---- will correctly deduce Outputable for (GhcPass p), but---- type instance XIPBinds GhcPs = NoExt-- type instance XIPBinds GhcRn = NoExt-- type instance XIPBinds GhcTc = TcEvBinds---- will not.-- | Provide a summary constraint that gives all am Outputable constraint to-- extension points needing onetypeOutputableX p =-- See Note [OutputableX](Outputable (XIPBinds p ),Outputable (XViaStrategy p ),Outputable (XViaStrategy GhcRn ))-- TODO: Should OutputableX be included in OutputableBndrId?-- ------------------------------------------------------------------------ |Constraint type to bundle up the requirement for 'OutputableBndr' on both-- the @id@ and the 'NameOrRdrName' type for ittypeOutputableBndrId id =(OutputableBndr (NameOrRdrName (IdP id )),OutputableBndr (IdP id ),OutputableBndr (NameOrRdrName (IdP (NoGhcTc id ))),OutputableBndr (IdP (NoGhcTc id )),NoGhcTcid ~NoGhcTc (NoGhcTc id ),OutputableX id ,OutputableX (NoGhcTc id ))