ghc-9.4.4: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.Haskell.Syntax.Extension

Synopsis

Documentation

data NoExtField Source #

A placeholder type for TTG extension points that are not currently unused to represent any particular value.

This should not be confused with DataConCantHappen, which are found in unused extension constructors and therefore should never be inhabited. In contrast, NoExtField is used in extension points (e.g., as the field of some constructor), so it must have an inhabitant to construct AST passes that manipulate fields with that extension point as their type.

Constructors

NoExtField 

Instances

Instances details
Data NoExtField Source # 
Instance details

Defined in Language.Haskell.Syntax.Extension

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NoExtField -> c NoExtField Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NoExtField Source #

toConstr :: NoExtField -> Constr Source #

dataTypeOf :: NoExtField -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NoExtField) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NoExtField) Source #

gmapT :: (forall b. Data b => b -> b) -> NoExtField -> NoExtField Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NoExtField -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NoExtField -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> NoExtField -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NoExtField -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NoExtField -> m NoExtField Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NoExtField -> m NoExtField Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NoExtField -> m NoExtField Source #

Outputable NoExtField Source # 
Instance details

Defined in Language.Haskell.Syntax.Extension

Methods

ppr :: NoExtField -> SDoc Source #

Eq NoExtField Source # 
Instance details

Defined in Language.Haskell.Syntax.Extension

Ord NoExtField Source # 
Instance details

Defined in Language.Haskell.Syntax.Extension

noExtField :: NoExtField Source #

Used when constructing a term with an unused extension point.

data DataConCantHappen Source #

Instances

Instances details
Data DataConCantHappen Source # 
Instance details

Defined in Language.Haskell.Syntax.Extension

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataConCantHappen -> c DataConCantHappen Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataConCantHappen Source #

toConstr :: DataConCantHappen -> Constr Source #

dataTypeOf :: DataConCantHappen -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DataConCantHappen) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataConCantHappen) Source #

gmapT :: (forall b. Data b => b -> b) -> DataConCantHappen -> DataConCantHappen Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataConCantHappen -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataConCantHappen -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> DataConCantHappen -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DataConCantHappen -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataConCantHappen -> m DataConCantHappen Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataConCantHappen -> m DataConCantHappen Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataConCantHappen -> m DataConCantHappen Source #

Outputable DataConCantHappen Source # 
Instance details

Defined in Language.Haskell.Syntax.Extension

Eq DataConCantHappen Source # 
Instance details

Defined in Language.Haskell.Syntax.Extension

Ord DataConCantHappen Source # 
Instance details

Defined in Language.Haskell.Syntax.Extension

dataConCantHappen :: DataConCantHappen -> a Source #

Eliminate a DataConCantHappen. See Note [Constructor cannot occur].

type family XRec p a = r | r -> a Source #

GHC's L prefixed variants wrap their vanilla variant in this type family, to add SrcLoc info via Located. Other passes than GhcPass not interested in location information can define this as type instance XRec NoLocated a = a. See Note [XRec and SrcSpans in the AST]

Instances

Instances details
type XRec (GhcPass p) a Source # 
Instance details

Defined in GHC.Hs.Extension

type XRec (GhcPass p) a = GenLocated (Anno a) a

type family Anno a = b Source #

Instances

Instances details
type Anno ConLike Source # 
Instance details

Defined in GHC.Hs.Pat

type Anno OverlapMode Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno OverlapMode Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno FieldLabelString Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno CType Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno Name Source # 
Instance details

Defined in GHC.Hs.Extension

type Anno RdrName Source # 
Instance details

Defined in GHC.Hs.Extension

type Anno StringLiteral Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno Id Source # 
Instance details

Defined in GHC.Hs.Extension

type Anno ModuleName Source # 
Instance details

Defined in GHC.Hs.ImpExp

type Anno HsIPName Source # 
Instance details

Defined in GHC.Hs.Type

type Anno Bool Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (IE (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type Anno (IE (GhcPass p)) = SrcSpanAnnA
type Anno (ImportDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type Anno (LocatedA (IE (GhcPass p))) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type Anno (LocatedN Name) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN RdrName) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN Id) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (FixitySig (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (IPBind (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (Sig (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (AnnDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (ClsInstDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (ConDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (DataFamInstDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (DefaultDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (DerivClauseTys (GhcPass _1)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (DerivDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (DerivStrategy (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (DocDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (FamilyDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (FamilyResultSig (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (ForeignDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (FunDep (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (HsDecl (GhcPass _1)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (HsDerivingClause (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (InjectivityAnn (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (InstDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (RoleAnnotDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (RuleBndr (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (RuleDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (RuleDecls (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (SpliceDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (StandaloneKindSig (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (TyClDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (TyFamInstDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (WarnDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (WarnDecls (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (DotFieldOcc (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (FieldLabelStrings (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (HsCmd (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (HsCmdTop (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (HsExpr (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (HsSplice (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (HsToken tok) Source # 
Instance details

Defined in GHC.Hs.Extension

type Anno (HsOverLit (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Pat

type Anno (Pat (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Pat

type Anno (AmbiguousFieldOcc (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

type Anno (BangType (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

type Anno (ConDeclField (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

type Anno (FieldOcc (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

type Anno (HsKind (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

type Anno (HsSigType (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

type Anno (HsType (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

type Anno (Maybe Role) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (Maybe Role) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno [LocatedA (IE (GhcPass p))] Source # 
Instance details

Defined in GHC.Hs.ImpExp

type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsCmd (GhcPass p))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (Match GhcPs (LocatedA (PatBuilder GhcPs)))] Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] = SrcSpanAnnL
type Anno [LocatedA (StmtLR GhcPs GhcPs (LocatedA (PatBuilder GhcPs)))] Source # 
Instance details

Defined in GHC.Parser.Types

type Anno [LocatedA (ConDeclField (GhcPass _1))] Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno [LocatedA (HsType (GhcPass p))] Source # 
Instance details

Defined in GHC.Hs.Type

type Anno [LocatedN Name] Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN RdrName] Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN Id] Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (HsBindLR (GhcPass idL) (GhcPass idR)) Source # 
Instance details

Defined in GHC.Hs.Binds

type Anno (HsBindLR (GhcPass idL) (GhcPass idR)) = SrcSpanAnnA
type Anno (FamEqn (GhcPass p) _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (FamEqn (GhcPass p) _1) = SrcSpanAnnA
type Anno (FamEqn (GhcPass p) _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (FamEqn (GhcPass p) _1) = SrcSpanAnnA
type Anno (FamEqn p (LocatedA (HsType p))) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (GRHS (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (GRHS (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (GRHS GhcPs (LocatedA (PatBuilder GhcPs))) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (Match (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (Match GhcPs (LocatedA (PatBuilder GhcPs))) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (HsUniToken tok utok) Source # 
Instance details

Defined in GHC.Hs.Extension

type Anno (HsUniToken tok utok) = TokenLocation
type Anno (HsFieldBind lhs rhs) Source # 
Instance details

Defined in GHC.Hs.Pat

type Anno (HsFieldBind lhs rhs) = SrcSpanAnnA
type Anno (HsOuterTyVarBndrs _1 (GhcPass _2)) Source # 
Instance details

Defined in GHC.Hs.Type

type Anno (HsTyVarBndr _flag (GhcPass _1)) Source # 
Instance details

Defined in GHC.Hs.Type

type Anno (HsTyVarBndr _flag (GhcPass _1)) = SrcSpanAnnA
type Anno (HsTyVarBndr _flag GhcPs) Source # 
Instance details

Defined in GHC.Hs.Type

type Anno (HsTyVarBndr _flag GhcRn) Source # 
Instance details

Defined in GHC.Hs.Type

type Anno (HsTyVarBndr _flag GhcTc) Source # 
Instance details

Defined in GHC.Hs.Type

type Anno (SourceText, RuleName) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (SourceText, RuleName) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr)))) Source # 
Instance details

Defined in GHC.Hs.Expr

type Anno (StmtLR GhcPs GhcPs (LocatedA (PatBuilder GhcPs))) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (StmtLR GhcRn GhcRn (LocatedA (body GhcRn))) Source # 
Instance details

Defined in GHC.Hs.Expr

class UnXRec p where Source #

We can strip off the XRec to access the underlying data. See Note [XRec and SrcSpans in the AST]

Methods

unXRec :: XRec p a -> a Source #

Instances

Instances details
UnXRec (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Extension

Methods

unXRec :: XRec (GhcPass p) a -> a Source #

class MapXRec p where Source #

We can map over the underlying type contained in an XRec while preserving the annotation as is.

Methods

mapXRec :: Anno a ~ Anno b => (a -> b) -> XRec p a -> XRec p b Source #

Instances

Instances details
MapXRec (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Extension

Methods

mapXRec :: Anno a ~ Anno b => (a -> b) -> XRec (GhcPass p) a -> XRec (GhcPass p) b Source #

class WrapXRec p a where Source #

The trivial wrapper that carries no additional information See Note [XRec and SrcSpans in the AST]

Methods

wrapXRec :: a -> XRec p a Source #

Instances

Instances details
Anno a ~ SrcSpanAnn' (EpAnn an) => WrapXRec (GhcPass p) a Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

wrapXRec :: a -> XRec (GhcPass p) a Source #

type family IdP p Source #

Maps the "normal" id type for a given pass

Instances

Instances details
type IdP (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Extension

type IdP (GhcPass p) = IdGhcP p

type LIdP p = XRec p (IdP p) Source #

type family XHsValBinds x x' Source #

Instances

Instances details
type XHsValBinds (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XHsIPBinds x x' Source #

Instances

Instances details
type XHsIPBinds (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XEmptyLocalBinds x x' Source #

Instances

Instances details
type XEmptyLocalBinds (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXHsLocalBindsLR x x' Source #

Instances

Instances details
type XXHsLocalBindsLR (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XValBinds x x' Source #

Instances

Instances details
type XValBinds (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXValBindsLR x x' Source #

Instances

Instances details
type XXValBindsLR (GhcPass pL) pR Source # 
Instance details

Defined in GHC.Hs.Binds

type family XFunBind x x' Source #

Instances

Instances details
type XFunBind (GhcPass pL) GhcPs Source # 
Instance details

Defined in GHC.Hs.Binds

type XFunBind (GhcPass pL) GhcRn Source #

After the renamer (but before the type-checker), the FunBind extension field contains the locally-bound free variables of this defn. See Note [Bind free vars]

Instance details

Defined in GHC.Hs.Binds

type XFunBind (GhcPass pL) GhcTc Source #

After the type-checker, the FunBind extension field contains a coercion from the type of the MatchGroup to the type of the Id. Example:

     f :: Int -> forall a. a -> a
     f x y = y

Then the MatchGroup will have type (Int -> a' -> a') (with a free type variable a'). The coercion will take a CoreExpr of this type and convert it to a CoreExpr of type Int -> forall a'. a' -> a' Notice that the coercion captures the free a'.

Instance details

Defined in GHC.Hs.Binds

type family XPatBind x x' Source #

Instances

Instances details
type XPatBind GhcPs (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type XPatBind GhcRn (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type XPatBind GhcTc (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XVarBind x x' Source #

Instances

Instances details
type XVarBind (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XPatSynBind x x' Source #

Instances

Instances details
type XPatSynBind (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXHsBindsLR x x' Source #

Instances

Instances details
type XXHsBindsLR GhcPs pR Source # 
Instance details

Defined in GHC.Hs.Binds

type XXHsBindsLR GhcRn pR Source # 
Instance details

Defined in GHC.Hs.Binds

type XXHsBindsLR GhcTc pR Source # 
Instance details

Defined in GHC.Hs.Binds

type family XPSB x x' Source #

Instances

Instances details
type XPSB (GhcPass idL) GhcPs Source # 
Instance details

Defined in GHC.Hs.Binds

type XPSB (GhcPass idL) GhcRn Source # 
Instance details

Defined in GHC.Hs.Binds

type XPSB (GhcPass idL) GhcRn = NameSet
type XPSB (GhcPass idL) GhcTc Source # 
Instance details

Defined in GHC.Hs.Binds

type XPSB (GhcPass idL) GhcTc = NameSet

type family XXPatSynBind x x' Source #

Instances

Instances details
type XXPatSynBind (GhcPass idL) (GhcPass idR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XIPBinds x Source #

Instances

Instances details
type XIPBinds GhcPs Source # 
Instance details

Defined in GHC.Hs.Binds

type XIPBinds GhcRn Source # 
Instance details

Defined in GHC.Hs.Binds

type XIPBinds GhcTc Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXHsIPBinds x Source #

Instances

Instances details
type XXHsIPBinds (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XCIPBind x Source #

Instances

Instances details
type XCIPBind GhcPs Source # 
Instance details

Defined in GHC.Hs.Binds

type XCIPBind GhcRn Source # 
Instance details

Defined in GHC.Hs.Binds

type XCIPBind GhcTc Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXIPBind x Source #

Instances

Instances details
type XXIPBind (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XTypeSig x Source #

Instances

Instances details
type XTypeSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XPatSynSig x Source #

Instances

Instances details
type XPatSynSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XClassOpSig x Source #

Instances

Instances details
type XClassOpSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XIdSig x Source #

Instances

Instances details
type XIdSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XFixSig x Source #

Instances

Instances details
type XFixSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XInlineSig x Source #

Instances

Instances details
type XInlineSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XSpecSig x Source #

Instances

Instances details
type XSpecSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XSpecInstSig x Source #

Instances

Instances details
type XSpecInstSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XMinimalSig x Source #

Instances

Instances details
type XMinimalSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XSCCFunSig x Source #

Instances

Instances details
type XSCCFunSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XCompleteMatchSig x Source #

Instances

Instances details
type XCompleteMatchSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXSig x Source #

Instances

Instances details
type XXSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XFixitySig x Source #

Instances

Instances details
type XFixitySig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXFixitySig x Source #

Instances

Instances details
type XXFixitySig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XStandaloneKindSig x Source #

Instances

Instances details
type XStandaloneKindSig GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XStandaloneKindSig GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XStandaloneKindSig GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXStandaloneKindSig x Source #

Instances

Instances details
type XXStandaloneKindSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XTyClD x Source #

Instances

Instances details
type XTyClD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XInstD x Source #

Instances

Instances details
type XInstD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XDerivD x Source #

Instances

Instances details
type XDerivD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XValD x Source #

Instances

Instances details
type XValD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XSigD x Source #

Instances

Instances details
type XSigD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XKindSigD x Source #

Instances

Instances details
type XKindSigD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XDefD x Source #

Instances

Instances details
type XDefD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XForD x Source #

Instances

Instances details
type XForD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XWarningD x Source #

Instances

Instances details
type XWarningD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XAnnD x Source #

Instances

Instances details
type XAnnD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XRuleD x Source #

Instances

Instances details
type XRuleD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XSpliceD x Source #

Instances

Instances details
type XSpliceD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XDocD x Source #

Instances

Instances details
type XDocD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XRoleAnnotD x Source #

Instances

Instances details
type XRoleAnnotD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXHsDecl x Source #

Instances

Instances details
type XXHsDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCHsGroup x Source #

Instances

Instances details
type XCHsGroup (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXHsGroup x Source #

Instances

Instances details
type XXHsGroup (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XSpliceDecl x Source #

Instances

Instances details
type XSpliceDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXSpliceDecl x Source #

Instances

Instances details
type XXSpliceDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XFamDecl x Source #

Instances

Instances details
type XFamDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XSynDecl x Source #

Instances

Instances details
type XSynDecl GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XSynDecl GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XSynDecl GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XDataDecl x Source #

Instances

Instances details
type XDataDecl GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XDataDecl GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XDataDecl GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XClassDecl x Source #

Instances

Instances details
type XClassDecl GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XClassDecl GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XClassDecl GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXTyClDecl x Source #

Instances

Instances details
type XXTyClDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCFunDep x Source #

Instances

Instances details
type XCFunDep (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXFunDep x Source #

Instances

Instances details
type XXFunDep (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCTyClGroup x Source #

Instances

Instances details
type XCTyClGroup (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXTyClGroup x Source #

Instances

Instances details
type XXTyClGroup (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XNoSig x Source #

Instances

Instances details
type XNoSig (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCKindSig x Source #

Instances

Instances details
type XCKindSig (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XTyVarSig x Source #

Instances

Instances details
type XTyVarSig (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXFamilyResultSig x Source #

Instances

Instances details
type XXFamilyResultSig (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCFamilyDecl x Source #

Instances

Instances details
type XCFamilyDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXFamilyDecl x Source #

Instances

Instances details
type XXFamilyDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCHsDataDefn x Source #

Instances

Instances details
type XCHsDataDefn (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXHsDataDefn x Source #

Instances

Instances details
type XXHsDataDefn (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCHsDerivingClause x Source #

Instances

Instances details
type XCHsDerivingClause (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXHsDerivingClause x Source #

Instances

Instances details
type XXHsDerivingClause (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XDctSingle x Source #

Instances

Instances details
type XDctSingle (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XDctMulti x Source #

Instances

Instances details
type XDctMulti (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXDerivClauseTys x Source #

Instances

Instances details
type XXDerivClauseTys (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XConDeclGADT x Source #

Instances

Instances details
type XConDeclGADT (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XConDeclH98 x Source #

Instances

Instances details
type XConDeclH98 (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXConDecl x Source #

Instances

Instances details
type XXConDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCFamEqn x r Source #

Instances

Instances details
type XCFamEqn (GhcPass _1) r Source # 
Instance details

Defined in GHC.Hs.Decls

type XCFamEqn (GhcPass _1) r = EpAnn [AddEpAnn]

type family XXFamEqn x r Source #

Instances

Instances details
type XXFamEqn (GhcPass _1) r Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCTyFamInstDecl x Source #

Instances

Instances details
type XCTyFamInstDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXTyFamInstDecl x Source #

Instances

Instances details
type XXTyFamInstDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCClsInstDecl x Source #

Instances

Instances details
type XCClsInstDecl GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XCClsInstDecl GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XCClsInstDecl GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXClsInstDecl x Source #

Instances

Instances details
type XXClsInstDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XClsInstD x Source #

Instances

Instances details
type XClsInstD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XDataFamInstD x Source #

Instances

Instances details
type XDataFamInstD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XTyFamInstD x Source #

Instances

Instances details
type XTyFamInstD GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XTyFamInstD GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XTyFamInstD GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXInstDecl x Source #

Instances

Instances details
type XXInstDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCDerivDecl x Source #

Instances

Instances details
type XCDerivDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXDerivDecl x Source #

Instances

Instances details
type XXDerivDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XStockStrategy x Source #

Instances

Instances details
type XStockStrategy GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XStockStrategy GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XStockStrategy GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XAnyClassStrategy x Source #

Instances

Instances details
type XAnyClassStrategy GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XAnyClassStrategy GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XAnyClassStrategy GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XNewtypeStrategy x Source #

Instances

Instances details
type XNewtypeStrategy GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XNewtypeStrategy GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XNewtypeStrategy GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XViaStrategy x Source #

Instances

Instances details
type XViaStrategy GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XViaStrategy GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XViaStrategy GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCDefaultDecl x Source #

Instances

Instances details
type XCDefaultDecl GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XCDefaultDecl GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XCDefaultDecl GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXDefaultDecl x Source #

Instances

Instances details
type XXDefaultDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XForeignImport x Source #

Instances

Instances details
type XForeignImport GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignImport GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignImport GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XForeignExport x Source #

Instances

Instances details
type XForeignExport GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignExport GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignExport GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXForeignDecl x Source #

Instances

Instances details
type XXForeignDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCRuleDecls x Source #

Instances

Instances details
type XCRuleDecls GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XCRuleDecls GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XCRuleDecls GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXRuleDecls x Source #

Instances

Instances details
type XXRuleDecls (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XHsRule x Source #

Instances

Instances details
type XHsRule GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XHsRule GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XHsRule GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXRuleDecl x Source #

Instances

Instances details
type XXRuleDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCRuleBndr x Source #

Instances

Instances details
type XCRuleBndr (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XRuleBndrSig x Source #

Instances

Instances details
type XRuleBndrSig (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXRuleBndr x Source #

Instances

Instances details
type XXRuleBndr (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XWarnings x Source #

Instances

Instances details
type XWarnings GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XWarnings GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XWarnings GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXWarnDecls x Source #

Instances

Instances details
type XXWarnDecls (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XWarning x Source #

Instances

Instances details
type XWarning (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXWarnDecl x Source #

Instances

Instances details
type XXWarnDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XHsAnnotation x Source #

Instances

Instances details
type XHsAnnotation (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXAnnDecl x Source #

Instances

Instances details
type XXAnnDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCRoleAnnotDecl x Source #

Instances

Instances details
type XCRoleAnnotDecl GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XCRoleAnnotDecl GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XCRoleAnnotDecl GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXRoleAnnotDecl x Source #

Instances

Instances details
type XXRoleAnnotDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCInjectivityAnn x Source #

Instances

Instances details
type XCInjectivityAnn (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXInjectivityAnn x Source #

Instances

Instances details
type XXInjectivityAnn (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XVar x Source #

Instances

Instances details
type XVar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XVar (GhcPass _1) = NoExtField
type XVar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XVar (GhcPass _1) = NoExtField

type family XUnboundVar x Source #

Instances

Instances details
type XUnboundVar GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XUnboundVar GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XUnboundVar GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XRecSel x Source #

Instances

Instances details
type XRecSel GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecSel GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecSel GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XOverLabel x Source #

Instances

Instances details
type XOverLabel GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XOverLabel GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XOverLabel GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XIPVar x Source #

Instances

Instances details
type XIPVar GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XIPVar GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XIPVar GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XOverLitE x Source #

Instances

Instances details
type XOverLitE (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XLitE x Source #

Instances

Instances details
type XLitE (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XLitE (GhcPass _1) = EpAnnCO

type family XLam x Source #

Instances

Instances details
type XLam (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XLam (GhcPass _1) = NoExtField
type XLam (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XLam (GhcPass _1) = NoExtField

type family XLamCase x Source #

Instances

Instances details
type XLamCase (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XApp x Source #

Instances

Instances details
type XApp (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XApp (GhcPass _1) = EpAnnCO

type family XAppTypeE x Source #

Instances

Instances details
type XAppTypeE GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XAppTypeE GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XAppTypeE GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XOpApp x Source #

Instances

Instances details
type XOpApp GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XOpApp GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XOpApp GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XNegApp x Source #

Instances

Instances details
type XNegApp GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XNegApp GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XNegApp GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XPar x Source #

Instances

Instances details
type XPar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XPar (GhcPass _1) = EpAnnCO

type family XSectionL x Source #

Instances

Instances details
type XSectionL GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XSectionL GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XSectionL GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XSectionR x Source #

Instances

Instances details
type XSectionR GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XSectionR GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XSectionR GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XExplicitTuple x Source #

Instances

Instances details
type XExplicitTuple GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitTuple GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitTuple GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XExplicitSum x Source #

Instances

Instances details
type XExplicitSum GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitSum GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitSum GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCase x Source #

Instances

Instances details
type XCase GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XCase GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XCase GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XIf x Source #

Instances

Instances details
type XIf GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XIf GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XIf GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XMultiIf x Source #

Instances

Instances details
type XMultiIf GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XMultiIf GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XMultiIf GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XLet x Source #

Instances

Instances details
type XLet GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XLet GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XLet GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XDo x Source #

Instances

Instances details
type XDo GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XDo GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XDo GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XDo GhcTc = Type

type family XExplicitList x Source #

Instances

Instances details
type XExplicitList GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitList GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitList GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XRecordCon x Source #

Instances

Instances details
type XRecordCon GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordCon GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordCon GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XRecordUpd x Source #

Instances

Instances details
type XRecordUpd GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordUpd GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordUpd GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XGetField x Source #

Instances

Instances details
type XGetField GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XGetField GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XGetField GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XProjection x Source #

Instances

Instances details
type XProjection GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XProjection GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XProjection GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XExprWithTySig x Source #

Instances

Instances details
type XExprWithTySig GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XExprWithTySig GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XExprWithTySig GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XArithSeq x Source #

Instances

Instances details
type XArithSeq GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XArithSeq GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XArithSeq GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XTypedBracket x Source #

Instances

Instances details
type XTypedBracket GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XTypedBracket GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XTypedBracket GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XUntypedBracket x Source #

Instances

Instances details
type XUntypedBracket GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XUntypedBracket GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XUntypedBracket GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XSpliceE x Source #

Instances

Instances details
type XSpliceE (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XProc x Source #

Instances

Instances details
type XProc (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XProc (GhcPass _1) = EpAnn [AddEpAnn]

type family XStatic x Source #

Instances

Instances details
type XStatic GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XStatic GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XStatic GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XTick x Source #

type family XBinTick x Source #

type family XPragE x Source #

Instances

Instances details
type XPragE (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXExpr x Source #

Instances

Instances details
type XXExpr GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XXExpr GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XXExpr GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCDotFieldOcc x Source #

Instances

Instances details
type XCDotFieldOcc (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXDotFieldOcc x Source #

Instances

Instances details
type XXDotFieldOcc (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XSCC x Source #

Instances

Instances details
type XSCC (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXPragE x Source #

Instances

Instances details
type XXPragE (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XUnambiguous x Source #

Instances

Instances details
type XUnambiguous GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XUnambiguous GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XUnambiguous GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type family XAmbiguous x Source #

Instances

Instances details
type XAmbiguous GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XAmbiguous GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XAmbiguous GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type family XXAmbiguousFieldOcc x Source #

Instances

Instances details
type XXAmbiguousFieldOcc (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XPresent x Source #

Instances

Instances details
type XPresent (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XMissing x Source #

Instances

Instances details
type XMissing GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XMissing GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XMissing GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXTupArg x Source #

Instances

Instances details
type XXTupArg (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XTypedSplice x Source #

Instances

Instances details
type XTypedSplice (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XUntypedSplice x Source #

Instances

Instances details
type XUntypedSplice (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XQuasiQuote x Source #

Instances

Instances details
type XQuasiQuote (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XSpliced x Source #

Instances

Instances details
type XSpliced (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXSplice x Source #

Instances

Instances details
type XXSplice GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XXSplice GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XXSplice GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XExpBr x Source #

Instances

Instances details
type XExpBr GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XExpBr GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XExpBr GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XPatBr x Source #

Instances

Instances details
type XPatBr GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XPatBr GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XPatBr GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XDecBrL x Source #

Instances

Instances details
type XDecBrL GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XDecBrL GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XDecBrL GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XDecBrG x Source #

Instances

Instances details
type XDecBrG GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XDecBrG GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XDecBrG GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XTypBr x Source #

Instances

Instances details
type XTypBr GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XTypBr GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XTypBr GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XVarBr x Source #

Instances

Instances details
type XVarBr GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XVarBr GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XVarBr GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXQuote x Source #

Instances

Instances details
type XXQuote GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XXQuote GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XXQuote GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdTop x Source #

Instances

Instances details
type XCmdTop GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdTop GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdTop GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXCmdTop x Source #

Instances

Instances details
type XXCmdTop (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XMG x b Source #

Instances

Instances details
type XMG GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XMG GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XMG GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXMatchGroup x b Source #

Instances

Instances details
type XXMatchGroup (GhcPass _1) b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCMatch x b Source #

Instances

Instances details
type XCMatch (GhcPass _1) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XCMatch (GhcPass _1) b = EpAnn [AddEpAnn]

type family XXMatch x b Source #

Instances

Instances details
type XXMatch (GhcPass _1) b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCGRHSs x b Source #

Instances

Instances details
type XCGRHSs (GhcPass _1) _2 Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXGRHSs x b Source #

Instances

Instances details
type XXGRHSs (GhcPass _1) _2 Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCGRHS x b Source #

Instances

Instances details
type XCGRHS (GhcPass _1) _2 Source # 
Instance details

Defined in GHC.Hs.Expr

type XCGRHS (GhcPass _1) _2 = EpAnn GrhsAnn

type family XXGRHS x b Source #

Instances

Instances details
type XXGRHS (GhcPass _1) b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XLastStmt x x' b Source #

Instances

Instances details
type XLastStmt (GhcPass _1) (GhcPass _2) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XLastStmt (GhcPass _1) (GhcPass _2) b = NoExtField

type family XBindStmt x x' b Source #

Instances

Instances details
type XBindStmt (GhcPass _1) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBindStmt (GhcPass _1) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBindStmt (GhcPass _1) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XApplicativeStmt x x' b Source #

Instances

Instances details
type XApplicativeStmt (GhcPass _1) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeStmt (GhcPass _1) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeStmt (GhcPass _1) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XBodyStmt x x' b Source #

Instances

Instances details
type XBodyStmt (GhcPass _1) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBodyStmt (GhcPass _1) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBodyStmt (GhcPass _1) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBodyStmt (GhcPass _1) GhcTc b = Type

type family XLetStmt x x' b Source #

Instances

Instances details
type XLetStmt (GhcPass _1) (GhcPass _2) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XLetStmt (GhcPass _1) (GhcPass _2) b = EpAnn [AddEpAnn]

type family XParStmt x x' b Source #

Instances

Instances details
type XParStmt (GhcPass _1) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XParStmt (GhcPass _1) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XParStmt (GhcPass _1) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XParStmt (GhcPass _1) GhcTc b = Type

type family XTransStmt x x' b Source #

Instances

Instances details
type XTransStmt (GhcPass _1) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XTransStmt (GhcPass _1) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XTransStmt (GhcPass _1) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XRecStmt x x' b Source #

Instances

Instances details
type XRecStmt (GhcPass _1) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecStmt (GhcPass _1) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecStmt (GhcPass _1) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXStmtLR x x' b Source #

Instances

Instances details
type XXStmtLR (GhcPass _1) (GhcPass _2) b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdArrApp x Source #

Instances

Instances details
type XCmdArrApp GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdArrApp GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdArrApp GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdArrForm x Source #

Instances

Instances details
type XCmdArrForm GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdArrForm GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdArrForm GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdApp x Source #

Instances

Instances details
type XCmdApp (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdApp (GhcPass _1) = EpAnnCO

type family XCmdLam x Source #

Instances

Instances details
type XCmdLam (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdPar x Source #

Instances

Instances details
type XCmdPar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdPar (GhcPass _1) = EpAnnCO

type family XCmdCase x Source #

Instances

Instances details
type XCmdCase GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdCase GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdCase GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdLamCase x Source #

Instances

Instances details
type XCmdLamCase (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdIf x Source #

Instances

Instances details
type XCmdIf GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdIf GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdIf GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdLet x Source #

Instances

Instances details
type XCmdLet GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdLet GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdLet GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdDo x Source #

Instances

Instances details
type XCmdDo GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdDo GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdDo GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdWrap x Source #

Instances

Instances details
type XCmdWrap (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXCmd x Source #

Instances

Instances details
type XXCmd GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XXCmd GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XXCmd GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XParStmtBlock x x' Source #

Instances

Instances details
type XParStmtBlock (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXParStmtBlock x x' Source #

Instances

Instances details
type XXParStmtBlock (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XApplicativeArgOne x Source #

Instances

Instances details
type XApplicativeArgOne GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeArgOne GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeArgOne GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XApplicativeArgMany x Source #

Instances

Instances details
type XApplicativeArgMany (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXApplicativeArg x Source #

Instances

Instances details
type XXApplicativeArg (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XHsChar x Source #

Instances

Instances details
type XHsChar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsCharPrim x Source #

Instances

Instances details
type XHsCharPrim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsString x Source #

Instances

Instances details
type XHsString (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsStringPrim x Source #

Instances

Instances details
type XHsStringPrim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsInt x Source #

Instances

Instances details
type XHsInt (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsIntPrim x Source #

Instances

Instances details
type XHsIntPrim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsWordPrim x Source #

Instances

Instances details
type XHsWordPrim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsInt64Prim x Source #

Instances

Instances details
type XHsInt64Prim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsWord64Prim x Source #

Instances

Instances details
type XHsWord64Prim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsInteger x Source #

Instances

Instances details
type XHsInteger (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsRat x Source #

Instances

Instances details
type XHsRat (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsFloatPrim x Source #

Instances

Instances details
type XHsFloatPrim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsDoublePrim x Source #

Instances

Instances details
type XHsDoublePrim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XXLit x Source #

Instances

Instances details
type XXLit (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XOverLit x Source #

Instances

Instances details
type XOverLit GhcPs Source # 
Instance details

Defined in GHC.Hs.Lit

type XOverLit GhcRn Source # 
Instance details

Defined in GHC.Hs.Lit

type XOverLit GhcTc Source # 
Instance details

Defined in GHC.Hs.Lit

type family XXOverLit x Source #

Instances

Instances details
type XXOverLit (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XWildPat x Source #

Instances

Instances details
type XWildPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XWildPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XWildPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XVarPat x Source #

Instances

Instances details
type XVarPat (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Pat

type family XLazyPat x Source #

Instances

Instances details
type XLazyPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XLazyPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XLazyPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XAsPat x Source #

Instances

Instances details
type XAsPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XAsPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XAsPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XParPat x Source #

Instances

Instances details
type XParPat (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Pat

type XParPat (GhcPass _1) = EpAnnCO

type family XBangPat x Source #

Instances

Instances details
type XBangPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XBangPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XBangPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XListPat x Source #

Instances

Instances details
type XListPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XListPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XListPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XTuplePat x Source #

Instances

Instances details
type XTuplePat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XTuplePat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XTuplePat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XSumPat x Source #

Instances

Instances details
type XSumPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XSumPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XSumPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XSumPat GhcTc = [Type]

type family XConPat x Source #

Instances

Instances details
type XConPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XConPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XConPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XViewPat x Source #

Instances

Instances details
type XViewPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XViewPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XViewPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XSplicePat x Source #

Instances

Instances details
type XSplicePat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XSplicePat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XSplicePat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XLitPat x Source #

Instances

Instances details
type XLitPat (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Pat

type family XNPat x Source #

Instances

Instances details
type XNPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XNPlusKPat x Source #

Instances

Instances details
type XNPlusKPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPlusKPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPlusKPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XSigPat x Source #

Instances

Instances details
type XSigPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XSigPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XSigPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XCoPat x Source #

type family XXPat x Source #

Instances

Instances details
type XXPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XXPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XXPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XHsFieldBind x Source #

Instances

Instances details
type XHsFieldBind _1 Source # 
Instance details

Defined in GHC.Hs.Pat

type family XHsQTvs x Source #

Instances

Instances details
type XHsQTvs GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XHsQTvs GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XHsQTvs GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type family XXLHsQTyVars x Source #

Instances

Instances details
type XXLHsQTyVars (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XHsOuterImplicit x Source #

Instances

Instances details
type XHsOuterImplicit GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XHsOuterImplicit GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XHsOuterImplicit GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type family XHsOuterExplicit x flag Source #

Instances

Instances details
type XHsOuterExplicit GhcPs _1 Source # 
Instance details

Defined in GHC.Hs.Type

type XHsOuterExplicit GhcRn _1 Source # 
Instance details

Defined in GHC.Hs.Type

type XHsOuterExplicit GhcTc flag Source # 
Instance details

Defined in GHC.Hs.Type

type XHsOuterExplicit GhcTc flag = [VarBndr TyVar flag]

type family XXHsOuterTyVarBndrs x Source #

Instances

Instances details
type XXHsOuterTyVarBndrs (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XHsSig x Source #

Instances

Instances details
type XHsSig (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XXHsSigType x Source #

Instances

Instances details
type XXHsSigType (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XHsWC x b Source #

Instances

Instances details
type XHsWC GhcPs b Source # 
Instance details

Defined in GHC.Hs.Type

type XHsWC GhcRn b Source # 
Instance details

Defined in GHC.Hs.Type

type XHsWC GhcRn b = [Name]
type XHsWC GhcTc b Source # 
Instance details

Defined in GHC.Hs.Type

type XHsWC GhcTc b = [Name]

type family XXHsWildCardBndrs x b Source #

Instances

Instances details
type XXHsWildCardBndrs (GhcPass _1) _2 Source # 
Instance details

Defined in GHC.Hs.Type

type family XHsPS x Source #

Instances

Instances details
type XHsPS GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XHsPS GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XHsPS GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type family XXHsPatSigType x Source #

Instances

Instances details
type XXHsPatSigType (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XForAllTy x Source #

Instances

Instances details
type XForAllTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XQualTy x Source #

Instances

Instances details
type XQualTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XTyVar x Source #

Instances

Instances details
type XTyVar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XAppTy x Source #

Instances

Instances details
type XAppTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XAppKindTy x Source #

Instances

Instances details
type XAppKindTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XFunTy x Source #

Instances

Instances details
type XFunTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XFunTy (GhcPass _1) = EpAnnCO

type family XListTy x Source #

Instances

Instances details
type XListTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XTupleTy x Source #

Instances

Instances details
type XTupleTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XSumTy x Source #

Instances

Instances details
type XSumTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XOpTy x Source #

Instances

Instances details
type XOpTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XOpTy (GhcPass _1) = EpAnn [AddEpAnn]

type family XParTy x Source #

Instances

Instances details
type XParTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XIParamTy x Source #

Instances

Instances details
type XIParamTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XStarTy x Source #

Instances

Instances details
type XStarTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XKindSig x Source #

Instances

Instances details
type XKindSig (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XSpliceTy x Source #

Instances

Instances details
type XSpliceTy GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XSpliceTy GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XSpliceTy GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type family XDocTy x Source #

Instances

Instances details
type XDocTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XBangTy x Source #

Instances

Instances details
type XBangTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XRecTy x Source #

Instances

Instances details
type XRecTy GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XRecTy GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XRecTy GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type family XExplicitListTy x Source #

Instances

Instances details
type XExplicitListTy GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XExplicitListTy GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XExplicitListTy GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type family XExplicitTupleTy x Source #

Instances

Instances details
type XExplicitTupleTy GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XExplicitTupleTy GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XExplicitTupleTy GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type family XTyLit x Source #

Instances

Instances details
type XTyLit (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XWildCardTy x Source #

Instances

Instances details
type XWildCardTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XXType x Source #

Instances

Instances details
type XXType (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XXType (GhcPass _1) = HsCoreTy

type family XHsForAllVis x Source #

Instances

Instances details
type XHsForAllVis (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XHsForAllInvis x Source #

Instances

Instances details
type XHsForAllInvis (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XXHsForAllTelescope x Source #

Instances

Instances details
type XXHsForAllTelescope (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XUserTyVar x Source #

Instances

Instances details
type XUserTyVar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XKindedTyVar x Source #

Instances

Instances details
type XKindedTyVar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XXTyVarBndr x Source #

Instances

Instances details
type XXTyVarBndr (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XConDeclField x Source #

Instances

Instances details
type XConDeclField (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XXConDeclField x Source #

Instances

Instances details
type XXConDeclField (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XCFieldOcc x Source #

Instances

Instances details
type XCFieldOcc GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XCFieldOcc GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XCFieldOcc GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type family XXFieldOcc x Source #

Instances

Instances details
type XXFieldOcc (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XCImportDecl x Source #

Instances

Instances details
type XCImportDecl GhcPs Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XCImportDecl GhcRn Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XCImportDecl GhcTc Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XXImportDecl x Source #

Instances

Instances details
type XXImportDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEVar x Source #

Instances

Instances details
type XIEVar GhcPs Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XIEVar GhcRn Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XIEVar GhcTc Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEThingAbs x Source #

Instances

Instances details
type XIEThingAbs (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEThingAll x Source #

Instances

Instances details
type XIEThingAll (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEThingWith x Source #

Instances

Instances details
type XIEThingWith (GhcPass 'Parsed) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XIEThingWith (GhcPass 'Renamed) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XIEThingWith (GhcPass 'Typechecked) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEModuleContents x Source #

Instances

Instances details
type XIEModuleContents GhcPs Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XIEModuleContents GhcRn Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XIEModuleContents GhcTc Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEGroup x Source #

Instances

Instances details
type XIEGroup (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEDoc x Source #

Instances

Instances details
type XIEDoc (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEDocNamed x Source #

Instances

Instances details
type XIEDocNamed (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XXIE x Source #

Instances

Instances details
type XXIE (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family NoGhcTc (p :: Type) Source #

See Note [NoGhcTc] in GHC.Hs.Extension. It has to be in this module because it is used like an extension point (in the data definitions of types that should be parameter-agnostic.

Instances

Instances details
type NoGhcTc (GhcPass pass) Source #

Marks that a field uses the GhcRn variant even when the pass parameter is GhcTc. Useful for storing HsTypes in GHC.Hs.Exprs, say, because HsType GhcTc should never occur. See Note [NoGhcTc]

Instance details

Defined in GHC.Hs.Extension

type NoGhcTc (GhcPass pass) = GhcPass (NoGhcTcPass pass)

type LHsToken tok p = XRec p (HsToken tok) Source #

data HsToken (tok :: Symbol) Source #

Constructors

HsTok 

Instances

Instances details
KnownSymbol tok => Data (HsToken tok) Source # 
Instance details

Defined in Language.Haskell.Syntax.Extension

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsToken tok -> c (HsToken tok) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsToken tok) Source #

toConstr :: HsToken tok -> Constr Source #

dataTypeOf :: HsToken tok -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsToken tok)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsToken tok)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsToken tok -> HsToken tok Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsToken tok -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsToken tok -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsToken tok -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsToken tok -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsToken tok -> m (HsToken tok) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsToken tok -> m (HsToken tok) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsToken tok -> m (HsToken tok) Source #

type Anno (HsToken tok) Source # 
Instance details

Defined in GHC.Hs.Extension

type LHsUniToken tok utok p = XRec p (HsUniToken tok utok) Source #

data HsUniToken (tok :: Symbol) (utok :: Symbol) Source #

Constructors

HsNormalTok 
HsUnicodeTok 

Instances

Instances details
(KnownSymbol tok, KnownSymbol utok) => Data (HsUniToken tok utok) Source # 
Instance details

Defined in Language.Haskell.Syntax.Extension

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsUniToken tok utok -> c (HsUniToken tok utok) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsUniToken tok utok) Source #

toConstr :: HsUniToken tok utok -> Constr Source #

dataTypeOf :: HsUniToken tok utok -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsUniToken tok utok)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsUniToken tok utok)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsUniToken tok utok -> HsUniToken tok utok Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsUniToken tok utok -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsUniToken tok utok -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsUniToken tok utok -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsUniToken tok utok -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsUniToken tok utok -> m (HsUniToken tok utok) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsUniToken tok utok -> m (HsUniToken tok utok) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsUniToken tok utok -> m (HsUniToken tok utok) Source #

type Anno (HsUniToken tok utok) Source # 
Instance details

Defined in GHC.Hs.Extension

type Anno (HsUniToken tok utok) = TokenLocation