ghc-8.4.3: The GHC API

Safe HaskellNone
LanguageHaskell2010

HsTypes

Synopsis

Documentation

data HsType pass Source #

Haskell Type

Constructors

HsForAllTy

Fields

HsQualTy 

Fields

HsTyVar Promoted (Located (IdP pass))
HsAppsTy [LHsAppType pass]
HsAppTy (LHsType pass) (LHsType pass)
HsFunTy (LHsType pass) (LHsType pass)
HsListTy (LHsType pass)
HsPArrTy (LHsType pass)
HsTupleTy HsTupleSort [LHsType pass]
HsSumTy [LHsType pass]
HsOpTy (LHsType pass) (Located (IdP pass)) (LHsType pass)
HsParTy (LHsType pass)
HsIParamTy (Located HsIPName) (LHsType pass)
(?x :: ty)
HsEqTy (LHsType pass) (LHsType pass)
ty1 ~ ty2
HsKindSig (LHsType pass) (LHsKind pass)
(ty :: kind)
HsSpliceTy (HsSplice pass) (PostTc pass Kind)
HsDocTy (LHsType pass) LHsDocString
HsBangTy HsSrcBang (LHsType pass)
HsRecTy [LConDeclField pass]
HsCoreTy Type
HsExplicitListTy Promoted (PostTc pass Kind) [LHsType pass]
HsExplicitTupleTy [PostTc pass Kind] [LHsType pass]
HsTyLit HsTyLit
HsWildCardTy (HsWildCardInfo pass)
Instances
DataId pass => Data (HsType pass) Source # 
Instance details

Defined in HsTypes

Methods

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

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

toConstr :: HsType pass -> Constr Source #

dataTypeOf :: HsType pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (HsType pass) Source # 
Instance details

Defined in HsTypes

Methods

ppr :: HsType pass -> SDoc Source #

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

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
DataId pass => Data (HsTyVarBndr pass) Source # 
Instance details

Defined in HsTypes

Methods

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

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

toConstr :: HsTyVarBndr pass -> Constr Source #

dataTypeOf :: HsTyVarBndr pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (HsTyVarBndr pass) Source # 
Instance details

Defined in HsTypes

type LHsTyVarBndr pass = Located (HsTyVarBndr pass) Source #

Located Haskell Type Variable Binder

data LHsQTyVars pass Source #

Located Haskell Quantified Type Variables

Constructors

HsQTvs 
Instances
DataId pass => Data (LHsQTyVars pass) Source # 
Instance details

Defined in HsTypes

Methods

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

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

toConstr :: LHsQTyVars pass -> Constr Source #

dataTypeOf :: LHsQTyVars pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (LHsQTyVars pass) Source # 
Instance details

Defined in HsTypes

Methods

ppr :: LHsQTyVars pass -> SDoc Source #

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

data HsImplicitBndrs pass thing Source #

Haskell Implicit Binders

Constructors

HsIB 

Fields

Instances
(DataId pass, Data thing) => Data (HsImplicitBndrs pass thing) Source # 
Instance details

Defined in HsTypes

Methods

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

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

toConstr :: HsImplicitBndrs pass thing -> Constr Source #

dataTypeOf :: HsImplicitBndrs pass thing -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable thing => Outputable (HsImplicitBndrs pass thing) Source # 
Instance details

Defined in HsTypes

Methods

ppr :: HsImplicitBndrs pass thing -> SDoc Source #

pprPrec :: Rational -> HsImplicitBndrs pass thing -> SDoc Source #

data HsWildCardBndrs pass thing Source #

Haskell Wildcard Binders

Constructors

HsWC 

Fields

Instances
(DataId pass, Data thing) => Data (HsWildCardBndrs pass thing) Source # 
Instance details

Defined in HsTypes

Methods

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

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

toConstr :: HsWildCardBndrs pass thing -> Constr Source #

dataTypeOf :: HsWildCardBndrs pass thing -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable thing => Outputable (HsWildCardBndrs pass thing) Source # 
Instance details

Defined in HsTypes

Methods

ppr :: HsWildCardBndrs pass thing -> SDoc Source #

pprPrec :: Rational -> HsWildCardBndrs pass thing -> SDoc Source #

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 HsTypes

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

data Promoted Source #

Promoted data types.

Constructors

Promoted 
NotPromoted 
Instances
Eq Promoted Source # 
Instance details

Defined in HsTypes

Data Promoted Source # 
Instance details

Defined in HsTypes

Methods

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

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

toConstr :: Promoted -> Constr Source #

dataTypeOf :: Promoted -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show Promoted Source # 
Instance details

Defined in HsTypes

type HsContext pass = [LHsType pass] Source #

Haskell Context

type LHsContext pass Source #

Arguments

 = Located (HsContext pass)

AnnKeywordId : AnnUnit

Located Haskell Context

data HsTyLit Source #

Haskell Type Literal

Instances
Data HsTyLit Source # 
Instance details

Defined in HsTypes

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 :: (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 HsTypes

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 HsTypes

Data HsIPName Source # 
Instance details

Defined in HsTypes

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

OutputableBndr HsIPName Source # 
Instance details

Defined in HsTypes

Outputable HsIPName Source # 
Instance details

Defined in HsTypes

data HsAppType pass Source #

Haskell Application Type

Constructors

HsAppInfix (Located (IdP pass)) 
HsAppPrefix (LHsType pass) 
Instances
DataId pass => Data (HsAppType pass) Source # 
Instance details

Defined in HsTypes

Methods

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

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

toConstr :: HsAppType pass -> Constr Source #

dataTypeOf :: HsAppType pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (HsAppType pass) Source # 
Instance details

Defined in HsTypes

Methods

ppr :: HsAppType pass -> SDoc Source #

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

type LHsAppType pass Source #

Located Haskell Application Type

type LBangType pass = Located (BangType pass) Source #

Located Bang Type

type BangType pass = HsType pass Source #

Bang Type

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

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

Outputable SrcUnpackedness Source # 
Instance details

Defined in DataCon

Binary SrcUnpackedness Source # 
Instance details

Defined in DataCon

data ConDeclField pass Source #

Constructor Declaration Field

Constructors

ConDeclField

Fields

Instances
DataId pass => Data (ConDeclField pass) Source # 
Instance details

Defined in HsTypes

Methods

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

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

toConstr :: ConDeclField pass -> Constr Source #

dataTypeOf :: ConDeclField pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (ConDeclField pass) Source # 
Instance details

Defined in HsTypes

type LConDeclField pass Source #

Arguments

 = Located (ConDeclField pass)

May have AnnKeywordId : AnnComma when in a list

Located Constructor Declaration Field

updateGadtResult Source #

Arguments

:: Monad m 
=> (SDoc -> m ()) 
-> SDoc 
-> HsConDetails (LHsType GhcRn) (Located [LConDeclField GhcRn])

Original details

-> LHsType GhcRn

Original result type

-> m (HsConDetails (LHsType GhcRn) (Located [LConDeclField GhcRn]), LHsType GhcRn) 

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 HsTypes

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

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

toConstr :: HsConDetails arg rec -> Constr Source #

dataTypeOf :: HsConDetails arg rec -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

Defined in HsTypes

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

Instances
Eq (PostRn pass (IdP pass)) => Eq (FieldOcc pass) Source # 
Instance details

Defined in HsTypes

Methods

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

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

DataId pass => Data (FieldOcc pass) Source # 
Instance details

Defined in HsTypes

Methods

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

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

toConstr :: FieldOcc pass -> Constr Source #

dataTypeOf :: FieldOcc pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord (PostRn pass (IdP pass)) => Ord (FieldOcc pass) Source # 
Instance details

Defined in HsTypes

Methods

compare :: FieldOcc pass -> FieldOcc pass -> Ordering #

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

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

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

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

max :: FieldOcc pass -> FieldOcc pass -> FieldOcc pass #

min :: FieldOcc pass -> FieldOcc pass -> FieldOcc pass #

Outputable (FieldOcc pass) Source # 
Instance details

Defined in HsTypes

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 HsPat and Note [Disambiguating record fields] in TcExpr. See Note [Located RdrNames] in HsExpr

Constructors

Unambiguous (Located RdrName) (PostRn pass (IdP pass)) 
Ambiguous (Located RdrName) (PostTc pass (IdP pass)) 
Instances
DataId pass => Data (AmbiguousFieldOcc pass) Source # 
Instance details

Defined in HsTypes

Methods

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

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

toConstr :: AmbiguousFieldOcc pass -> Constr Source #

dataTypeOf :: AmbiguousFieldOcc pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

OutputableBndr (AmbiguousFieldOcc pass) Source # 
Instance details

Defined in HsTypes

Outputable (AmbiguousFieldOcc pass) Source # 
Instance details

Defined in HsTypes

newtype HsWildCardInfo pass Source #

Constructors

AnonWildCard (PostRn pass (Located Name)) 
Instances
DataId pass => Data (HsWildCardInfo pass) Source # 
Instance details

Defined in HsTypes

Methods

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

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

toConstr :: HsWildCardInfo pass -> Constr Source #

dataTypeOf :: HsWildCardInfo pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable (HsWildCardInfo pass) Source # 
Instance details

Defined in HsTypes

hsImplicitBody :: HsImplicitBndrs pass thing -> thing Source #

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?

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

splitHsAppsTy :: [LHsAppType pass] -> ([[LHsType pass]], [Located (IdP pass)]) Source #

Splits a [HsAppType pass] (the payload of an HsAppsTy) into regions of prefix types (normal types) and infix operators. If splitHsAppsTy tys = (non_syms, syms), then tys starts with the first element of non_syms followed by the first element of syms followed by the next element of non_syms, etc. It is guaranteed that the non_syms list has one more element than the syms list.

getAppsTyHead_maybe :: [LHsAppType pass] -> Maybe (LHsType pass, [LHsType pass], LexicalFixity) Source #

Retrieves the head of an HsAppsTy, if this can be done unambiguously, without consulting fixities.

mkHsOpTy :: LHsType pass -> Located (IdP pass) -> LHsType pass -> HsType pass Source #

mkHsAppTy :: LHsType pass -> LHsType pass -> LHsType pass Source #

mkHsAppTys :: LHsType pass -> [LHsType pass] -> LHsType pass Source #

hsLTyVarBndrToType :: LHsTyVarBndr pass -> LHsType pass Source #

Convert a LHsTyVarBndr to an equivalent LHsType.

hsLTyVarBndrsToTypes :: LHsQTyVars pass -> [LHsType pass] Source #

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

pprHsForAllExtra :: (SourceTextX pass, OutputableBndrId pass) => Maybe SrcSpan -> [LHsTyVarBndr pass] -> LHsContext pass -> 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.

isCompoundHsType :: LHsType pass -> Bool Source #

Return True for compound types that will need parentheses when used in an argument position.

parenthesizeCompoundHsType :: LHsType pass -> LHsType pass Source #

parenthesizeCompoundHsType ty checks if isCompoundHsType ty is true, and if so, surrounds ty with an HsParTy. Otherwise, it simply returns ty.