ghc-7.10.3: The GHC API

Safe HaskellNone
LanguageHaskell2010

HsTypes

Synopsis

Documentation

data HsType name Source

Constructors

HsForAllTy HsExplicitFlag (Maybe SrcSpan) (LHsTyVarBndrs name) (LHsContext name) (LHsType name)
HsTyVar name
HsAppTy (LHsType name) (LHsType name)
HsFunTy (LHsType name) (LHsType name)
HsListTy (LHsType name)
HsPArrTy (LHsType name)
HsTupleTy HsTupleSort [LHsType name]
HsOpTy (LHsType name) (LHsTyOp name) (LHsType name)
HsParTy (LHsType name)
HsIParamTy HsIPName (LHsType name)
(?x :: ty)
HsEqTy (LHsType name) (LHsType name)
ty1 ~ ty2
HsKindSig (LHsType name) (LHsKind name)
(ty :: kind)
HsQuasiQuoteTy (HsQuasiQuote name)
HsSpliceTy (HsSplice name) (PostTc name Kind)
HsDocTy (LHsType name) LHsDocString
HsBangTy HsSrcBang (LHsType name)
HsRecTy [LConDeclField name]
HsCoreTy Type
HsExplicitListTy (PostTc name Kind) [LHsType name]
HsExplicitTupleTy [PostTc name Kind] [LHsType name]
HsTyLit HsTyLit
HsWrapTy HsTyWrapper (HsType name)
HsWildcardTy
HsNamedWildcardTy name

Instances

DataId name => Data (HsType name) 
OutputableBndr name => Outputable (HsType name) 

type LHsType name Source

Arguments

 = Located (HsType name)

May have AnnKeywordId : AnnComma when in a list

type HsKind name = HsType name Source

type LHsKind name Source

Arguments

 = Located (HsKind name)

AnnKeywordId : AnnDcolon

type HsTyOp name = (HsTyWrapper, name) Source

type LHsTyOp name = HsTyOp (Located name) Source

data HsTyVarBndr name Source

Instances

DataId name => Data (HsTyVarBndr name) 
OutputableBndr name => Outputable (HsTyVarBndr name) 

data LHsTyVarBndrs name Source

Constructors

HsQTvs 

Fields

hsq_kvs :: [Name]
 
hsq_tvs :: [LHsTyVarBndr name]
 

Instances

data HsWithBndrs name thing Source

Constructors

HsWB 

Fields

hswb_cts :: thing
 
hswb_kvs :: PostRn name [Name]
 
hswb_tvs :: PostRn name [Name]
 
hswb_wcs :: PostRn name [Name]
 

Instances

(Data name, Data thing, Data (PostRn name [Name])) => Data (HsWithBndrs name thing) 
Outputable thing => Outputable (HsWithBndrs name thing) 

type HsContext name = [LHsType name] Source

type LHsContext name Source

Arguments

 = Located (HsContext name)

AnnKeywordId : AnnUnit

data HsTyWrapper Source

Constructors

WpKiApps [Kind] 

Instances

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 

type LBangType name = Located (BangType name) Source

type BangType name = HsType name Source

type LConDeclField name Source

Arguments

 = Located (ConDeclField name)

May have AnnKeywordId : AnnComma when in a list

isHsKindedTyVar :: HsTyVarBndr name -> Bool Source

Does this HsTyVarBndr come with an explicit kind annotation?

hsTvbAllKinded :: LHsTyVarBndrs name -> Bool Source

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

mkImplicitHsForAllTy :: LHsType RdrName -> HsType RdrName Source

mkImplicitHsForAllTy is called when we encounter f :: type Wrap around a HsForallTy if one is not there already.

mkHsForAllTy :: HsExplicitFlag -> [LHsTyVarBndr RdrName] -> LHsContext RdrName -> LHsType RdrName -> HsType RdrName Source

Smart constructor for HsForAllTy, which populates the extra-constraints field if a wildcard is present in the context.

flattenTopLevelLHsForAllTy :: LHsType name -> LHsType name Source

When a sigtype is parsed, the type found is wrapped in an Implicit HsForAllTy via mkImplicitHsForAllTy, to ensure that a signature always has a forall at the outer level. For Api Annotations this nested structure is important to ensure that all forall and . locations are retained. From the renamer onwards this structure is flattened, to ease the renaming and type checking process.

splitHsClassTy_maybe :: HsType name -> Maybe (name, [LHsType name]) Source

mkHsOpTy :: LHsType name -> Located name -> LHsType name -> HsType name Source

pprHsForAllExtra :: OutputableBndr name => HsExplicitFlag -> Maybe SrcSpan -> LHsTyVarBndrs name -> LHsContext name -> 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.