ghc-lib-parser-9.2.2.20220307: The GHC API, decoupled from GHC versions
Safe HaskellNone
LanguageHaskell2010

GHC.Hs.Type

Synopsis

Documentation

type Mult = Type Source #

Mult is a type alias for Type.

Mult must contain Type because multiplicity variables are mere type variables (of kind Multiplicity) in Haskell. So the simplest implementation is to make Mult be Type.

Multiplicities can be formed with: - One: GHC.Types.One (= oneDataCon) - Many: GHC.Types.Many (= manyDataCon) - Multiplication: GHC.Types.MultMul (= multMulTyCon)

So that Mult feels a bit more structured, we provide pattern synonyms and smart constructors for these.

data HsScaled pass a Source #

This is used in the syntax. In constructor declaration. It must keep the arrow representation.

Constructors

HsScaled (HsArrow pass) a 

Instances

Instances details
Data thing => Data (HsScaled GhcTc thing) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsScaled GhcTc thing -> c (HsScaled GhcTc thing) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsScaled GhcTc thing) #

toConstr :: HsScaled GhcTc thing -> Constr #

dataTypeOf :: HsScaled GhcTc thing -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsScaled GhcTc thing)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsScaled GhcTc thing)) #

gmapT :: (forall b. Data b => b -> b) -> HsScaled GhcTc thing -> HsScaled GhcTc thing #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcTc thing -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcTc thing -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsScaled GhcTc thing -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsScaled GhcTc thing -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsScaled GhcTc thing -> m (HsScaled GhcTc thing) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcTc thing -> m (HsScaled GhcTc thing) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcTc thing -> m (HsScaled GhcTc thing) #

Data thing => Data (HsScaled GhcRn thing) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsScaled GhcRn thing -> c (HsScaled GhcRn thing) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsScaled GhcRn thing) #

toConstr :: HsScaled GhcRn thing -> Constr #

dataTypeOf :: HsScaled GhcRn thing -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsScaled GhcRn thing)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsScaled GhcRn thing)) #

gmapT :: (forall b. Data b => b -> b) -> HsScaled GhcRn thing -> HsScaled GhcRn thing #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcRn thing -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcRn thing -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsScaled GhcRn thing -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsScaled GhcRn thing -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsScaled GhcRn thing -> m (HsScaled GhcRn thing) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcRn thing -> m (HsScaled GhcRn thing) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcRn thing -> m (HsScaled GhcRn thing) #

Data thing => Data (HsScaled GhcPs thing) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsScaled GhcPs thing -> c (HsScaled GhcPs thing) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsScaled GhcPs thing) #

toConstr :: HsScaled GhcPs thing -> Constr #

dataTypeOf :: HsScaled GhcPs thing -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsScaled GhcPs thing)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsScaled GhcPs thing)) #

gmapT :: (forall b. Data b => b -> b) -> HsScaled GhcPs thing -> HsScaled GhcPs thing #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcPs thing -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcPs thing -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsScaled GhcPs thing -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsScaled GhcPs thing -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsScaled GhcPs thing -> m (HsScaled GhcPs thing) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcPs thing -> m (HsScaled GhcPs thing) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcPs thing -> m (HsScaled GhcPs thing) #

Outputable a => Outputable (HsScaled pass a) Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: HsScaled pass a -> SDoc Source #

hsMult :: HsScaled pass a -> HsArrow pass Source #

data HsArrow pass Source #

Denotes the type of arrows in the surface language

Constructors

HsUnrestrictedArrow IsUnicodeSyntax

a -> b or a → b

HsLinearArrow IsUnicodeSyntax (Maybe AddEpAnn)

a %1 -> b or a %1 → b, or a ⊸ b

HsExplicitMult IsUnicodeSyntax (Maybe AddEpAnn) (LHsType pass)

a %m -> b or a %m → b (very much including `a %Many -> b`! This is how the programmer wrote it). It is stored as an HsType so as to preserve the syntax as written in the program.

Instances

Instances details
Data (HsArrow GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsArrow GhcTc -> c (HsArrow GhcTc) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArrow GhcTc) #

toConstr :: HsArrow GhcTc -> Constr #

dataTypeOf :: HsArrow GhcTc -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsArrow GhcTc -> HsArrow GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsArrow GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArrow GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArrow GhcTc -> m (HsArrow GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcTc -> m (HsArrow GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcTc -> m (HsArrow GhcTc) #

Data (HsArrow GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsArrow GhcRn -> c (HsArrow GhcRn) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArrow GhcRn) #

toConstr :: HsArrow GhcRn -> Constr #

dataTypeOf :: HsArrow GhcRn -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsArrow GhcRn -> HsArrow GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsArrow GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArrow GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArrow GhcRn -> m (HsArrow GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcRn -> m (HsArrow GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcRn -> m (HsArrow GhcRn) #

Data (HsArrow GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsArrow GhcPs -> c (HsArrow GhcPs) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArrow GhcPs) #

toConstr :: HsArrow GhcPs -> Constr #

dataTypeOf :: HsArrow GhcPs -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsArrow GhcPs -> HsArrow GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcPs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsArrow GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArrow GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArrow GhcPs -> m (HsArrow GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcPs -> m (HsArrow GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcPs -> m (HsArrow GhcPs) #

OutputableBndrId pass => Outputable (HsArrow (GhcPass pass)) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: HsArrow (GhcPass pass) -> SDoc Source #

arrowToHsType :: HsArrow GhcRn -> LHsType GhcRn Source #

Convert an arrow into its corresponding multiplicity. In essence this erases the information of whether the programmer wrote an explicit multiplicity or a shorthand.

hsLinear :: a -> HsScaled pass a Source #

When creating syntax we use the shorthands. It's better for printing, also, the shorthands work trivially at each pass.

hsUnrestricted :: a -> HsScaled pass a Source #

When creating syntax we use the shorthands. It's better for printing, also, the shorthands work trivially at each pass.

data HsType pass Source #

Haskell Type

Constructors

HsForAllTy
HsQualTy 

Fields

HsTyVar (XTyVar pass) PromotionFlag (LIdP pass)
HsAppTy (XAppTy pass) (LHsType pass) (LHsType pass)
HsAppKindTy (XAppKindTy pass) (LHsType pass) (LHsKind pass) 
HsFunTy (XFunTy pass) (HsArrow pass) (LHsType pass) (LHsType pass)
HsListTy (XListTy pass) (LHsType pass)
HsTupleTy (XTupleTy pass) HsTupleSort [LHsType pass]
HsSumTy (XSumTy pass) [LHsType pass]
HsOpTy (XOpTy pass) (LHsType pass) (LIdP pass) (LHsType pass)
HsParTy (XParTy pass) (LHsType pass)
HsIParamTy (XIParamTy pass) (XRec pass HsIPName) (LHsType pass)
(?x :: ty)
HsStarTy (XStarTy pass) Bool
HsKindSig (XKindSig pass) (LHsType pass) (LHsKind pass)
(ty :: kind)
HsSpliceTy (XSpliceTy pass) (HsSplice pass)
HsDocTy (XDocTy pass) (LHsType pass) LHsDocString
HsBangTy (XBangTy pass) HsSrcBang (LHsType pass)
HsRecTy (XRecTy pass) [LConDeclField pass]
HsExplicitListTy (XExplicitListTy pass) PromotionFlag [LHsType pass]
HsExplicitTupleTy (XExplicitTupleTy pass) [LHsType pass]
HsTyLit (XTyLit pass) HsTyLit
HsWildCardTy (XWildCardTy pass)
XHsType !(XXType pass) 

Instances

Instances details
Data (HsType GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsType GhcTc -> c (HsType GhcTc) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsType GhcTc) #

toConstr :: HsType GhcTc -> Constr #

dataTypeOf :: HsType GhcTc -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsType GhcTc -> HsType GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsType GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsType GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsType GhcTc -> m (HsType GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcTc -> m (HsType GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcTc -> m (HsType GhcTc) #

Data (HsType GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsType GhcRn -> c (HsType GhcRn) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsType GhcRn) #

toConstr :: HsType GhcRn -> Constr #

dataTypeOf :: HsType GhcRn -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsType GhcRn -> HsType GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsType GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsType GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsType GhcRn -> m (HsType GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcRn -> m (HsType GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcRn -> m (HsType GhcRn) #

Data (HsType GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsType GhcPs -> c (HsType GhcPs) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsType GhcPs) #

toConstr :: HsType GhcPs -> Constr #

dataTypeOf :: HsType GhcPs -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsType GhcPs -> HsType GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcPs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsType GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsType GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsType GhcPs -> m (HsType GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcPs -> m (HsType GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcPs -> m (HsType GhcPs) #

OutputableBndrId p => Outputable (HsType (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: HsType (GhcPass p) -> SDoc Source #

DisambTD (HsType GhcPs) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Anno [LocatedA (HsType (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 (HsKind (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 (FamEqn p (LocatedA (HsType p))) Source # 
Instance details

Defined in GHC.Hs.Decls

type LHsType pass Source #

Arguments

 = XRec pass (HsType pass)

May have AnnKeywordId : AnnComma when in a list

Located Haskell Type

type HsKind pass = HsType pass Source #

Haskell Kind

type LHsKind pass Source #

Arguments

 = XRec pass (HsKind pass)

AnnKeywordId : AnnDcolon

Located Haskell Kind

data HsForAllTelescope pass Source #

The type variable binders in an HsForAllTy. See also Note [Variable Specificity and Forall Visibility] in GHC.Tc.Gen.HsType.

Constructors

HsForAllVis

A visible forall (e.g., forall a -> {...}). These do not have any notion of specificity, so we use () as a placeholder value.

Fields

HsForAllInvis

An invisible forall (e.g., forall a {b} c. {...}), where each binder has a Specificity.

XHsForAllTelescope !(XXHsForAllTelescope pass) 

Instances

Instances details
Data (HsForAllTelescope GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsForAllTelescope GhcTc -> c (HsForAllTelescope GhcTc) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsForAllTelescope GhcTc) #

toConstr :: HsForAllTelescope GhcTc -> Constr #

dataTypeOf :: HsForAllTelescope GhcTc -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsForAllTelescope GhcTc -> HsForAllTelescope GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsForAllTelescope GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsForAllTelescope GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcTc -> m (HsForAllTelescope GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcTc -> m (HsForAllTelescope GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcTc -> m (HsForAllTelescope GhcTc) #

Data (HsForAllTelescope GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsForAllTelescope GhcRn -> c (HsForAllTelescope GhcRn) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsForAllTelescope GhcRn) #

toConstr :: HsForAllTelescope GhcRn -> Constr #

dataTypeOf :: HsForAllTelescope GhcRn -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsForAllTelescope GhcRn -> HsForAllTelescope GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsForAllTelescope GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsForAllTelescope GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcRn -> m (HsForAllTelescope GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcRn -> m (HsForAllTelescope GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcRn -> m (HsForAllTelescope GhcRn) #

Data (HsForAllTelescope GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsForAllTelescope GhcPs -> c (HsForAllTelescope GhcPs) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsForAllTelescope GhcPs) #

toConstr :: HsForAllTelescope GhcPs -> Constr #

dataTypeOf :: HsForAllTelescope GhcPs -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsForAllTelescope GhcPs -> HsForAllTelescope GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcPs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsForAllTelescope GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsForAllTelescope GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcPs -> m (HsForAllTelescope GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcPs -> m (HsForAllTelescope GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcPs -> m (HsForAllTelescope GhcPs) #

OutputableBndrId p => Outputable (HsForAllTelescope (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

type EpAnnForallTy Source #

Arguments

 = EpAnn (AddEpAnn, AddEpAnn)

Location of forall and -> for HsForAllVis Location of forall and . for HsForAllInvis

data HsTyVarBndr flag pass Source #

Haskell Type Variable Binder The flag annotates the binder. It is Specificity in places where explicit specificity is allowed (e.g. x :: forall {a} b. ...) or () in other places.

Constructors

UserTyVar (XUserTyVar pass) flag (LIdP pass) 
KindedTyVar (XKindedTyVar pass) flag (LIdP pass) (LHsKind pass)
XTyVarBndr !(XXTyVarBndr pass) 

Instances

Instances details
Data flag => Data (HsTyVarBndr flag GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyVarBndr flag GhcTc -> c (HsTyVarBndr flag GhcTc) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyVarBndr flag GhcTc) #

toConstr :: HsTyVarBndr flag GhcTc -> Constr #

dataTypeOf :: HsTyVarBndr flag GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyVarBndr flag GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyVarBndr flag GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> HsTyVarBndr flag GhcTc -> HsTyVarBndr flag GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcTc -> m (HsTyVarBndr flag GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcTc -> m (HsTyVarBndr flag GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcTc -> m (HsTyVarBndr flag GhcTc) #

Data flag => Data (HsTyVarBndr flag GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyVarBndr flag GhcRn -> c (HsTyVarBndr flag GhcRn) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyVarBndr flag GhcRn) #

toConstr :: HsTyVarBndr flag GhcRn -> Constr #

dataTypeOf :: HsTyVarBndr flag GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyVarBndr flag GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyVarBndr flag GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> HsTyVarBndr flag GhcRn -> HsTyVarBndr flag GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcRn -> m (HsTyVarBndr flag GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcRn -> m (HsTyVarBndr flag GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcRn -> m (HsTyVarBndr flag GhcRn) #

Data flag => Data (HsTyVarBndr flag GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyVarBndr flag GhcPs -> c (HsTyVarBndr flag GhcPs) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyVarBndr flag GhcPs) #

toConstr :: HsTyVarBndr flag GhcPs -> Constr #

dataTypeOf :: HsTyVarBndr flag GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyVarBndr flag GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyVarBndr flag GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> HsTyVarBndr flag GhcPs -> HsTyVarBndr flag GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcPs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcPs -> m (HsTyVarBndr flag GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcPs -> m (HsTyVarBndr flag GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcPs -> m (HsTyVarBndr flag GhcPs) #

(OutputableBndrId p, OutputableBndrFlag flag p) => Outputable (HsTyVarBndr flag (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: HsTyVarBndr flag (GhcPass p) -> SDoc Source #

NamedThing (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 (HsTyVarBndr _flag GhcRn) Source # 
Instance details

Defined in GHC.Hs.Type

type Anno (HsTyVarBndr _flag GhcPs) 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 LHsTyVarBndr flag pass = XRec pass (HsTyVarBndr flag pass) Source #

Located Haskell Type Variable Binder

data LHsQTyVars pass Source #

Located Haskell Quantified Type Variables

Constructors

HsQTvs 

Fields

XLHsQTyVars !(XXLHsQTyVars pass) 

Instances

Instances details
Data (LHsQTyVars GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsQTyVars GhcTc -> c (LHsQTyVars GhcTc) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsQTyVars GhcTc) #

toConstr :: LHsQTyVars GhcTc -> Constr #

dataTypeOf :: LHsQTyVars GhcTc -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> LHsQTyVars GhcTc -> LHsQTyVars GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> LHsQTyVars GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsQTyVars GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcTc -> m (LHsQTyVars GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcTc -> m (LHsQTyVars GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcTc -> m (LHsQTyVars GhcTc) #

Data (LHsQTyVars GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsQTyVars GhcRn -> c (LHsQTyVars GhcRn) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsQTyVars GhcRn) #

toConstr :: LHsQTyVars GhcRn -> Constr #

dataTypeOf :: LHsQTyVars GhcRn -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> LHsQTyVars GhcRn -> LHsQTyVars GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> LHsQTyVars GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsQTyVars GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcRn -> m (LHsQTyVars GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcRn -> m (LHsQTyVars GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcRn -> m (LHsQTyVars GhcRn) #

Data (LHsQTyVars GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsQTyVars GhcPs -> c (LHsQTyVars GhcPs) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsQTyVars GhcPs) #

toConstr :: LHsQTyVars GhcPs -> Constr #

dataTypeOf :: LHsQTyVars GhcPs -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> LHsQTyVars GhcPs -> LHsQTyVars GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcPs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> LHsQTyVars GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsQTyVars GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcPs -> m (LHsQTyVars GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcPs -> m (LHsQTyVars GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcPs -> m (LHsQTyVars GhcPs) #

OutputableBndrId p => Outputable (LHsQTyVars (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: LHsQTyVars (GhcPass p) -> SDoc Source #

data HsOuterTyVarBndrs flag pass Source #

The outermost type variables in a type that obeys the forall-or-nothing rule. See Note [forall-or-nothing rule].

Constructors

HsOuterImplicit

Implicit forall, e.g., f :: a -> b -> b

HsOuterExplicit

Explicit forall, e.g., f :: forall a b. a -> b -> b

Fields

XHsOuterTyVarBndrs !(XXHsOuterTyVarBndrs pass) 

Instances

Instances details
Data flag => Data (HsOuterTyVarBndrs flag GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsOuterTyVarBndrs flag GhcTc -> c (HsOuterTyVarBndrs flag GhcTc) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOuterTyVarBndrs flag GhcTc) #

toConstr :: HsOuterTyVarBndrs flag GhcTc -> Constr #

dataTypeOf :: HsOuterTyVarBndrs flag GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOuterTyVarBndrs flag GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOuterTyVarBndrs flag GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> HsOuterTyVarBndrs flag GhcTc -> HsOuterTyVarBndrs flag GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcTc -> m (HsOuterTyVarBndrs flag GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcTc -> m (HsOuterTyVarBndrs flag GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcTc -> m (HsOuterTyVarBndrs flag GhcTc) #

Data flag => Data (HsOuterTyVarBndrs flag GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsOuterTyVarBndrs flag GhcRn -> c (HsOuterTyVarBndrs flag GhcRn) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOuterTyVarBndrs flag GhcRn) #

toConstr :: HsOuterTyVarBndrs flag GhcRn -> Constr #

dataTypeOf :: HsOuterTyVarBndrs flag GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOuterTyVarBndrs flag GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOuterTyVarBndrs flag GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> HsOuterTyVarBndrs flag GhcRn -> HsOuterTyVarBndrs flag GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcRn -> m (HsOuterTyVarBndrs flag GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcRn -> m (HsOuterTyVarBndrs flag GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcRn -> m (HsOuterTyVarBndrs flag GhcRn) #

Data flag => Data (HsOuterTyVarBndrs flag GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsOuterTyVarBndrs flag GhcPs -> c (HsOuterTyVarBndrs flag GhcPs) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOuterTyVarBndrs flag GhcPs) #

toConstr :: HsOuterTyVarBndrs flag GhcPs -> Constr #

dataTypeOf :: HsOuterTyVarBndrs flag GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOuterTyVarBndrs flag GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOuterTyVarBndrs flag GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> HsOuterTyVarBndrs flag GhcPs -> HsOuterTyVarBndrs flag GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcPs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcPs -> m (HsOuterTyVarBndrs flag GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcPs -> m (HsOuterTyVarBndrs flag GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcPs -> m (HsOuterTyVarBndrs flag GhcPs) #

(OutputableBndrFlag flag p, OutputableBndrFlag flag (NoGhcTcPass p), OutputableBndrId p) => Outputable (HsOuterTyVarBndrs flag (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: HsOuterTyVarBndrs flag (GhcPass p) -> SDoc Source #

type Anno (HsOuterTyVarBndrs _1 (GhcPass _2)) Source # 
Instance details

Defined in GHC.Hs.Type

type HsOuterFamEqnTyVarBndrs = HsOuterTyVarBndrs () Source #

Used for type-family instance equations, e.g.,

type instance forall a. F [a] = Tree a

The notion of specificity is irrelevant in type family equations, so we use () for the HsOuterTyVarBndrs flag.

type HsOuterSigTyVarBndrs = HsOuterTyVarBndrs Specificity Source #

Used for signatures, e.g.,

f :: forall a {b}. blah

We use Specificity for the HsOuterTyVarBndrs flag to allow distinguishing between specified and inferred type variables.

data HsWildCardBndrs pass thing Source #

Haskell Wildcard Binders

Constructors

HsWC 

Fields

XHsWildCardBndrs !(XXHsWildCardBndrs pass thing) 

Instances

Instances details
Data thing => Data (HsWildCardBndrs GhcTc thing) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWildCardBndrs GhcTc thing -> c (HsWildCardBndrs GhcTc thing) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs GhcTc thing) #

toConstr :: HsWildCardBndrs GhcTc thing -> Constr #

dataTypeOf :: HsWildCardBndrs GhcTc thing -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs GhcTc thing)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs GhcTc thing)) #

gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs GhcTc thing -> HsWildCardBndrs GhcTc thing #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcTc thing -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcTc thing -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs GhcTc thing -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs GhcTc thing -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcTc thing -> m (HsWildCardBndrs GhcTc thing) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcTc thing -> m (HsWildCardBndrs GhcTc thing) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcTc thing -> m (HsWildCardBndrs GhcTc thing) #

Data thing => Data (HsWildCardBndrs GhcRn thing) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWildCardBndrs GhcRn thing -> c (HsWildCardBndrs GhcRn thing) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs GhcRn thing) #

toConstr :: HsWildCardBndrs GhcRn thing -> Constr #

dataTypeOf :: HsWildCardBndrs GhcRn thing -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs GhcRn thing)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs GhcRn thing)) #

gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs GhcRn thing -> HsWildCardBndrs GhcRn thing #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcRn thing -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcRn thing -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs GhcRn thing -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs GhcRn thing -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcRn thing -> m (HsWildCardBndrs GhcRn thing) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcRn thing -> m (HsWildCardBndrs GhcRn thing) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcRn thing -> m (HsWildCardBndrs GhcRn thing) #

Data thing => Data (HsWildCardBndrs GhcPs thing) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWildCardBndrs GhcPs thing -> c (HsWildCardBndrs GhcPs thing) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs GhcPs thing) #

toConstr :: HsWildCardBndrs GhcPs thing -> Constr #

dataTypeOf :: HsWildCardBndrs GhcPs thing -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs GhcPs thing)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs GhcPs thing)) #

gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs GhcPs thing -> HsWildCardBndrs GhcPs thing #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcPs thing -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcPs thing -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs GhcPs thing -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs GhcPs thing -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcPs thing -> m (HsWildCardBndrs GhcPs thing) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcPs thing -> m (HsWildCardBndrs GhcPs thing) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcPs thing -> m (HsWildCardBndrs GhcPs thing) #

Outputable thing => Outputable (HsWildCardBndrs (GhcPass p) thing) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: HsWildCardBndrs (GhcPass p) thing -> SDoc Source #

data HsPatSigType pass Source #

Types that can appear in pattern signatures, as well as the signatures for term-level binders in RULES. See Note [Pattern signature binders and scoping].

This is very similar to HsSigWcType, but with slightly different semantics: see Note [HsType binders]. See also Note [The wildcard story for types].

Constructors

HsPS 

Fields

XHsPatSigType !(XXHsPatSigType pass) 

Instances

Instances details
Data (HsPatSigType GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsPatSigType GhcTc -> c (HsPatSigType GhcTc) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatSigType GhcTc) #

toConstr :: HsPatSigType GhcTc -> Constr #

dataTypeOf :: HsPatSigType GhcTc -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsPatSigType GhcTc -> HsPatSigType GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsPatSigType GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatSigType GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatSigType GhcTc -> m (HsPatSigType GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcTc -> m (HsPatSigType GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcTc -> m (HsPatSigType GhcTc) #

Data (HsPatSigType GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsPatSigType GhcRn -> c (HsPatSigType GhcRn) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatSigType GhcRn) #

toConstr :: HsPatSigType GhcRn -> Constr #

dataTypeOf :: HsPatSigType GhcRn -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsPatSigType GhcRn -> HsPatSigType GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsPatSigType GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatSigType GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatSigType GhcRn -> m (HsPatSigType GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcRn -> m (HsPatSigType GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcRn -> m (HsPatSigType GhcRn) #

Data (HsPatSigType GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsPatSigType GhcPs -> c (HsPatSigType GhcPs) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatSigType GhcPs) #

toConstr :: HsPatSigType GhcPs -> Constr #

dataTypeOf :: HsPatSigType GhcPs -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsPatSigType GhcPs -> HsPatSigType GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcPs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsPatSigType GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatSigType GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatSigType GhcPs -> m (HsPatSigType GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcPs -> m (HsPatSigType GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcPs -> m (HsPatSigType GhcPs) #

OutputableBndrId p => Outputable (HsPatSigType (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: HsPatSigType (GhcPass p) -> SDoc Source #

data HsPSRn Source #

The extension field for HsPatSigType, which is only used in the renamer onwards. See Note [Pattern signature binders and scoping].

Constructors

HsPSRn 

Fields

Instances

Instances details
Data HsPSRn Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

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

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

toConstr :: HsPSRn -> Constr #

dataTypeOf :: HsPSRn -> DataType #

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

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

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

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

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

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

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

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

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

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

data HsSigType pass Source #

A type signature that obeys the forall-or-nothing rule. In other words, an LHsType that uses an HsOuterSigTyVarBndrs to represent its outermost type variable quantification. See Note [Representing type signatures].

Constructors

HsSig 

Fields

XHsSigType !(XXHsSigType pass) 

Instances

Instances details
Data (HsSigType GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSigType GhcTc -> c (HsSigType GhcTc) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSigType GhcTc) #

toConstr :: HsSigType GhcTc -> Constr #

dataTypeOf :: HsSigType GhcTc -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsSigType GhcTc -> HsSigType GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsSigType GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSigType GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSigType GhcTc -> m (HsSigType GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcTc -> m (HsSigType GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcTc -> m (HsSigType GhcTc) #

Data (HsSigType GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSigType GhcRn -> c (HsSigType GhcRn) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSigType GhcRn) #

toConstr :: HsSigType GhcRn -> Constr #

dataTypeOf :: HsSigType GhcRn -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsSigType GhcRn -> HsSigType GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsSigType GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSigType GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSigType GhcRn -> m (HsSigType GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcRn -> m (HsSigType GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcRn -> m (HsSigType GhcRn) #

Data (HsSigType GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSigType GhcPs -> c (HsSigType GhcPs) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSigType GhcPs) #

toConstr :: HsSigType GhcPs -> Constr #

dataTypeOf :: HsSigType GhcPs -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsSigType GhcPs -> HsSigType GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcPs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsSigType GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSigType GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSigType GhcPs -> m (HsSigType GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcPs -> m (HsSigType GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcPs -> m (HsSigType GhcPs) #

OutputableBndrId p => Outputable (HsSigType (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: HsSigType (GhcPass p) -> SDoc Source #

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

Defined in GHC.Hs.Type

type LHsSigType pass = XRec pass (HsSigType pass) Source #

Located Haskell Signature Type

type LHsSigWcType pass = HsWildCardBndrs pass (LHsSigType pass) Source #

Located Haskell Signature Wildcard Type

type LHsWcType pass = HsWildCardBndrs pass (LHsType pass) Source #

Located Haskell Wildcard Type

data HsTupleSort Source #

Haskell Tuple Sort

Instances

Instances details
Data HsTupleSort Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

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

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

toConstr :: HsTupleSort -> Constr #

dataTypeOf :: HsTupleSort -> DataType #

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

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

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

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

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

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

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

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

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

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

type HsContext pass = [LHsType pass] Source #

Haskell Context

type LHsContext pass Source #

Arguments

 = XRec pass (HsContext pass)

AnnKeywordId : AnnUnit For details on above see note [exact print annotations] in GHC.Parser.Annotation

Located Haskell Context

data HsTyLit Source #

Haskell Type Literal

Instances

Instances details
Data HsTyLit Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

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

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

toConstr :: HsTyLit -> Constr #

dataTypeOf :: HsTyLit -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable HsTyLit Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: HsTyLit -> SDoc Source #

newtype HsIPName Source #

These names are used early on to store the names of implicit parameters. They completely disappear after type-checking.

Constructors

HsIPName FastString 

Instances

Instances details
Eq HsIPName Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Data HsIPName Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

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

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

toConstr :: HsIPName -> Constr #

dataTypeOf :: HsIPName -> DataType #

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

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

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

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

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

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

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

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

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

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

OutputableBndr HsIPName Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Outputable HsIPName Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: HsIPName -> SDoc Source #

type Anno HsIPName Source # 
Instance details

Defined in GHC.Hs.Type

data HsArg tm ty Source #

Constructors

HsValArg tm 
HsTypeArg SrcSpan ty 
HsArgPar SrcSpan 

Instances

Instances details
(Data a, Data b) => Data (HsArg a b) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> HsArg a b -> c (HsArg a b) #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArg a b) #

toConstr :: HsArg a b -> Constr #

dataTypeOf :: HsArg a b -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArg a b)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArg a b)) #

gmapT :: (forall b0. Data b0 => b0 -> b0) -> HsArg a b -> HsArg a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg a b -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsArg a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg a b -> m (HsArg a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg a b -> m (HsArg a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg a b -> m (HsArg a b) #

(Outputable tm, Outputable ty) => Outputable (HsArg tm ty) Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: HsArg tm ty -> SDoc Source #

lhsTypeArgSrcSpan :: LHsTypeArg (GhcPass pass) -> SrcSpan Source #

Compute the SrcSpan associated with an LHsTypeArg.

class OutputableBndrFlag flag p Source #

Minimal complete definition

pprTyVarBndr

Instances

Instances details
OutputableBndrFlag () p Source # 
Instance details

Defined in GHC.Hs.Type

Methods

pprTyVarBndr :: HsTyVarBndr () (GhcPass p) -> SDoc

OutputableBndrFlag Specificity p Source # 
Instance details

Defined in GHC.Hs.Type

type LBangType pass = XRec pass (BangType pass) Source #

Located Bang Type

type BangType pass = HsType pass Source #

Bang Type

In the parser, strictness and packedness annotations bind more tightly than docstrings. This means that when consuming a BangType (and looking for HsBangTy) we must be ready to peer behind a potential layer of HsDocTy. See #15206 for motivation and getBangType for an example.

data HsSrcBang Source #

Haskell Source Bang

Bangs on data constructor arguments as the user wrote them in the source code.

(HsSrcBang _ SrcUnpack SrcLazy) and (HsSrcBang _ SrcUnpack NoSrcStrict) (without StrictData) makes no sense, we emit a warning (in checkValidDataCon) and treat it like (HsSrcBang _ NoSrcUnpack SrcLazy)

Instances

Instances details
Data HsSrcBang Source # 
Instance details

Defined in GHC.Core.DataCon

Methods

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

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

toConstr :: HsSrcBang -> Constr #

dataTypeOf :: HsSrcBang -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable HsSrcBang Source # 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: HsSrcBang -> SDoc Source #

data HsImplBang Source #

Haskell Implementation Bang

Bangs of data constructor arguments as generated by the compiler after consulting HsSrcBang, flags, etc.

Constructors

HsLazy

Lazy field, or one with an unlifted type

HsStrict

Strict but not unpacked field

HsUnpack (Maybe Coercion)

Strict and unpacked field co :: arg-ty ~ product-ty HsBang

Instances

Instances details
Data HsImplBang Source # 
Instance details

Defined in GHC.Core.DataCon

Methods

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

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

toConstr :: HsImplBang -> Constr #

dataTypeOf :: HsImplBang -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable HsImplBang Source # 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: HsImplBang -> SDoc Source #

data SrcStrictness Source #

Source Strictness

What strictness annotation the user wrote

Constructors

SrcLazy

Lazy, ie '~'

SrcStrict

Strict, ie !

NoSrcStrict

no strictness annotation

Instances

Instances details
Eq SrcStrictness Source # 
Instance details

Defined in GHC.Core.DataCon

Data SrcStrictness Source # 
Instance details

Defined in GHC.Core.DataCon

Methods

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

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

toConstr :: SrcStrictness -> Constr #

dataTypeOf :: SrcStrictness -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable SrcStrictness Source # 
Instance details

Defined in GHC.Core.DataCon

Binary SrcStrictness Source # 
Instance details

Defined in GHC.Core.DataCon

data SrcUnpackedness Source #

Source Unpackedness

What unpackedness the user requested

Constructors

SrcUnpack

{--} specified

SrcNoUnpack

{--} specified

NoSrcUnpack

no unpack pragma

Instances

Instances details
Eq SrcUnpackedness Source # 
Instance details

Defined in GHC.Core.DataCon

Data SrcUnpackedness Source # 
Instance details

Defined in GHC.Core.DataCon

Methods

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

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

toConstr :: SrcUnpackedness -> Constr #

dataTypeOf :: SrcUnpackedness -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable SrcUnpackedness Source # 
Instance details

Defined in GHC.Core.DataCon

Binary SrcUnpackedness Source # 
Instance details

Defined in GHC.Core.DataCon

data ConDeclField pass Source #

Constructor Declaration Field

Constructors

ConDeclField

Fields

XConDeclField !(XXConDeclField pass) 

Instances

Instances details
Data (ConDeclField GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDeclField GhcTc -> c (ConDeclField GhcTc) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDeclField GhcTc) #

toConstr :: ConDeclField GhcTc -> Constr #

dataTypeOf :: ConDeclField GhcTc -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> ConDeclField GhcTc -> ConDeclField GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConDeclField GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDeclField GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDeclField GhcTc -> m (ConDeclField GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcTc -> m (ConDeclField GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcTc -> m (ConDeclField GhcTc) #

Data (ConDeclField GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDeclField GhcRn -> c (ConDeclField GhcRn) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDeclField GhcRn) #

toConstr :: ConDeclField GhcRn -> Constr #

dataTypeOf :: ConDeclField GhcRn -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> ConDeclField GhcRn -> ConDeclField GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConDeclField GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDeclField GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDeclField GhcRn -> m (ConDeclField GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcRn -> m (ConDeclField GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcRn -> m (ConDeclField GhcRn) #

Data (ConDeclField GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDeclField GhcPs -> c (ConDeclField GhcPs) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDeclField GhcPs) #

toConstr :: ConDeclField GhcPs -> Constr #

dataTypeOf :: ConDeclField GhcPs -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> ConDeclField GhcPs -> ConDeclField GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcPs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConDeclField GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDeclField GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDeclField GhcPs -> m (ConDeclField GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcPs -> m (ConDeclField GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcPs -> m (ConDeclField GhcPs) #

OutputableBndrId p => Outputable (ConDeclField (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: ConDeclField (GhcPass p) -> SDoc Source #

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

Defined in GHC.Hs.Decls

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

Defined in GHC.Hs.Type

type LConDeclField pass Source #

Arguments

 = XRec pass (ConDeclField pass)

May have AnnKeywordId : AnnComma when in a list

Located Constructor Declaration Field

data HsConDetails tyarg arg rec Source #

Describes the arguments to a data constructor. This is a common representation for several constructor-related concepts, including:

  • The arguments in a Haskell98-style constructor declaration (see HsConDeclH98Details in GHC.Hs.Decls).
  • The arguments in constructor patterns in case/function definitions (see HsConPatDetails in GHC.Hs.Pat).
  • The left-hand side arguments in a pattern synonym binding (see HsPatSynDetails in GHC.Hs.Binds).

One notable exception is the arguments in a GADT constructor, which uses a separate data type entirely (see HsConDeclGADTDetails in GHC.Hs.Decls). This is because GADT constructors cannot be declared with infix syntax, unlike the concepts above (#18844).

Constructors

PrefixCon [tyarg] [arg] 
RecCon rec 
InfixCon arg arg 

Instances

Instances details
(Data tyarg, Data arg, Data rec) => Data (HsConDetails tyarg arg rec) Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsConDetails tyarg arg rec -> c (HsConDetails tyarg arg rec) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsConDetails tyarg arg rec) #

toConstr :: HsConDetails tyarg arg rec -> Constr #

dataTypeOf :: HsConDetails tyarg arg rec -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsConDetails tyarg arg rec)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsConDetails tyarg arg rec)) #

gmapT :: (forall b. Data b => b -> b) -> HsConDetails tyarg arg rec -> HsConDetails tyarg arg rec #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsConDetails tyarg arg rec -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsConDetails tyarg arg rec -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsConDetails tyarg arg rec -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsConDetails tyarg arg rec -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec) #

(Outputable tyarg, Outputable arg, Outputable rec) => Outputable (HsConDetails tyarg arg rec) Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: HsConDetails tyarg arg rec -> SDoc Source #

noTypeArgs :: [Void] Source #

An empty list that can be used to indicate that there are no type arguments allowed in cases where HsConDetails is applied to Void.

data FieldOcc pass Source #

Field Occurrence

Represents an *occurrence* of an unambiguous field. This may or may not be a binding occurrence (e.g. this type is used in ConDeclField and RecordPatSynField which bind their fields, but also in HsRecField for record construction and patterns, which do not).

We store both the RdrName the user originally wrote, and after the renamer, the selector function.

Constructors

FieldOcc 

Fields

XFieldOcc !(XXFieldOcc pass) 

Instances

Instances details
(Eq (XCFieldOcc pass), Eq (XXFieldOcc pass)) => Eq (FieldOcc pass) Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

(==) :: FieldOcc pass -> FieldOcc pass -> Bool #

(/=) :: FieldOcc pass -> FieldOcc pass -> Bool #

Data (FieldOcc GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldOcc GhcTc -> c (FieldOcc GhcTc) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldOcc GhcTc) #

toConstr :: FieldOcc GhcTc -> Constr #

dataTypeOf :: FieldOcc GhcTc -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> FieldOcc GhcTc -> FieldOcc GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> FieldOcc GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldOcc GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldOcc GhcTc -> m (FieldOcc GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcTc -> m (FieldOcc GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcTc -> m (FieldOcc GhcTc) #

Data (FieldOcc GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldOcc GhcRn -> c (FieldOcc GhcRn) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldOcc GhcRn) #

toConstr :: FieldOcc GhcRn -> Constr #

dataTypeOf :: FieldOcc GhcRn -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> FieldOcc GhcRn -> FieldOcc GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> FieldOcc GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldOcc GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldOcc GhcRn -> m (FieldOcc GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcRn -> m (FieldOcc GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcRn -> m (FieldOcc GhcRn) #

Data (FieldOcc GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldOcc GhcPs -> c (FieldOcc GhcPs) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldOcc GhcPs) #

toConstr :: FieldOcc GhcPs -> Constr #

dataTypeOf :: FieldOcc GhcPs -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> FieldOcc GhcPs -> FieldOcc GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcPs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> FieldOcc GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldOcc GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldOcc GhcPs -> m (FieldOcc GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcPs -> m (FieldOcc GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcPs -> m (FieldOcc GhcPs) #

OutputableBndr (FieldOcc pass) Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Outputable (FieldOcc pass) Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: FieldOcc pass -> SDoc Source #

OutputableBndr (GenLocated SrcSpan (FieldOcc pass)) Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

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

Defined in GHC.Hs.Type

type Anno (HsRecField (GhcPass p) arg) Source # 
Instance details

Defined in GHC.Hs.Pat

type LFieldOcc pass = XRec pass (FieldOcc pass) Source #

Located Field Occurrence

data AmbiguousFieldOcc pass Source #

Ambiguous Field Occurrence

Represents an *occurrence* of a field that is potentially ambiguous after the renamer, with the ambiguity resolved by the typechecker. We always store the RdrName that the user originally wrote, and store the selector function after the renamer (for unambiguous occurrences) or the typechecker (for ambiguous occurrences).

See Note [HsRecField and HsRecUpdField] in GHC.Hs.Pat and Note [Disambiguating record fields] in GHC.Tc.Gen.Head. See Note [Located RdrNames] in GHC.Hs.Expr

Instances

Instances details
Data (AmbiguousFieldOcc GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AmbiguousFieldOcc GhcTc -> c (AmbiguousFieldOcc GhcTc) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AmbiguousFieldOcc GhcTc) #

toConstr :: AmbiguousFieldOcc GhcTc -> Constr #

dataTypeOf :: AmbiguousFieldOcc GhcTc -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> AmbiguousFieldOcc GhcTc -> AmbiguousFieldOcc GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcTc -> m (AmbiguousFieldOcc GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcTc -> m (AmbiguousFieldOcc GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcTc -> m (AmbiguousFieldOcc GhcTc) #

Data (AmbiguousFieldOcc GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AmbiguousFieldOcc GhcRn -> c (AmbiguousFieldOcc GhcRn) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AmbiguousFieldOcc GhcRn) #

toConstr :: AmbiguousFieldOcc GhcRn -> Constr #

dataTypeOf :: AmbiguousFieldOcc GhcRn -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> AmbiguousFieldOcc GhcRn -> AmbiguousFieldOcc GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcRn -> m (AmbiguousFieldOcc GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcRn -> m (AmbiguousFieldOcc GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcRn -> m (AmbiguousFieldOcc GhcRn) #

Data (AmbiguousFieldOcc GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AmbiguousFieldOcc GhcPs -> c (AmbiguousFieldOcc GhcPs) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AmbiguousFieldOcc GhcPs) #

toConstr :: AmbiguousFieldOcc GhcPs -> Constr #

dataTypeOf :: AmbiguousFieldOcc GhcPs -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> AmbiguousFieldOcc GhcPs -> AmbiguousFieldOcc GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcPs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcPs -> m (AmbiguousFieldOcc GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcPs -> m (AmbiguousFieldOcc GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcPs -> m (AmbiguousFieldOcc GhcPs) #

OutputableBndr (AmbiguousFieldOcc (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

Outputable (AmbiguousFieldOcc (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

type Anno (AmbiguousFieldOcc GhcTc) Source # 
Instance details

Defined in GHC.Hs.Pat

type Anno (HsRecField' (AmbiguousFieldOcc p) (LocatedA (HsExpr p))) Source # 
Instance details

Defined in GHC.Hs.Pat

isHsKindedTyVar :: HsTyVarBndr flag pass -> Bool Source #

Does this HsTyVarBndr come with an explicit kind annotation?

hsTvbAllKinded :: LHsQTyVars (GhcPass p) -> Bool Source #

Do all type variables in this LHsQTyVars come with kind annotations?

splitLHsInstDeclTy :: LHsSigType GhcRn -> ([Name], Maybe (LHsContext GhcRn), LHsType GhcRn) Source #

Decompose a type class instance type (of the form forall tvs. context => instance_head) into its constituent parts. Note that the [Name]s returned correspond to either:

  • The implicitly bound type variables (if the type lacks an outermost forall), or
  • The explicitly bound type variables (if the type has an outermost forall).

This function is careful not to look through parentheses. See Note [No nested foralls or contexts in instance types] for why this is important.

getLHsInstDeclHead :: LHsSigType (GhcPass p) -> LHsType (GhcPass p) Source #

Decompose a type class instance type (of the form forall tvs. context => instance_head) into the instance_head.

getLHsInstDeclClass_maybe :: Anno (IdGhcP p) ~ SrcSpanAnnN => LHsSigType (GhcPass p) -> Maybe (LocatedN (IdP (GhcPass p))) Source #

Decompose a type class instance type (of the form forall tvs. context => instance_head) into the instance_head and retrieve the underlying class type constructor (if it exists).

splitLHsPatSynTy :: LHsSigType (GhcPass p) -> ([LHsTyVarBndr Specificity (GhcPass (NoGhcTcPass p))], Maybe (LHsContext (GhcPass p)), [LHsTyVarBndr Specificity (GhcPass p)], Maybe (LHsContext (GhcPass p)), LHsType (GhcPass p)) Source #

Decompose a pattern synonym type signature into its constituent parts.

Note that this function looks through parentheses, so it will work on types such as (forall a. ...). The downside to this is that it is not generally possible to take the returned types and reconstruct the original type (parentheses and all) from them.

splitLHsForAllTyInvis :: LHsType (GhcPass pass) -> ((EpAnnForallTy, [LHsTyVarBndr Specificity (GhcPass pass)]), LHsType (GhcPass pass)) Source #

Decompose a type of the form forall tvs. body into its constituent parts. Only splits type variable binders that were quantified invisibly (e.g., forall a., with a dot).

This function is used to split apart certain types, such as instance declaration types, which disallow visible foralls. For instance, if GHC split apart the forall in instance forall a -> Show (Blah a), then that declaration would mistakenly be accepted!

Note that this function looks through parentheses, so it will work on types such as (forall a. ...). The downside to this is that it is not generally possible to take the returned types and reconstruct the original type (parentheses and all) from them. Unlike splitLHsSigmaTyInvis, this function does not look through parentheses, hence the suffix _KP (short for "Keep Parentheses").

splitLHsForAllTyInvis_KP :: LHsType (GhcPass pass) -> (Maybe (EpAnnForallTy, [LHsTyVarBndr Specificity (GhcPass pass)]), LHsType (GhcPass pass)) Source #

Decompose a type of the form forall tvs. body into its constituent parts. Only splits type variable binders that were quantified invisibly (e.g., forall a., with a dot).

This function is used to split apart certain types, such as instance declaration types, which disallow visible foralls. For instance, if GHC split apart the forall in instance forall a -> Show (Blah a), then that declaration would mistakenly be accepted!

Unlike splitLHsForAllTyInvis, this function does not look through parentheses, hence the suffix _KP (short for "Keep Parentheses").

splitLHsQualTy :: LHsType (GhcPass pass) -> (Maybe (LHsContext (GhcPass pass)), LHsType (GhcPass pass)) Source #

Decompose a type of the form context => body into its constituent parts.

Note that this function looks through parentheses, so it will work on types such as (context => ...). The downside to this is that it is not generally possible to take the returned types and reconstruct the original type (parentheses and all) from them.

splitLHsSigmaTyInvis :: LHsType (GhcPass p) -> ([LHsTyVarBndr Specificity (GhcPass p)], Maybe (LHsContext (GhcPass p)), LHsType (GhcPass p)) Source #

Decompose a sigma type (of the form forall tvs. context => body) into its constituent parts. Only splits type variable binders that were quantified invisibly (e.g., forall a., with a dot).

This function is used to split apart certain types, such as instance declaration types, which disallow visible foralls. For instance, if GHC split apart the forall in instance forall a -> Show (Blah a), then that declaration would mistakenly be accepted!

Note that this function looks through parentheses, so it will work on types such as (forall a. ...). The downside to this is that it is not generally possible to take the returned types and reconstruct the original type (parentheses and all) from them.

splitLHsGadtTy :: LHsSigType GhcPs -> (HsOuterSigTyVarBndrs GhcPs, Maybe (LHsContext GhcPs), LHsType GhcPs) Source #

Decompose a GADT type into its constituent parts. Returns (outer_bndrs, mb_ctxt, body), where:

  • outer_bndrs are HsOuterExplicit if the type has explicit, outermost type variable binders. Otherwise, they are HsOuterImplicit.
  • mb_ctxt is Just the context, if it is provided. Otherwise, it is Nothing.
  • body is the body of the type after the optional foralls and context.

This function is careful not to look through parentheses. See Note [GADT abstract syntax] (Wrinkle: No nested foralls or contexts) GHC.Hs.Decls for why this is important.

hsTyGetAppHead_maybe :: Anno (IdGhcP p) ~ SrcSpanAnnN => LHsType (GhcPass p) -> Maybe (LocatedN (IdP (GhcPass p))) Source #

Retrieve the name of the "head" of a nested type application. This is somewhat like GHC.Tc.Gen.HsType.splitHsAppTys, but a little more thorough. The purpose of this function is to examine instance heads, so it doesn't handle *all* cases (like lists, tuples, (~), etc.).

hsSigWcType :: forall p. UnXRec p => LHsSigWcType p -> LHsType p Source #

hsTyKindSig :: LHsType (GhcPass p) -> Maybe (LHsKind (GhcPass p)) Source #

Get the kind signature of a type, ignoring parentheses:

hsTyKindSig `Maybe ` = Nothing hsTyKindSig `Maybe :: Type -> Type ` = Just `Type -> Type` hsTyKindSig `Maybe :: ((Type -> Type))` = Just `Type -> Type`

This is used to extract the result kind of type synonyms with a CUSK:

type S = (F :: res_kind) ^^^^^^^^

setHsTyVarBndrFlag :: flag -> HsTyVarBndr flag' (GhcPass pass) -> HsTyVarBndr flag (GhcPass pass) Source #

Set the attached flag

hsTyVarBndrFlag :: HsTyVarBndr flag (GhcPass pass) -> flag Source #

Return the attached flag

pprHsForAll :: forall p. OutputableBndrId p => HsForAllTelescope (GhcPass p) -> Maybe (LHsContext (GhcPass p)) -> SDoc Source #

Prints a forall; When passed an empty list, prints forall ./forall -> only when -dppr-debug is enabled.

pprHsOuterFamEqnTyVarBndrs :: OutputableBndrId p => HsOuterFamEqnTyVarBndrs (GhcPass p) -> SDoc Source #

Prints the explicit forall in a type family equation if one is written. If there is no explicit forall, nothing is printed.

pprHsOuterSigTyVarBndrs :: OutputableBndrId p => HsOuterSigTyVarBndrs (GhcPass p) -> SDoc Source #

Prints the outermost forall in a type signature if one is written. If there is no outermost forall, nothing is printed.

hsTypeNeedsParens :: PprPrec -> HsType (GhcPass p) -> Bool Source #

hsTypeNeedsParens p t returns True if the type t needs parentheses under precedence p.

parenthesizeHsType :: PprPrec -> LHsType (GhcPass p) -> LHsType (GhcPass p) Source #

parenthesizeHsType p ty checks if hsTypeNeedsParens p ty is true, and if so, surrounds ty with an HsParTy. Otherwise, it simply returns ty.

parenthesizeHsContext :: PprPrec -> LHsContext (GhcPass p) -> LHsContext (GhcPass p) Source #

parenthesizeHsContext p ctxt checks if ctxt is a single constraint c such that hsTypeNeedsParens p c is true, and if so, surrounds c with an HsParTy to form a parenthesized ctxt. Otherwise, it simply returns ctxt unchanged.

Orphan instances

OutputableBndr (AmbiguousFieldOcc (GhcPass p)) Source # 
Instance details

Outputable (AmbiguousFieldOcc (GhcPass p)) Source # 
Instance details

OutputableBndrId p => Outputable (ConDeclField (GhcPass p)) Source # 
Instance details

Methods

ppr :: ConDeclField (GhcPass p) -> SDoc Source #

OutputableBndrId pass => Outputable (HsArrow (GhcPass pass)) Source # 
Instance details

Methods

ppr :: HsArrow (GhcPass pass) -> SDoc Source #

OutputableBndrId p => Outputable (HsType (GhcPass p)) Source # 
Instance details

Methods

ppr :: HsType (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (HsSigType (GhcPass p)) Source # 
Instance details

Methods

ppr :: HsSigType (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (HsPatSigType (GhcPass p)) Source # 
Instance details

Methods

ppr :: HsPatSigType (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (LHsQTyVars (GhcPass p)) Source # 
Instance details

Methods

ppr :: LHsQTyVars (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (HsForAllTelescope (GhcPass p)) Source # 
Instance details

(OutputableBndrId p, OutputableBndrFlag flag p) => Outputable (HsTyVarBndr flag (GhcPass p)) Source # 
Instance details

Methods

ppr :: HsTyVarBndr flag (GhcPass p) -> SDoc Source #

Outputable thing => Outputable (HsWildCardBndrs (GhcPass p) thing) Source # 
Instance details

Methods

ppr :: HsWildCardBndrs (GhcPass p) thing -> SDoc Source #

(OutputableBndrFlag flag p, OutputableBndrFlag flag (NoGhcTcPass p), OutputableBndrId p) => Outputable (HsOuterTyVarBndrs flag (GhcPass p)) Source # 
Instance details

Methods

ppr :: HsOuterTyVarBndrs flag (GhcPass p) -> SDoc Source #

NamedThing (HsTyVarBndr flag GhcRn) Source # 
Instance details