ghc-lib-parser-0.20200102: The GHC API, decoupled from GHC versions

Safe HaskellNone
LanguageHaskell2010

GHC.Hs.Types

Synopsis

Documentation

data HsType pass Source #

Haskell Type

Constructors

HsForAllTy
HsQualTy 

Fields

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

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsType GhcTc -> Constr #

dataTypeOf :: HsType GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsType GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsType GhcRn -> Constr #

dataTypeOf :: HsType GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsType GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsType GhcPs -> Constr #

dataTypeOf :: HsType GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Types

Data (HsArg (LHsType GhcTc) (LHsKind 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) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> c (HsArg (LHsType GhcTc) (LHsKind GhcTc)) #

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

toConstr :: HsArg (LHsType GhcTc) (LHsKind GhcTc) -> Constr #

dataTypeOf :: HsArg (LHsType GhcTc) (LHsKind GhcTc) -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> r #

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> m (HsArg (LHsType GhcTc) (LHsKind GhcTc)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> m (HsArg (LHsType GhcTc) (LHsKind GhcTc)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> m (HsArg (LHsType GhcTc) (LHsKind GhcTc)) #

Data (HsArg (LHsType GhcRn) (LHsKind 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) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> c (HsArg (LHsType GhcRn) (LHsKind GhcRn)) #

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

toConstr :: HsArg (LHsType GhcRn) (LHsKind GhcRn) -> Constr #

dataTypeOf :: HsArg (LHsType GhcRn) (LHsKind GhcRn) -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> r #

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> m (HsArg (LHsType GhcRn) (LHsKind GhcRn)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> m (HsArg (LHsType GhcRn) (LHsKind GhcRn)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> m (HsArg (LHsType GhcRn) (LHsKind GhcRn)) #

Data (HsArg (LHsType GhcPs) (LHsKind 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) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> c (HsArg (LHsType GhcPs) (LHsKind GhcPs)) #

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

toConstr :: HsArg (LHsType GhcPs) (LHsKind GhcPs) -> Constr #

dataTypeOf :: HsArg (LHsType GhcPs) (LHsKind GhcPs) -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> r #

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> m (HsArg (LHsType GhcPs) (LHsKind GhcPs)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> m (HsArg (LHsType GhcPs) (LHsKind GhcPs)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> m (HsArg (LHsType GhcPs) (LHsKind GhcPs)) #

data NewHsTypeX Source #

Constructors

NHsCoreTy Type 
Instances
Data NewHsTypeX Source #
Instance details

Defined in GHC.Hs.Types

Methods

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

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

toConstr :: NewHsTypeX -> Constr #

dataTypeOf :: NewHsTypeX -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable NewHsTypeX Source # 
Instance details

Defined in GHC.Hs.Types

type LHsType pass Source #

Arguments

 = Located (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

 = Located (HsKind pass)

AnnKeywordId : AnnDcolon

Located Haskell Kind

data HsTyVarBndr pass Source #

Haskell Type Variable Binder

Instances
Data (HsTyVarBndr 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 GhcTc -> c (HsTyVarBndr GhcTc) #

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

toConstr :: HsTyVarBndr GhcTc -> Constr #

dataTypeOf :: HsTyVarBndr GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

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

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

toConstr :: HsTyVarBndr GhcRn -> Constr #

dataTypeOf :: HsTyVarBndr GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsTyVarBndr 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 GhcPs -> c (HsTyVarBndr GhcPs) #

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

toConstr :: HsTyVarBndr GhcPs -> Constr #

dataTypeOf :: HsTyVarBndr GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Types

NamedThing (HsTyVarBndr GhcRn) Source # 
Instance details

Defined in GHC.Hs.Types

type LHsTyVarBndr pass = Located (HsTyVarBndr pass) Source #

Located Haskell Type Variable Binder

data ForallVisFlag Source #

Is a forall invisible (e.g., forall a b. {...}, with a dot) or visible (e.g., forall a b -> {...}, with an arrow)?

Constructors

ForallVis

A visible forall (with an arrow)

ForallInvis

An invisible forall (with a dot)

Instances
Eq ForallVisFlag Source # 
Instance details

Defined in Var

Data ForallVisFlag Source # 
Instance details

Defined in Var

Methods

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

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

toConstr :: ForallVisFlag -> Constr #

dataTypeOf :: ForallVisFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ForallVisFlag Source # 
Instance details

Defined in Var

Outputable ForallVisFlag Source # 
Instance details

Defined in Var

data LHsQTyVars pass Source #

Located Haskell Quantified Type Variables

Constructors

HsQTvs 

Fields

XLHsQTyVars (XXLHsQTyVars pass) 
Instances
Data (LHsQTyVars GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: LHsQTyVars GhcTc -> Constr #

dataTypeOf :: LHsQTyVars GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (LHsQTyVars GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: LHsQTyVars GhcRn -> Constr #

dataTypeOf :: LHsQTyVars GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (LHsQTyVars GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: LHsQTyVars GhcPs -> Constr #

dataTypeOf :: LHsQTyVars GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Types

data HsImplicitBndrs pass thing Source #

Haskell Implicit Binders

Constructors

HsIB 

Fields

XHsImplicitBndrs (XXHsImplicitBndrs pass thing) 
Instances
Data thing => Data (HsImplicitBndrs 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) -> HsImplicitBndrs GhcTc thing -> c (HsImplicitBndrs GhcTc thing) #

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

toConstr :: HsImplicitBndrs GhcTc thing -> Constr #

dataTypeOf :: HsImplicitBndrs GhcTc thing -> DataType #

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

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

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

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

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

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

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

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

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

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

Data thing => Data (HsImplicitBndrs 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) -> HsImplicitBndrs GhcRn thing -> c (HsImplicitBndrs GhcRn thing) #

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

toConstr :: HsImplicitBndrs GhcRn thing -> Constr #

dataTypeOf :: HsImplicitBndrs GhcRn thing -> DataType #

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

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

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

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

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

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

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

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

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

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

Data thing => Data (HsImplicitBndrs 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) -> HsImplicitBndrs GhcPs thing -> c (HsImplicitBndrs GhcPs thing) #

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

toConstr :: HsImplicitBndrs GhcPs thing -> Constr #

dataTypeOf :: HsImplicitBndrs GhcPs thing -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Types

data HsWildCardBndrs pass thing Source #

Haskell Wildcard Binders

Constructors

HsWC 

Fields

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

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsWildCardBndrs GhcTc thing -> Constr #

dataTypeOf :: HsWildCardBndrs GhcTc thing -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsWildCardBndrs GhcRn thing -> Constr #

dataTypeOf :: HsWildCardBndrs GhcRn thing -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsWildCardBndrs GhcPs thing -> Constr #

dataTypeOf :: HsWildCardBndrs GhcPs thing -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Types

type LHsSigType pass = HsImplicitBndrs pass (LHsType 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
Data HsTupleSort Source # 
Instance details

Defined in GHC.Hs.Types

Methods

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

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

toConstr :: HsTupleSort -> Constr #

dataTypeOf :: HsTupleSort -> DataType #

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

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

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

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

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

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

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

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

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

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

type HsContext pass = [LHsType pass] Source #

Haskell Context

type LHsContext pass Source #

Arguments

 = Located (HsContext pass)

AnnKeywordId : AnnUnit For details on above see note [Api annotations] in ApiAnnotation

Located Haskell Context

data HsTyLit Source #

Haskell Type Literal

Instances
Data HsTyLit Source # 
Instance details

Defined in GHC.Hs.Types

Methods

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

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

toConstr :: HsTyLit -> Constr #

dataTypeOf :: HsTyLit -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable HsTyLit Source # 
Instance details

Defined in GHC.Hs.Types

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
Eq HsIPName Source # 
Instance details

Defined in GHC.Hs.Types

Data HsIPName Source # 
Instance details

Defined in GHC.Hs.Types

Methods

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

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

toConstr :: HsIPName -> Constr #

dataTypeOf :: HsIPName -> DataType #

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

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

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

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

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

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

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

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

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

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

OutputableBndr HsIPName Source # 
Instance details

Defined in GHC.Hs.Types

Outputable HsIPName Source # 
Instance details

Defined in GHC.Hs.Types

data HsArg tm ty Source #

Constructors

HsValArg tm 
HsTypeArg SrcSpan ty 
HsArgPar SrcSpan 
Instances
Data (HsArg (LHsType GhcTc) (LHsKind 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) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> c (HsArg (LHsType GhcTc) (LHsKind GhcTc)) #

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

toConstr :: HsArg (LHsType GhcTc) (LHsKind GhcTc) -> Constr #

dataTypeOf :: HsArg (LHsType GhcTc) (LHsKind GhcTc) -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> r #

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> m (HsArg (LHsType GhcTc) (LHsKind GhcTc)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> m (HsArg (LHsType GhcTc) (LHsKind GhcTc)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> m (HsArg (LHsType GhcTc) (LHsKind GhcTc)) #

Data (HsArg (LHsType GhcRn) (LHsKind 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) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> c (HsArg (LHsType GhcRn) (LHsKind GhcRn)) #

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

toConstr :: HsArg (LHsType GhcRn) (LHsKind GhcRn) -> Constr #

dataTypeOf :: HsArg (LHsType GhcRn) (LHsKind GhcRn) -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> r #

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> m (HsArg (LHsType GhcRn) (LHsKind GhcRn)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> m (HsArg (LHsType GhcRn) (LHsKind GhcRn)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> m (HsArg (LHsType GhcRn) (LHsKind GhcRn)) #

Data (HsArg (LHsType GhcPs) (LHsKind 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) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> c (HsArg (LHsType GhcPs) (LHsKind GhcPs)) #

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

toConstr :: HsArg (LHsType GhcPs) (LHsKind GhcPs) -> Constr #

dataTypeOf :: HsArg (LHsType GhcPs) (LHsKind GhcPs) -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> r #

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> m (HsArg (LHsType GhcPs) (LHsKind GhcPs)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> m (HsArg (LHsType GhcPs) (LHsKind GhcPs)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> m (HsArg (LHsType GhcPs) (LHsKind GhcPs)) #

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

Defined in GHC.Hs.Types

Methods

ppr :: HsArg tm ty -> SDoc Source #

pprPrec :: Rational -> HsArg tm ty -> SDoc Source #

type LBangType pass = Located (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
Data HsSrcBang Source # 
Instance details

Defined in DataCon

Methods

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

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

toConstr :: HsSrcBang -> Constr #

dataTypeOf :: HsSrcBang -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable HsSrcBang Source # 
Instance details

Defined in DataCon

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
Data HsImplBang Source # 
Instance details

Defined in DataCon

Methods

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

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

toConstr :: HsImplBang -> Constr #

dataTypeOf :: HsImplBang -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable HsImplBang Source # 
Instance details

Defined in DataCon

data SrcStrictness Source #

Source Strictness

What strictness annotation the user wrote

Constructors

SrcLazy

Lazy, ie '~'

SrcStrict

Strict, ie !

NoSrcStrict

no strictness annotation

Instances
Eq SrcStrictness Source # 
Instance details

Defined in DataCon

Data SrcStrictness Source # 
Instance details

Defined in DataCon

Methods

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

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

toConstr :: SrcStrictness -> Constr #

dataTypeOf :: SrcStrictness -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable SrcStrictness Source # 
Instance details

Defined in DataCon

Binary SrcStrictness Source # 
Instance details

Defined in DataCon

data SrcUnpackedness Source #

Source Unpackedness

What unpackedness the user requested

Constructors

SrcUnpack

{--} specified

SrcNoUnpack

{--} specified

NoSrcUnpack

no unpack pragma

Instances
Eq SrcUnpackedness Source # 
Instance details

Defined in DataCon

Data SrcUnpackedness Source # 
Instance details

Defined in DataCon

Methods

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

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

toConstr :: SrcUnpackedness -> Constr #

dataTypeOf :: SrcUnpackedness -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable SrcUnpackedness Source # 
Instance details

Defined in DataCon

Binary SrcUnpackedness Source # 
Instance details

Defined in DataCon

data ConDeclField pass Source #

Constructor Declaration Field

Instances
Data (ConDeclField GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: ConDeclField GhcTc -> Constr #

dataTypeOf :: ConDeclField GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (ConDeclField GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: ConDeclField GhcRn -> Constr #

dataTypeOf :: ConDeclField GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (ConDeclField GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: ConDeclField GhcPs -> Constr #

dataTypeOf :: ConDeclField GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Types

type LConDeclField pass Source #

Arguments

 = Located (ConDeclField pass)

May have AnnKeywordId : AnnComma when in a list

Located Constructor Declaration Field

data HsConDetails arg rec Source #

Haskell Constructor Details

Constructors

PrefixCon [arg] 
RecCon rec 
InfixCon arg arg 
Instances
(Data arg, Data rec) => Data (HsConDetails arg rec) Source # 
Instance details

Defined in GHC.Hs.Types

Methods

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

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

toConstr :: HsConDetails arg rec -> Constr #

dataTypeOf :: HsConDetails arg rec -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Types

Methods

ppr :: HsConDetails arg rec -> SDoc Source #

pprPrec :: Rational -> HsConDetails arg rec -> SDoc Source #

data FieldOcc pass Source #

Field Occurrence

Represents an *occurrence* of an unambiguous field. We store both the RdrName the user originally wrote, and after the renamer, the selector function.

Constructors

FieldOcc 

Fields

XFieldOcc (XXFieldOcc pass) 
Instances
Eq (XCFieldOcc (GhcPass p)) => Eq (FieldOcc (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Types

Methods

(==) :: FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) -> Bool #

(/=) :: FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) -> Bool #

Data (FieldOcc GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: FieldOcc GhcTc -> Constr #

dataTypeOf :: FieldOcc GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (FieldOcc GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: FieldOcc GhcRn -> Constr #

dataTypeOf :: FieldOcc GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (FieldOcc GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: FieldOcc GhcPs -> Constr #

dataTypeOf :: FieldOcc GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord (XCFieldOcc (GhcPass p)) => Ord (FieldOcc (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Types

Outputable (FieldOcc pass) Source # 
Instance details

Defined in GHC.Hs.Types

Methods

ppr :: FieldOcc pass -> SDoc Source #

pprPrec :: Rational -> FieldOcc pass -> SDoc Source #

type LFieldOcc pass = Located (FieldOcc pass) Source #

Located Field Occurrence

data AmbiguousFieldOcc pass Source #

Ambiguous Field Occurrence

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

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

Instances
Data (AmbiguousFieldOcc GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: AmbiguousFieldOcc GhcTc -> Constr #

dataTypeOf :: AmbiguousFieldOcc GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (AmbiguousFieldOcc GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: AmbiguousFieldOcc GhcRn -> Constr #

dataTypeOf :: AmbiguousFieldOcc GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (AmbiguousFieldOcc GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: AmbiguousFieldOcc GhcPs -> Constr #

dataTypeOf :: AmbiguousFieldOcc GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Hs.Types

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

Defined in GHC.Hs.Types

isHsKindedTyVar :: HsTyVarBndr pass -> Bool Source #

Does this HsTyVarBndr come with an explicit kind annotation?

hsTvbAllKinded :: LHsQTyVars pass -> Bool Source #

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

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

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

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

splitLHsPatSynTy :: LHsType pass -> ([LHsTyVarBndr pass], LHsContext pass, [LHsTyVarBndr pass], LHsContext pass, LHsType pass) Source #

Decompose a pattern synonym type signature into its constituent parts.

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

splitLHsForAllTy :: LHsType pass -> ([LHsTyVarBndr pass], LHsType pass) Source #

Decompose a type of the form forall tvs. body) into its constituent parts.

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

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

Like splitLHsForAllTy, but only splits type variable binders that were quantified invisibly (e.g., forall a., with a dot).

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

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

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

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

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

splitLHsSigmaTy :: LHsType pass -> ([LHsTyVarBndr pass], LHsContext pass, LHsType pass) Source #

Decompose a sigma type (of the form forall tvs. context => body) into its constituent parts.

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

splitLHsSigmaTyInvis :: LHsType pass -> ([LHsTyVarBndr pass], LHsContext pass, LHsType pass) Source #

Like splitLHsSigmaTy, but only splits type variable binders that were quantified invisibly (e.g., forall a., with a dot).

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

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

hsLTyVarBndrToType :: LHsTyVarBndr (GhcPass p) -> LHsType (GhcPass p) Source #

Convert a LHsTyVarBndr to an equivalent LHsType.

hsLTyVarBndrsToTypes :: LHsQTyVars (GhcPass p) -> [LHsType (GhcPass p)] Source #

Convert a LHsTyVarBndrs to a list of types. Works on *type* variable only, no kind vars.

hsTyKindSig :: LHsType pass -> Maybe (LHsKind pass) Source #

Get the kind signature of a type, ignoring parentheses:

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

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

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

pprHsForAll :: OutputableBndrId p => ForallVisFlag -> [LHsTyVarBndr (GhcPass p)] -> LHsContext (GhcPass p) -> SDoc Source #

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

pprHsForAllExtra :: OutputableBndrId p => Maybe SrcSpan -> ForallVisFlag -> [LHsTyVarBndr (GhcPass p)] -> LHsContext (GhcPass p) -> SDoc Source #

Version of pprHsForAll that can also print an extra-constraints wildcard, e.g. _ => a -> Bool or (Show a, _) => a -> String. This underscore will be printed when the 'Maybe SrcSpan' argument is a Just containing the location of the extra-constraints wildcard. A special function for this is needed, as the extra-constraints wildcard is removed from the actual context and type, and stored in a separate field, thus just printing the type will not print the extra-constraints wildcard.

pprHsExplicitForAll :: OutputableBndrId p => ForallVisFlag -> Maybe [LHsTyVarBndr (GhcPass p)] -> SDoc Source #

Version of pprHsForAll or pprHsForAllExtra that will always print forall. when passed Just []. Prints nothing if passed Nothing

hsTypeNeedsParens :: PprPrec -> HsType pass -> Bool Source #

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

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

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

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

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