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

Language.Haskell.Syntax.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 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) Source #

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

toConstr :: HsScaled GhcPs thing -> Constr Source #

dataTypeOf :: HsScaled GhcPs thing -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: HsScaled GhcRn thing -> Constr Source #

dataTypeOf :: HsScaled GhcRn thing -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: HsScaled GhcTc thing -> Constr Source #

dataTypeOf :: HsScaled GhcTc thing -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

data HsArrow pass Source #

Denotes the type of arrows in the surface language

Constructors

HsUnrestrictedArrow !(LHsUniToken "->" "\8594" pass)

a -> b or a → b

HsLinearArrow !(HsLinearArrowTokens pass)

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

HsExplicitMult !(LHsToken "%" pass) !(LHsType pass) !(LHsUniToken "->" "\8594" 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 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) Source #

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

toConstr :: HsArrow GhcPs -> Constr Source #

dataTypeOf :: HsArrow GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: HsArrow GhcRn -> Constr Source #

dataTypeOf :: HsArrow GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: HsArrow GhcTc -> Constr Source #

dataTypeOf :: HsArrow GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Type

Methods

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

data HsLinearArrowTokens pass Source #

Constructors

HsPct1 !(LHsToken "%1" pass) !(LHsUniToken "->" "\8594" pass) 
HsLolly !(LHsToken "\8888" pass) 

Instances

Instances details
Data (HsLinearArrowTokens 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) -> HsLinearArrowTokens GhcPs -> c (HsLinearArrowTokens GhcPs) Source #

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

toConstr :: HsLinearArrowTokens GhcPs -> Constr Source #

dataTypeOf :: HsLinearArrowTokens GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (HsLinearArrowTokens 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) -> HsLinearArrowTokens GhcRn -> c (HsLinearArrowTokens GhcRn) Source #

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

toConstr :: HsLinearArrowTokens GhcRn -> Constr Source #

dataTypeOf :: HsLinearArrowTokens GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (HsLinearArrowTokens 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) -> HsLinearArrowTokens GhcTc -> c (HsLinearArrowTokens GhcTc) Source #

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

toConstr :: HsLinearArrowTokens GhcTc -> Constr Source #

dataTypeOf :: HsLinearArrowTokens GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) PromotionFlag (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) (LHsDoc pass)
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 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) Source #

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

toConstr :: HsType GhcPs -> Constr Source #

dataTypeOf :: HsType GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: HsType GhcRn -> Constr Source #

dataTypeOf :: HsType GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: HsType GhcTc -> Constr Source #

dataTypeOf :: HsType GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

DisambTD (HsType GhcPs) Source # 
Instance details

Defined in GHC.Parser.PostProcess

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

Defined in GHC.Hs.Type

Methods

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

type Anno (BangType (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 (HsType (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

type Anno [LocatedA (HsType (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 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) Source #

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

toConstr :: HsForAllTelescope GhcPs -> Constr Source #

dataTypeOf :: HsForAllTelescope GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: HsForAllTelescope GhcRn -> Constr Source #

dataTypeOf :: HsForAllTelescope GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: HsForAllTelescope GhcTc -> Constr Source #

dataTypeOf :: HsForAllTelescope GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Type

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 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) Source #

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

toConstr :: HsTyVarBndr flag GhcPs -> Constr Source #

dataTypeOf :: HsTyVarBndr flag GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: HsTyVarBndr flag GhcRn -> Constr Source #

dataTypeOf :: HsTyVarBndr flag GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: HsTyVarBndr flag GhcTc -> Constr Source #

dataTypeOf :: HsTyVarBndr flag GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

NamedThing (HsTyVarBndr flag GhcRn) Source # 
Instance details

Defined in GHC.Hs.Type

(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 #

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

Defined in GHC.Hs.Type

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

Defined in GHC.Hs.Type

type Anno (HsTyVarBndr _flag GhcRn) Source # 
Instance details

Defined in GHC.Hs.Type

type Anno (HsTyVarBndr _flag GhcTc) Source # 
Instance details

Defined in GHC.Hs.Type

type 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 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) Source #

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

toConstr :: LHsQTyVars GhcPs -> Constr Source #

dataTypeOf :: LHsQTyVars GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: LHsQTyVars GhcRn -> Constr Source #

dataTypeOf :: LHsQTyVars GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: LHsQTyVars GhcTc -> Constr Source #

dataTypeOf :: LHsQTyVars GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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 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) Source #

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

toConstr :: HsOuterTyVarBndrs flag GhcPs -> Constr Source #

dataTypeOf :: HsOuterTyVarBndrs flag GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: HsOuterTyVarBndrs flag GhcRn -> Constr Source #

dataTypeOf :: HsOuterTyVarBndrs flag GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: HsOuterTyVarBndrs flag GhcTc -> Constr Source #

dataTypeOf :: HsOuterTyVarBndrs flag GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(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 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) Source #

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

toConstr :: HsWildCardBndrs GhcPs thing -> Constr Source #

dataTypeOf :: HsWildCardBndrs GhcPs thing -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: HsWildCardBndrs GhcRn thing -> Constr Source #

dataTypeOf :: HsWildCardBndrs GhcRn thing -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: HsWildCardBndrs GhcTc thing -> Constr Source #

dataTypeOf :: HsWildCardBndrs GhcTc thing -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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 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) Source #

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

toConstr :: HsPatSigType GhcPs -> Constr Source #

dataTypeOf :: HsPatSigType GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: HsPatSigType GhcRn -> Constr Source #

dataTypeOf :: HsPatSigType GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: HsPatSigType GhcTc -> Constr Source #

dataTypeOf :: HsPatSigType GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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 Source #

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

toConstr :: HsPSRn -> Constr Source #

dataTypeOf :: HsPSRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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 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) Source #

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

toConstr :: HsSigType GhcPs -> Constr Source #

dataTypeOf :: HsSigType GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: HsSigType GhcRn -> Constr Source #

dataTypeOf :: HsSigType GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: HsSigType GhcTc -> Constr Source #

dataTypeOf :: HsSigType GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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 Source #

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

toConstr :: HsTupleSort -> Constr Source #

dataTypeOf :: HsTupleSort -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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 Source #

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

toConstr :: HsTyLit -> Constr Source #

dataTypeOf :: HsTyLit -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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
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 Source #

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

toConstr :: HsIPName -> Constr Source #

dataTypeOf :: HsIPName -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable HsIPName Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: HsIPName -> SDoc Source #

OutputableBndr HsIPName Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Eq HsIPName Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

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) Source #

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

toConstr :: HsArg a b -> Constr Source #

dataTypeOf :: HsArg a b -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

This instance is meant for debug-printing purposes. If you wish to pretty-print an application of HsArgs, use pprHsArgsApp instead.

Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: HsArg tm ty -> SDoc Source #

pprHsArgsApp :: (OutputableBndr id, Outputable tm, Outputable ty) => id -> LexicalFixity -> [HsArg tm ty] -> SDoc Source #

pprHsArgsApp id fixity args pretty-prints an application of id to args, using the fixity to tell whether id should be printed prefix or infix. Examples:

pprHsArgsApp T Prefix [HsTypeArg Bool, HsValArg Int]                        = T @Bool Int
pprHsArgsApp T Prefix [HsTypeArg Bool, HsArgPar, HsValArg Int]              = (T @Bool) Int
pprHsArgsApp (++) Infix [HsValArg Char, HsValArg Double]                    = Char ++ Double
pprHsArgsApp (++) Infix [HsValArg Char, HsValArg Double, HsVarArg Ordering] = (Char ++ Double) Ordering

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 Source #

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

toConstr :: HsSrcBang -> Constr Source #

dataTypeOf :: HsSrcBang -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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 Source #

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

toConstr :: HsImplBang -> Constr Source #

dataTypeOf :: HsImplBang -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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
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 Source #

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

toConstr :: SrcStrictness -> Constr Source #

dataTypeOf :: SrcStrictness -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Binary SrcStrictness Source # 
Instance details

Defined in GHC.Core.DataCon

Outputable SrcStrictness Source # 
Instance details

Defined in GHC.Core.DataCon

Eq SrcStrictness Source # 
Instance details

Defined in GHC.Core.DataCon

data SrcUnpackedness Source #

Source Unpackedness

What unpackedness the user requested

Constructors

SrcUnpack

{-# UNPACK #-} specified

SrcNoUnpack

{-# NOUNPACK #-} specified

NoSrcUnpack

no unpack pragma

Instances

Instances details
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 Source #

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

toConstr :: SrcUnpackedness -> Constr Source #

dataTypeOf :: SrcUnpackedness -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Binary SrcUnpackedness Source # 
Instance details

Defined in GHC.Core.DataCon

Outputable SrcUnpackedness Source # 
Instance details

Defined in GHC.Core.DataCon

Eq 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 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) Source #

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

toConstr :: ConDeclField GhcPs -> Constr Source #

dataTypeOf :: ConDeclField GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: ConDeclField GhcRn -> Constr Source #

dataTypeOf :: ConDeclField GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: ConDeclField GhcTc -> Constr Source #

dataTypeOf :: ConDeclField GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Type

Methods

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

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

Defined in GHC.Hs.Type

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

Defined in GHC.Hs.Decls

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 rec, Data arg) => 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) Source #

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

toConstr :: HsConDetails tyarg arg rec -> Constr Source #

dataTypeOf :: HsConDetails tyarg arg rec -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(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 a 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 we use the extension field to store the selector function.

Constructors

FieldOcc 

Fields

XFieldOcc !(XXFieldOcc pass) 

Instances

Instances details
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) Source #

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

toConstr :: FieldOcc GhcPs -> Constr Source #

dataTypeOf :: FieldOcc GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: FieldOcc GhcRn -> Constr Source #

dataTypeOf :: FieldOcc GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: FieldOcc GhcTc -> Constr Source #

dataTypeOf :: FieldOcc GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable (XRec pass RdrName) => Outputable (FieldOcc pass) Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

ppr :: FieldOcc pass -> SDoc Source #

(UnXRec pass, OutputableBndr (XRec pass RdrName)) => OutputableBndr (FieldOcc pass) Source # 
Instance details

Defined in Language.Haskell.Syntax.Type

(Eq (XRec pass RdrName), 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 #

(UnXRec pass, OutputableBndr (XRec pass RdrName)) => 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 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. See Note [Located RdrNames] in GHC.Hs.Expr.

Instances

Instances details
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) Source #

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

toConstr :: AmbiguousFieldOcc GhcPs -> Constr Source #

dataTypeOf :: AmbiguousFieldOcc GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: AmbiguousFieldOcc GhcRn -> Constr Source #

dataTypeOf :: AmbiguousFieldOcc GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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) Source #

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

toConstr :: AmbiguousFieldOcc GhcTc -> Constr Source #

dataTypeOf :: AmbiguousFieldOcc GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Type

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

Defined in GHC.Hs.Type

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

Defined in GHC.Hs.Type

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

Defined in GHC.Hs.Type

type LAmbiguousFieldOcc pass = XRec pass (AmbiguousFieldOcc pass) Source #

Located Ambiguous Field Occurence

isHsKindedTyVar :: HsTyVarBndr flag pass -> Bool Source #

Does this HsTyVarBndr come with an explicit kind annotation?