ghc-8.10.1: The GHC API
Safe HaskellNone
LanguageHaskell2010

IfaceType

Synopsis

Documentation

data IfaceType Source #

A kind of universal type, used for types and kinds.

Any time a Type is pretty-printed, it is first converted to an IfaceType before being printed. See Note [Pretty printing via IfaceSyn] in PprTyThing

Instances

Instances details
NFData IfaceType Source # 
Instance details

Defined in IfaceType

Methods

rnf :: IfaceType -> () #

Outputable IfaceType Source # 
Instance details

Defined in IfaceType

Binary IfaceType Source # 
Instance details

Defined in IfaceType

Binary (DefMethSpec IfaceType) Source # 
Instance details

Defined in IfaceType

data IfaceMCoercion Source #

Instances

Instances details
NFData IfaceMCoercion Source # 
Instance details

Defined in IfaceType

Methods

rnf :: IfaceMCoercion -> () #

Binary IfaceMCoercion Source # 
Instance details

Defined in IfaceType

data IfaceTyCon Source #

Instances

Instances details
Eq IfaceTyCon Source # 
Instance details

Defined in IfaceType

NFData IfaceTyCon Source # 
Instance details

Defined in IfaceType

Methods

rnf :: IfaceTyCon -> () #

Outputable IfaceTyCon Source # 
Instance details

Defined in IfaceType

Binary IfaceTyCon Source # 
Instance details

Defined in IfaceType

data IfaceTyConSort Source #

The various types of TyCons which have special, built-in syntax.

Constructors

IfaceNormalTyCon

a regular tycon

IfaceTupleTyCon !Arity !TupleSort

e.g. (a, b, c) or (). The arity is the tuple width, not the tycon arity (which is twice the width in the case of unboxed tuples).

IfaceSumTyCon !Arity

e.g. (a | b | c)

IfaceEqualityTyCon

A heterogeneous equality TyCon (i.e. eqPrimTyCon, eqReprPrimTyCon, heqTyCon) that is actually being applied to two types of the same kind. This affects pretty-printing only: see Note [Equality predicates in IfaceType]

Instances

Instances details
Eq IfaceTyConSort Source # 
Instance details

Defined in IfaceType

NFData IfaceTyConSort Source # 
Instance details

Defined in IfaceType

Methods

rnf :: IfaceTyConSort -> () #

Binary IfaceTyConSort Source # 
Instance details

Defined in IfaceType

data IfaceTyLit Source #

Instances

Instances details
Eq IfaceTyLit Source # 
Instance details

Defined in IfaceType

NFData IfaceTyLit Source # 
Instance details

Defined in IfaceType

Methods

rnf :: IfaceTyLit -> () #

Outputable IfaceTyLit Source # 
Instance details

Defined in IfaceType

Binary IfaceTyLit Source # 
Instance details

Defined in IfaceType

data IfaceAppArgs Source #

Stores the arguments in a type application as a list. See Note [Suppressing invisible arguments].

data IfaceBndr Source #

Instances

Instances details
NFData IfaceBndr Source # 
Instance details

Defined in IfaceType

Methods

rnf :: IfaceBndr -> () #

Outputable IfaceBndr Source # 
Instance details

Defined in IfaceType

Binary IfaceBndr Source # 
Instance details

Defined in IfaceType

data IfaceOneShot Source #

Instances

Instances details
NFData IfaceOneShot Source # 
Instance details

Defined in IfaceType

Methods

rnf :: IfaceOneShot -> () #

Binary IfaceOneShot Source # 
Instance details

Defined in IfaceType

data ArgFlag Source #

Argument Flag

Is something required to appear in source Haskell (Required), permitted by request (Specified) (visible type application), or prohibited entirely from appearing in source Haskell (Inferred)? See Note [VarBndrs, TyCoVarBinders, TyConBinders, and visibility] in TyCoRep

Constructors

Inferred 
Specified 
Required 

Instances

Instances details
Eq ArgFlag Source # 
Instance details

Defined in Var

Methods

(==) :: ArgFlag -> ArgFlag -> Bool #

(/=) :: ArgFlag -> ArgFlag -> Bool #

Data ArgFlag Source # 
Instance details

Defined in Var

Methods

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

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

toConstr :: ArgFlag -> Constr #

dataTypeOf :: ArgFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ArgFlag Source # 
Instance details

Defined in Var

Outputable ArgFlag Source # 
Instance details

Defined in Var

Binary ArgFlag Source # 
Instance details

Defined in Var

Outputable tv => Outputable (VarBndr tv ArgFlag) Source # 
Instance details

Defined in Var

data AnonArgFlag Source #

The non-dependent version of ArgFlag.

Constructors

VisArg

Used for (->): an ordinary non-dependent arrow. The argument is visible in source code.

InvisArg

Used for (=>): a non-dependent predicate arrow. The argument is invisible in source code.

Instances

Instances details
Eq AnonArgFlag Source # 
Instance details

Defined in Var

Data AnonArgFlag Source # 
Instance details

Defined in Var

Methods

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

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

toConstr :: AnonArgFlag -> Constr #

dataTypeOf :: AnonArgFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AnonArgFlag Source # 
Instance details

Defined in Var

Outputable AnonArgFlag Source # 
Instance details

Defined in Var

Binary AnonArgFlag Source # 
Instance details

Defined in Var

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

Instances details
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 :: forall r r'. (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 ShowForAllFlag Source #

Show forall flag

Unconditionally show the forall quantifier with (ShowForAllMust) or when (ShowForAllWhen) the names used are free in the binder or when compiling with -fprint-explicit-foralls.

mkIfaceTyConKind :: [IfaceTyConBinder] -> IfaceKind -> IfaceKind Source #

Build the tyConKind from the binders and the result kind. Keep in sync with mkTyConKind in types/TyCon.

ifForAllBndrName :: IfaceForAllBndr -> IfLclName Source #

Extract the variable name from an IfaceForAllBndr.

ifTyConBinderName :: IfaceTyConBinder -> IfLclName Source #

Extract the variable name from an IfaceTyConBinder.

newtype SuppressBndrSig Source #

Do we want to suppress kind annotations on binders? See Note [Suppressing binder signatures]

Constructors

SuppressBndrSig Bool 

newtype UseBndrParens Source #

Constructors

UseBndrParens Bool 

pprIfaceContext :: PprPrec -> [IfacePredType] -> SDoc Source #

Prints a context or () if empty You give it the context precedence

pprIfaceContextArr :: [IfacePredType] -> SDoc Source #

Prints "(C a, D b) =>", including the arrow. Used when we want to print a context in a type, so we use funPrec to decide whether to parenthesise a singleton predicate; e.g. Num a => a -> a

pprIfaceForAllPartMust :: [IfaceForAllBndr] -> [IfacePredType] -> SDoc -> SDoc Source #

Like pprIfaceForAllPart, but always uses an explicit forall.

pprIfaceForAll :: [IfaceForAllBndr] -> SDoc Source #

Render the "forall ... ." or "forall ... ->" bit of a type.

mkIfaceTySubst :: [(IfLclName, IfaceType)] -> IfaceTySubst Source #

inDomIfaceTySubst :: IfaceTySubst -> IfaceTvBndr -> Bool Source #