ghc-9.11: The GHC API
Safe HaskellNone
LanguageGHC2021

GHC.Plugins

Description

This module is not used by GHC itself. Rather, it exports all of the functions and types you are likely to need when writing a plugin for GHC. So authors of plugins can probably get away simply with saying "import GHC.Plugins".

Particularly interesting modules for plugin writers include GHC.Core and GHC.Core.Opt.Monad.

Synopsis

Documentation

alterOccEnv :: (Maybe a -> Maybe a) -> OccEnv a -> OccName -> OccEnv a Source #

Alter an OccEnv, adding or removing an element at the given key.

delFromOccEnv :: OccEnv a -> OccName -> OccEnv a Source #

Delete one element from an OccEnv.

delListFromOccEnv :: OccEnv a -> [OccName] -> OccEnv a Source #

Delete multiple elements from an OccEnv.

elemOccEnv :: OccName -> OccEnv a -> Bool Source #

Compute whether there is a value keyed by the given OccName.

extendOccEnv :: OccEnv a -> OccName -> a -> OccEnv a Source #

Add a single element to an OccEnv.

extendOccEnvList :: OccEnv a -> [(OccName, a)] -> OccEnv a Source #

Extend an OccEnv by a list.

OccNames later on in the list override earlier OccNames.

extendOccEnv_Acc Source #

Arguments

:: (a -> b -> b)

add to existing

-> (a -> b)

new element

-> OccEnv b

old

-> OccName 
-> a

new

-> OccEnv b 

Add a single element to an OccEnv, using a different function whether the OccName already exists or not.

filterOccEnv :: (a -> Bool) -> OccEnv a -> OccEnv a Source #

Filter out all elements in an OccEnv using a predicate.

forceOccEnv :: (a -> ()) -> OccEnv a -> () Source #

Force an OccEnv with the provided function.

intersectOccEnv_C :: (a -> b -> c) -> OccEnv a -> OccEnv b -> OccEnv c Source #

isDataSymOcc :: OccName -> Bool Source #

Test if the OccName is a data constructor that starts with a symbol (e.g. :, or [])

isDerivedOccName :: OccName -> Bool Source #

Test for definitions internally generated by GHC. This predicate is used to suppress printing of internal definitions in some debug prints

isSymOcc :: OccName -> Bool Source #

Test if the OccName is that for any operator (whether it is a data constructor or variable or whatever)

isTermVarOrFieldNameSpace :: NameSpace -> Bool Source #

Is this a term variable or field name namespace?

isTypeableBindOcc :: OccName -> Bool Source #

Is an OccName one of a Typeable TyCon or Module binding? This is needed as these bindings are renamed differently. See Note [Grand plan for Typeable] in GHC.Tc.Instance.Typeable.

isValOcc :: OccName -> Bool Source #

Value OccNamess are those that are either in the variable, field name or data constructor namespaces

lookupFieldsOccEnv :: OccEnv a -> FastString -> [a] Source #

Look up all the record fields that match with the given FastString in an OccEnv.

lookupOccEnv :: OccEnv a -> OccName -> Maybe a Source #

Look an element up in an OccEnv.

lookupOccEnv_AllNameSpaces :: OccEnv a -> OccName -> [a] Source #

Lookup an element in an OccEnv, ignoring NameSpaces entirely.

lookupOccEnv_WithFields :: OccEnv a -> OccName -> [a] Source #

Lookup an element in an OccEnv, looking in the record field namespace for a variable.

mapMaybeOccEnv :: (a -> Maybe b) -> OccEnv a -> OccEnv b Source #

mapMaybe for b OccEnv.

mapOccEnv :: (a -> b) -> OccEnv a -> OccEnv b Source #

Map over an OccEnv (Functor instance).

minusOccEnv :: OccEnv a -> OccEnv b -> OccEnv a Source #

Remove elements of the first OccEnv that appear in the second OccEnv.

minusOccEnv_C :: (a -> b -> Maybe a) -> OccEnv a -> OccEnv b -> OccEnv a Source #

Alters (replaces or removes) those elements of the first OccEnv that are mentioned in the second OccEnv.

Same idea as differenceWith.

mkDFunOcc Source #

Arguments

:: String

Typically the class and type glommed together e.g. OrdMaybe. Only used in debug mode, for extra clarity

-> Bool

Is this a hs-boot instance DFun?

-> OccSet

avoid these Occs

-> OccName

E.g. $f3OrdMaybe

mkInstTyTcOcc Source #

Arguments

:: String

Family name, e.g. Map

-> OccSet

avoid these Occs

-> OccName
R:Map

Derive a name for the representation type constructor of a data/newtype instance.

mkLocalOcc Source #

Arguments

:: Unique

Unique to combine with the OccName

-> OccName

Local name, e.g. sat

-> OccName

Nice unique version, e.g. $L23sat

mkOccEnv :: [(OccName, a)] -> OccEnv a Source #

Create an OccEnv from a list.

OccNames later on in the list override earlier OccNames.

mkOccEnv_C Source #

Arguments

:: (a -> a -> a)

old -> new -> result

-> [(OccName, a)] 
-> OccEnv a 

Create an OccEnv from a list, combining different values with the same OccName using the combining function.

mkSuperDictSelOcc Source #

Arguments

:: Int

Index of superclass, e.g. 3

-> OccName

Class, e.g. Ord

-> OccName

Derived Occname, e.g. $p3Ord

nonDetFoldOccEnv :: (a -> b -> b) -> b -> OccEnv a -> b Source #

Fold over an OccEnv. Non-deterministic, unless the folding function is commutative (i.e. a1 f ( a2 f b ) == a2 f ( a1 f b ) for all a1, a2, b).

nonDetOccEnvElts :: OccEnv a -> [a] Source #

Obtain the elements of an OccEnv.

The resulting order is non-deterministic.

occNameMangledFS :: OccName -> FastString Source #

Mangle field names to avoid duplicate symbols.

See Note [Mangling OccNames].

parenSymOcc :: OccName -> SDoc -> SDoc Source #

Wrap parens around an operator

plusOccEnv :: OccEnv a -> OccEnv a -> OccEnv a Source #

Union of two OccEnvs, right-biased.

plusOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccEnv a -> OccEnv a Source #

Union of two OccEnvs with a combining function.

pprOccEnv :: (a -> SDoc) -> OccEnv a -> SDoc Source #

pprOccName :: IsLine doc => OccName -> doc Source #

startsWithUnderscore :: OccName -> Bool Source #

Haskell 98 encourages compilers to suppress warnings about unused names in a pattern if they start with _: this implements that test

strictMapOccEnv :: (a -> b) -> OccEnv a -> OccEnv b Source #

Map over an OccEnv strictly.

unitOccEnv :: OccName -> a -> OccEnv a Source #

A singleton OccEnv.

type FastStringEnv a = UniqFM FastString a Source #

A non-deterministic set of FastStrings. See Note [Deterministic UniqFM] in GHC.Types.Unique.DFM for explanation why it's not deterministic and why it matters. Use DFastStringEnv if the set eventually gets converted into a list or folded over in a way where the order changes the generated code.

class HasOccName name where Source #

Other names in the compiler add additional information to an OccName. This class provides a consistent way to access the underlying OccName.

Methods

occName :: name -> OccName Source #

Instances

Instances details
HasOccName IfaceClassOp Source # 
Instance details

Defined in GHC.Iface.Syntax

HasOccName IfaceConDecl Source # 
Instance details

Defined in GHC.Iface.Syntax

HasOccName IfaceDecl Source # 
Instance details

Defined in GHC.Iface.Syntax

HasOccName HoleFitCandidate Source # 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

HasOccName TcBinder Source # 
Instance details

Defined in GHC.Tc.Types.BasicTypes

HasOccName FieldLabel Source # 
Instance details

Defined in GHC.Types.FieldLabel

HasOccName Name Source # 
Instance details

Defined in GHC.Types.Name

Methods

occName :: Name -> OccName Source #

HasOccName OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

HasOccName RdrName Source # 
Instance details

Defined in GHC.Types.Name.Reader

HasOccName Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

occName :: Var -> OccName Source #

HasOccName (GlobalRdrEltX info) Source # 
Instance details

Defined in GHC.Types.Name.Reader

(HasOccName (IdP (GhcPass p)), OutputableBndrId p) => HasOccName (IEWrappedName (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.ImpExp

data OccEnv a Source #

A map keyed on OccName. See Note [OccEnv].

Instances

Instances details
Functor OccEnv Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

fmap :: (a -> b) -> OccEnv a -> OccEnv b #

(<$) :: a -> OccEnv b -> OccEnv a #

NFData a => NFData (OccEnv a) Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

rnf :: OccEnv a -> () Source #

Outputable a => Outputable (OccEnv a) Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccEnv a -> SDoc Source #

data OccName Source #

Occurrence Name

In this context that means: "classified (i.e. as a type name, value name, etc) but not qualified and not yet resolved"

Instances

Instances details
NFData OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

rnf :: OccName -> () Source #

HasOccName OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Binary OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Outputable OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccName -> SDoc Source #

OutputableBndr OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Data OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

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

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

toConstr :: OccName -> Constr #

dataTypeOf :: OccName -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

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

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

Ord OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

isDynLinkName :: Platform -> Module -> Name -> Bool Source #

Will the Name come from a dynamically linked package?

isUnboxedTupleDataConLikeName :: Name -> Bool Source #

This matches a datacon as well as its worker and promoted tycon.

isWiredIn :: NamedThing thing => thing -> Bool Source #

localiseName :: Name -> Name Source #

Make the Name into an internal name, regardless of what it was to begin with

mkExternalName :: Unique -> Module -> OccName -> SrcSpan -> Name Source #

Create a name which definitely originates in the given module

mkFCallName :: Unique -> FastString -> Name Source #

Make a name for a foreign call

mkInternalName :: Unique -> OccName -> SrcSpan -> Name Source #

Create a name which is (for now at least) local to the current module and hence does not need a Module to disambiguate it from other Names

mkSystemName :: Unique -> OccName -> Name Source #

Create a name brought into being by the compiler

mkWiredInName :: Module -> OccName -> Unique -> TyThing -> BuiltInSyntax -> Name Source #

Create a name which is actually defined by the compiler itself

nameIsExternalOrFrom :: Module -> Name -> Bool Source #

Returns True if the name is external or from the interactive package See documentation of nameIsLocalOrFrom function

nameIsFromExternalPackage :: HomeUnit -> Name -> Bool Source #

Returns True if the Name comes from some other package: neither this package nor the interactive package.

nameIsLocalOrFrom :: Module -> Name -> Bool Source #

Returns True if the name is (a) Internal (b) External but from the specified module (c) External but from the interactive package

The key idea is that False means: the entity is defined in some other module you can find the details (type, fixity, instances) in some interface file those details will be stored in the EPT or HPT

True means: the entity is defined in this module or earlier in the GHCi session you can find details (type, fixity, instances) in the TcGblEnv or TcLclEnv

The isInteractiveModule part is because successive interactions of a GHCi session each give rise to a fresh module (Ghci1, Ghci2, etc), but they all come from the magic interactive package; and all the details are kept in the TcLclEnv, TcGblEnv, NOT in the HPT or EPT. See Note [The interactive package] in GHC.Runtime.Context

nameStableString :: Name -> String Source #

Get a string representation of a Name that's unique and stable across recompilations. Used for deterministic generation of binds for derived instances. eg. "$aeson_70dylHtv1FFGeai1IoxcQr$Data.Aeson.Types.Internal$String"

pprFullName :: Module -> Name -> SDoc Source #

Print fully qualified name (with unit-id, module and unique)

pprName :: IsLine doc => Name -> doc Source #

pprNameUnqualified :: Name -> SDoc Source #

Print the string of Name unqualifiedly directly.

pprTickyName :: Module -> Name -> SDoc Source #

Print a ticky ticky styled name

Module argument is the module to use for internal and system names. When printing the name in a ticky profile, the module name is included even for local things. However, ticky uses the format "x (M)" rather than "M.x". Hence, this function provides a separation from normal styling.

stableNameCmp :: Name -> Name -> Ordering Source #

Compare Names lexicographically This only works for Names that originate in the source code or have been tidied.

alterOccEnv :: (Maybe a -> Maybe a) -> OccEnv a -> OccName -> OccEnv a Source #

Alter an OccEnv, adding or removing an element at the given key.

delFromOccEnv :: OccEnv a -> OccName -> OccEnv a Source #

Delete one element from an OccEnv.

delListFromOccEnv :: OccEnv a -> [OccName] -> OccEnv a Source #

Delete multiple elements from an OccEnv.

elemOccEnv :: OccName -> OccEnv a -> Bool Source #

Compute whether there is a value keyed by the given OccName.

extendOccEnv :: OccEnv a -> OccName -> a -> OccEnv a Source #

Add a single element to an OccEnv.

extendOccEnvList :: OccEnv a -> [(OccName, a)] -> OccEnv a Source #

Extend an OccEnv by a list.

OccNames later on in the list override earlier OccNames.

extendOccEnv_Acc Source #

Arguments

:: (a -> b -> b)

add to existing

-> (a -> b)

new element

-> OccEnv b

old

-> OccName 
-> a

new

-> OccEnv b 

Add a single element to an OccEnv, using a different function whether the OccName already exists or not.

filterOccEnv :: (a -> Bool) -> OccEnv a -> OccEnv a Source #

Filter out all elements in an OccEnv using a predicate.

forceOccEnv :: (a -> ()) -> OccEnv a -> () Source #

Force an OccEnv with the provided function.

intersectOccEnv_C :: (a -> b -> c) -> OccEnv a -> OccEnv b -> OccEnv c Source #

isDataSymOcc :: OccName -> Bool Source #

Test if the OccName is a data constructor that starts with a symbol (e.g. :, or [])

isDerivedOccName :: OccName -> Bool Source #

Test for definitions internally generated by GHC. This predicate is used to suppress printing of internal definitions in some debug prints

isSymOcc :: OccName -> Bool Source #

Test if the OccName is that for any operator (whether it is a data constructor or variable or whatever)

isTermVarOrFieldNameSpace :: NameSpace -> Bool Source #

Is this a term variable or field name namespace?

isTypeableBindOcc :: OccName -> Bool Source #

Is an OccName one of a Typeable TyCon or Module binding? This is needed as these bindings are renamed differently. See Note [Grand plan for Typeable] in GHC.Tc.Instance.Typeable.

isValOcc :: OccName -> Bool Source #

Value OccNamess are those that are either in the variable, field name or data constructor namespaces

lookupFieldsOccEnv :: OccEnv a -> FastString -> [a] Source #

Look up all the record fields that match with the given FastString in an OccEnv.

lookupOccEnv :: OccEnv a -> OccName -> Maybe a Source #

Look an element up in an OccEnv.

lookupOccEnv_AllNameSpaces :: OccEnv a -> OccName -> [a] Source #

Lookup an element in an OccEnv, ignoring NameSpaces entirely.

lookupOccEnv_WithFields :: OccEnv a -> OccName -> [a] Source #

Lookup an element in an OccEnv, looking in the record field namespace for a variable.

mapMaybeOccEnv :: (a -> Maybe b) -> OccEnv a -> OccEnv b Source #

mapMaybe for b OccEnv.

mapOccEnv :: (a -> b) -> OccEnv a -> OccEnv b Source #

Map over an OccEnv (Functor instance).

minusOccEnv :: OccEnv a -> OccEnv b -> OccEnv a Source #

Remove elements of the first OccEnv that appear in the second OccEnv.

minusOccEnv_C :: (a -> b -> Maybe a) -> OccEnv a -> OccEnv b -> OccEnv a Source #

Alters (replaces or removes) those elements of the first OccEnv that are mentioned in the second OccEnv.

Same idea as differenceWith.

mkDFunOcc Source #

Arguments

:: String

Typically the class and type glommed together e.g. OrdMaybe. Only used in debug mode, for extra clarity

-> Bool

Is this a hs-boot instance DFun?

-> OccSet

avoid these Occs

-> OccName

E.g. $f3OrdMaybe

mkInstTyTcOcc Source #

Arguments

:: String

Family name, e.g. Map

-> OccSet

avoid these Occs

-> OccName
R:Map

Derive a name for the representation type constructor of a data/newtype instance.

mkLocalOcc Source #

Arguments

:: Unique

Unique to combine with the OccName

-> OccName

Local name, e.g. sat

-> OccName

Nice unique version, e.g. $L23sat

mkOccEnv :: [(OccName, a)] -> OccEnv a Source #

Create an OccEnv from a list.

OccNames later on in the list override earlier OccNames.

mkOccEnv_C Source #

Arguments

:: (a -> a -> a)

old -> new -> result

-> [(OccName, a)] 
-> OccEnv a 

Create an OccEnv from a list, combining different values with the same OccName using the combining function.

mkSuperDictSelOcc Source #

Arguments

:: Int

Index of superclass, e.g. 3

-> OccName

Class, e.g. Ord

-> OccName

Derived Occname, e.g. $p3Ord

nonDetFoldOccEnv :: (a -> b -> b) -> b -> OccEnv a -> b Source #

Fold over an OccEnv. Non-deterministic, unless the folding function is commutative (i.e. a1 f ( a2 f b ) == a2 f ( a1 f b ) for all a1, a2, b).

nonDetOccEnvElts :: OccEnv a -> [a] Source #

Obtain the elements of an OccEnv.

The resulting order is non-deterministic.

occNameMangledFS :: OccName -> FastString Source #

Mangle field names to avoid duplicate symbols.

See Note [Mangling OccNames].

parenSymOcc :: OccName -> SDoc -> SDoc Source #

Wrap parens around an operator

plusOccEnv :: OccEnv a -> OccEnv a -> OccEnv a Source #

Union of two OccEnvs, right-biased.

plusOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccEnv a -> OccEnv a Source #

Union of two OccEnvs with a combining function.

pprOccEnv :: (a -> SDoc) -> OccEnv a -> SDoc Source #

pprOccName :: IsLine doc => OccName -> doc Source #

startsWithUnderscore :: OccName -> Bool Source #

Haskell 98 encourages compilers to suppress warnings about unused names in a pattern if they start with _: this implements that test

strictMapOccEnv :: (a -> b) -> OccEnv a -> OccEnv b Source #

Map over an OccEnv strictly.

unitOccEnv :: OccName -> a -> OccEnv a Source #

A singleton OccEnv.

type FastStringEnv a = UniqFM FastString a Source #

A non-deterministic set of FastStrings. See Note [Deterministic UniqFM] in GHC.Types.Unique.DFM for explanation why it's not deterministic and why it matters. Use DFastStringEnv if the set eventually gets converted into a list or folded over in a way where the order changes the generated code.

data BuiltInSyntax Source #

BuiltInSyntax is for things like (:), [] and tuples, which have special syntactic forms. They aren't in scope as such.

Constructors

BuiltInSyntax 
UserSyntax 

data Name Source #

A unique, unambiguous name for something, containing information about where that thing originated.

Instances

Instances details
NFData Name Source # 
Instance details

Defined in GHC.Types.Name

Methods

rnf :: Name -> () Source #

NamedThing Name Source # 
Instance details

Defined in GHC.Types.Name

HasOccName Name Source # 
Instance details

Defined in GHC.Types.Name

Methods

occName :: Name -> OccName Source #

Uniquable Name Source # 
Instance details

Defined in GHC.Types.Name

Binary Name Source #

Assumes that the Name is a non-binding one. See putIfaceTopBndr and getIfaceTopBndr for serializing binding Names. See UserData for the rationale for this distinction.

Instance details

Defined in GHC.Types.Name

Outputable Name Source # 
Instance details

Defined in GHC.Types.Name

Methods

ppr :: Name -> SDoc Source #

OutputableBndr Name Source # 
Instance details

Defined in GHC.Types.Name

Data Name Source # 
Instance details

Defined in GHC.Types.Name

Methods

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

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

toConstr :: Name -> Constr #

dataTypeOf :: Name -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq Name Source #

The same comments as for Name's Ord instance apply.

Instance details

Defined in GHC.Types.Name

Methods

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

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

Ord Name Source #

Caution: This instance is implemented via nonDetCmpUnique, which means that the ordering is not stable across deserialization or rebuilds.

See nonDetCmpUnique for further information, and #15240 for a bug caused by improper use of this instance.

Instance details

Defined in GHC.Types.Name

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

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

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

type Anno Name Source # 
Instance details

Defined in GHC.Hs.Extension

class NamedThing a where Source #

A class allowing convenient access to the Name of various datatypes

Minimal complete definition

getName

Methods

getOccName :: a -> OccName Source #

getName :: a -> Name Source #

Instances

Instances details
NamedThing Class Source # 
Instance details

Defined in GHC.Core.Class

NamedThing ConLike Source # 
Instance details

Defined in GHC.Core.ConLike

NamedThing DataCon Source # 
Instance details

Defined in GHC.Core.DataCon

NamedThing FamInst Source # 
Instance details

Defined in GHC.Core.FamInstEnv

NamedThing ClsInst Source # 
Instance details

Defined in GHC.Core.InstEnv

NamedThing PatSyn Source # 
Instance details

Defined in GHC.Core.PatSyn

NamedThing TyCon Source # 
Instance details

Defined in GHC.Core.TyCon

NamedThing IfaceClassOp Source # 
Instance details

Defined in GHC.Iface.Syntax

NamedThing IfaceConDecl Source # 
Instance details

Defined in GHC.Iface.Syntax

NamedThing IfaceDecl Source # 
Instance details

Defined in GHC.Iface.Syntax

NamedThing HoleFitCandidate Source # 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

NamedThing InvalidFamInstQTv Source # 
Instance details

Defined in GHC.Tc.Errors.Types

NamedThing Name Source # 
Instance details

Defined in GHC.Types.Name

NamedThing TyThing Source # 
Instance details

Defined in GHC.Types.TyThing

NamedThing Var Source # 
Instance details

Defined in GHC.Types.Var

NamedThing (CoAxiom br) Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

NamedThing e => NamedThing (Located e) Source # 
Instance details

Defined in GHC.Types.Name

NamedThing (Located a) => NamedThing (LocatedAn an a) Source # 
Instance details

Defined in GHC.Parser.Annotation

NamedThing tv => NamedThing (VarBndr tv flag) Source # 
Instance details

Defined in GHC.Types.Var

Methods

getOccName :: VarBndr tv flag -> OccName Source #

getName :: VarBndr tv flag -> Name Source #

NamedThing (HsTyVarBndr flag GhcRn) Source # 
Instance details

Defined in GHC.Hs.Type

class HasOccName name where Source #

Other names in the compiler add additional information to an OccName. This class provides a consistent way to access the underlying OccName.

Methods

occName :: name -> OccName Source #

Instances

Instances details
HasOccName IfaceClassOp Source # 
Instance details

Defined in GHC.Iface.Syntax

HasOccName IfaceConDecl Source # 
Instance details

Defined in GHC.Iface.Syntax

HasOccName IfaceDecl Source # 
Instance details

Defined in GHC.Iface.Syntax

HasOccName HoleFitCandidate Source # 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

HasOccName TcBinder Source # 
Instance details

Defined in GHC.Tc.Types.BasicTypes

HasOccName FieldLabel Source # 
Instance details

Defined in GHC.Types.FieldLabel

HasOccName Name Source # 
Instance details

Defined in GHC.Types.Name

Methods

occName :: Name -> OccName Source #

HasOccName OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

HasOccName RdrName Source # 
Instance details

Defined in GHC.Types.Name.Reader

HasOccName Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

occName :: Var -> OccName Source #

HasOccName (GlobalRdrEltX info) Source # 
Instance details

Defined in GHC.Types.Name.Reader

(HasOccName (IdP (GhcPass p)), OutputableBndrId p) => HasOccName (IEWrappedName (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.ImpExp

data OccEnv a Source #

A map keyed on OccName. See Note [OccEnv].

Instances

Instances details
Functor OccEnv Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

fmap :: (a -> b) -> OccEnv a -> OccEnv b #

(<$) :: a -> OccEnv b -> OccEnv a #

NFData a => NFData (OccEnv a) Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

rnf :: OccEnv a -> () Source #

Outputable a => Outputable (OccEnv a) Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccEnv a -> SDoc Source #

data OccName Source #

Occurrence Name

In this context that means: "classified (i.e. as a type name, value name, etc) but not qualified and not yet resolved"

Instances

Instances details
NFData OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

rnf :: OccName -> () Source #

HasOccName OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Binary OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Outputable OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccName -> SDoc Source #

OutputableBndr OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Data OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

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

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

toConstr :: OccName -> Constr #

dataTypeOf :: OccName -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

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

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

Ord OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

alwaysActiveUnfoldingFun :: IdUnfoldingFun Source #

Returns an unfolding only if (a) not a strong loop breaker and (b) always active

asJoinId :: Id -> JoinArity -> JoinId infixl 1 Source #

asNonWorkerLikeId :: Id -> Id Source #

Remove any cbv marks on arguments from a given Id.

asWorkerLikeId :: Id -> Id Source #

Turn this id into a WorkerLikeId if possible.

hasNoBinding :: Id -> Bool Source #

Returns True of an Id which may not have a binding, even though it is defined in this module.

idCafInfo :: Id -> CafInfo infixl 1 Source #

idDataCon :: Id -> DataCon Source #

Get from either the worker or the wrapper Id to the DataCon. Currently used only in the desugarer.

INVARIANT: idDataCon (dataConWrapId d) = d: remember, dataConWrapId can return either the wrapper or the worker

idDmdSig :: Id -> DmdSig Source #

Accesses the Id's dmdSigInfo.

idFunRepArity :: Id -> RepArity Source #

This function counts all arguments post-unarisation, which includes arguments with no runtime representation -- see Note [Unarisation and arity]

idJoinPointHood :: Var -> JoinPointHood Source #

Doesn't return strictness marks

idUnfolding :: IdUnfoldingFun Source #

Returns the Ids unfolding, but does not expose the unfolding of a strong loop breaker. See unfoldingInfo.

If you really want the unfolding of a strong loopbreaker, call realIdUnfolding.

isDeadEndId :: Var -> Bool Source #

Returns true if an application to n args diverges or throws an exception See Note [Dead ends] in GHC.Types.Demand.

isImplicitId :: Id -> Bool Source #

isImplicitId tells whether an Ids info is implied by other declarations, so we don't need to put its signature in an interface file, even if it's mentioned in some other interface unfolding.

isStrictId :: Id -> Bool Source #

isStrictId says whether either (a) the Id has a strict demand placed on it or (b) definitely has a "strict type", such that it can always be evaluated strictly (i.e an unlifted type) We need to check (b) as well as (a), because when the demand for the given id hasn't been computed yet but id has a strict type, we still want `isStrictId id` to be True. Returns False if the type is levity polymorphic; False is always safe.

isWorkerLikeId :: Id -> Bool Source #

An Id for which we might require all callers to pass strict arguments properly tagged + evaluated.

See Note [CBV Function Ids]

mkExportedLocalId :: IdDetails -> Name -> Type -> Id Source #

Create a local Id that is marked as exported. This prevents things attached to it from being removed as dead code. See Note [Exported LocalIds]

mkGlobalId :: IdDetails -> Name -> Type -> IdInfo -> Id Source #

For an explanation of global vs. local Ids, see GHC.Types.Var.Var

mkLocalCoVar :: HasDebugCallStack => Name -> Type -> CoVar Source #

Make a local CoVar

mkLocalId :: HasDebugCallStack => Name -> Mult -> Type -> Id Source #

For an explanation of global vs. local Ids, see GHC.Types.Var

mkLocalIdOrCoVar :: HasDebugCallStack => Name -> Mult -> Type -> Id Source #

Like mkLocalId, but checks the type to see if it should make a covar

mkSysLocal :: FastString -> Unique -> Mult -> Type -> Id Source #

Create a system local Id. These are local Ids (see Var) that are created by the compiler out of thin air

mkSysLocalOrCoVar :: FastString -> Unique -> Mult -> Type -> Id Source #

Like mkSysLocal, but checks to see if we have a covar type

mkTemplateLocal :: Int -> Type -> Id Source #

Create a template local: a family of system local Ids in bijection with Ints, typically used in unfoldings

mkTemplateLocals :: [Type] -> [Id] Source #

Create a template local for a series of types

mkTemplateLocalsNum :: Int -> [Type] -> [Id] Source #

Create a template local for a series of type, but start from a specified template local

mkUserLocal :: OccName -> Unique -> Mult -> Type -> SrcSpan -> Id Source #

Create a user local Id. These are local Ids (see GHC.Types.Var) with a name and location that the user might recognize

mkUserLocalOrCoVar :: OccName -> Unique -> Mult -> Type -> SrcSpan -> Id Source #

Like mkUserLocal, but checks if we have a coercion type

mkVanillaGlobal :: HasDebugCallStack => Name -> Type -> Id Source #

Make a global Id without any extra information at all

mkVanillaGlobalWithInfo :: HasDebugCallStack => Name -> Type -> IdInfo -> Id Source #

Make a global Id with no global information but some generic IdInfo

mkWorkerId :: Unique -> Id -> Type -> Id Source #

Workers get local names. CoreTidy will externalise these if necessary

realIdUnfolding :: Id -> Unfolding Source #

Expose the unfolding if there is one, including for loop breakers

recordSelectorTyCon :: Id -> RecSelParent Source #

If the Id is that for a record selector, extract the sel_tycon. Panic otherwise.

scaleVarBy :: Mult -> Var -> Var Source #

Like scaleIdBy, but skips non-Ids. Useful for scaling a mixed list of ids and tyvars.

setIdArity :: Id -> Arity -> Id infixl 1 Source #

setIdCallArity :: Id -> Arity -> Id infixl 1 Source #

setIdCbvMarks :: Id -> [CbvMark] -> Id infixl 1 Source #

If all marks are NotMarkedStrict we just set nothing.

setIdCprSig :: Id -> CprSig -> Id infixl 1 Source #

setIdDemandInfo :: Id -> Demand -> Id infixl 1 Source #

setIdDmdSig :: Id -> DmdSig -> Id infixl 1 Source #

setIdOccInfo :: Id -> OccInfo -> Id infixl 1 Source #

setIdType :: Id -> Type -> Id Source #

Not only does this set the Id Type, it also evaluates the type to try and reduce space usage

setIdUnfolding :: Id -> Unfolding -> Id infixl 1 Source #

whenActiveUnfoldingFun :: (Activation -> Bool) -> IdUnfoldingFun Source #

Returns an unfolding only if (a) not a strong loop breaker and (b) active in according to is_active

zapIdUnfolding :: Id -> Id Source #

Similar to trimUnfolding, but also removes evaldness info.

globaliseId :: Id -> Id Source #

If it's a local, make it global

isExportedId :: Var -> Bool Source #

isExportedIdVar means "don't throw this away"

isId :: Var -> Bool Source #

Is this a value-level (i.e., computationally relevant) Identifier? Satisfies isId = not . isTyVar.

updateIdTypeAndMultM :: Monad m => (Type -> m Type) -> Id -> m Id Source #

type Id = Var Source #

Identifier

type InId = Id Source #

type InVar = Var Source #

type JoinId = Id Source #

type OutId = Id Source #

data Var Source #

Variable

Essentially a typed Name, that may also contain some additional information about the Var and its use sites.

Instances

Instances details
NamedThing Var Source # 
Instance details

Defined in GHC.Types.Var

HasOccName Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

occName :: Var -> OccName Source #

Uniquable Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

getUnique :: Var -> Unique Source #

Outputable Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: Var -> SDoc Source #

OutputableBndr Var Source # 
Instance details

Defined in GHC.Core.Ppr

Data Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

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

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

toConstr :: Var -> Constr #

dataTypeOf :: Var -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

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

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

Ord Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

compare :: Var -> Var -> Ordering #

(<) :: Var -> Var -> Bool #

(<=) :: Var -> Var -> Bool #

(>) :: Var -> Var -> Bool #

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

max :: Var -> Var -> Var #

min :: Var -> Var -> Var #

Eq (DeBruijn CoreAlt) Source # 
Instance details

Defined in GHC.Core.Map.Expr

Eq (DeBruijn CoreExpr) Source # 
Instance details

Defined in GHC.Core.Map.Expr

Eq (DeBruijn Var) Source # 
Instance details

Defined in GHC.Core.Map.Type

OutputableBndr (Id, TagSig) Source # 
Instance details

Defined in GHC.Stg.InferTags.TagSig

type Anno Id Source # 
Instance details

Defined in GHC.Hs.Extension

module GHC.Core

cloneBndrs :: MonadUnique m => Subst -> [Var] -> m (Subst, [Var]) Source #

cloneIdBndr :: Subst -> UniqSupply -> Id -> (Subst, Id) Source #

Very similar to substBndr, but it always allocates a new Unique for each variable in its output. It substitutes the IdInfo though. Discards non-Stable unfoldings

cloneIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id]) Source #

Applies cloneIdBndr to a number of Ids, accumulating a final substitution from left to right Discards non-Stable unfoldings

cloneRecIdBndrs :: MonadUnique m => Subst -> [Id] -> m (Subst, [Id]) Source #

Clone a mutually recursive group of Ids

deShadowBinds :: CoreProgram -> CoreProgram Source #

De-shadowing the program is sometimes a useful pre-pass. It can be done simply by running over the bindings with an empty substitution, because substitution returns a result that has no-shadowing guaranteed.

(Actually, within a single type there might still be shadowing, because substTy is a no-op for the empty substitution, but that's probably OK.)

Aug 09
This function is not used in GHC at the moment, but seems so short and simple that I'm going to leave it here

extendIdSubst :: Subst -> Id -> CoreExpr -> Subst Source #

Add a substitution for an Id to the Subst: you must ensure that the in-scope set is such that TyCoSubst Note [The substitution invariant] holds after extending the substitution like this

extendIdSubstList :: Subst -> [(Id, CoreExpr)] -> Subst Source #

Adds multiple Id substitutions to the Subst: see also extendIdSubst

extendSubst :: Subst -> Var -> CoreArg -> Subst Source #

Add a substitution appropriate to the thing being substituted (whether an expression, type, or coercion). See also extendIdSubst, extendTvSubst, extendCvSubst

extendSubstList :: Subst -> [(Var, CoreArg)] -> Subst Source #

Add a substitution as appropriate to each of the terms being substituted (whether expressions, types, or coercions). See also extendSubst.

lookupIdSubst :: HasDebugCallStack => Subst -> Id -> CoreExpr Source #

Find the substitution for an Id in the Subst The Id should not be a CoVar

mkOpenSubst :: InScopeSet -> [(Var, CoreArg)] -> Subst Source #

Simultaneously substitute for a bunch of variables No left-right shadowing ie the substitution for (x y. e) a1 a2 so neither x nor y scope over a1 a2

substBind :: HasDebugCallStack => Subst -> CoreBind -> (Subst, CoreBind) Source #

Apply a substitution to an entire CoreBind, additionally returning an updated Subst that should be used by subsequent substitutions.

substBindSC :: HasDebugCallStack => Subst -> CoreBind -> (Subst, CoreBind) Source #

Apply a substitution to an entire CoreBind, additionally returning an updated Subst that should be used by subsequent substitutions.

substBndr :: Subst -> Var -> (Subst, Var) Source #

Substitutes a Var for another one according to the Subst given, returning the result and an updated Subst that should be used by subsequent substitutions. IdInfo is preserved by this process, although it is substituted into appropriately.

substBndrs :: Traversable f => Subst -> f Var -> (Subst, f Var) Source #

Applies substBndr to a number of Vars, accumulating a new Subst left-to-right

substExpr :: HasDebugCallStack => Subst -> CoreExpr -> CoreExpr Source #

substExpr applies a substitution to an entire CoreExpr. Remember, you may only apply the substitution once: See Note [Substitutions apply only once] in GHC.Core.TyCo.Subst

Do *not* attempt to short-cut in the case of an empty substitution! See Note [Extending the IdSubstEnv]

substIdInfo :: Subst -> Id -> IdInfo -> Maybe IdInfo Source #

Substitute into some IdInfo with regard to the supplied new Id. Discards unfoldings, unless they are Stable

substRecBndrs :: Traversable f => Subst -> f Id -> (Subst, f Id) Source #

Substitute in a mutually recursive group of Ids

substRuleInfo :: Subst -> Id -> RuleInfo -> RuleInfo Source #

Substitutes for the Ids within the RuleInfo given the new function Id

substTickish :: Subst -> CoreTickish -> CoreTickish Source #

Drop free vars from the breakpoint if they have a non-variable substitution.

substUnfolding :: Subst -> Unfolding -> Unfolding Source #

Substitutes for the Ids within an unfolding NB: substUnfolding discards any unfolding without without a Stable source. This is usually what we want, but it may be a bit unexpected

substUnfoldingSC :: Subst -> Unfolding -> Unfolding Source #

Substitutes for the Ids within an unfolding NB: substUnfolding discards any unfolding without without a Stable source. This is usually what we want, but it may be a bit unexpected

extendSubstInScope :: Subst -> Var -> Subst Source #

Add the Var to the in-scope set

extendSubstInScopeList :: Subst -> [Var] -> Subst Source #

Add the Vars to the in-scope set: see also extendInScope

extendTvSubst :: Subst -> TyVar -> Type -> Subst Source #

Add a substitution for a TyVar to the Subst The TyVar *must* be a real TyVar, and not a CoVar You must ensure that the in-scope set is such that Note [The substitution invariant] holds after extending the substitution like this.

extendTvSubstList :: Subst -> [(TyVar, Type)] -> Subst Source #

Adds multiple TyVar substitutions to the Subst: see also extendTvSubst

getSubstInScope :: Subst -> InScopeSet Source #

Find the in-scope set: see Note [The substitution invariant]

substCo :: HasDebugCallStack => Subst -> Coercion -> Coercion Source #

Substitute within a Coercion The substitution has to satisfy the invariants described in Note [The substitution invariant].

substTyUnchecked :: Subst -> Type -> Type Source #

Substitute within a Type disabling the sanity checks. The problems that the sanity checks in substTy catch are described in Note [The substitution invariant]. The goal of #11371 is to migrate all the calls of substTyUnchecked to substTy and remove this function. Please don't use in new code.

zapSubst :: Subst -> Subst Source #

Remove all substitutions that might have been built up while preserving the in-scope set originally called zapSubstEnv

type IdSubstEnv = IdEnv CoreExpr Source #

A substitution of Exprs for non-coercion Ids

data Subst Source #

Type & coercion & id substitution

The Subst data type defined in this module contains substitution for tyvar, covar and id. However, operations on IdSubstEnv (mapping from Id to CoreExpr) that require the definition of the Expr data type are defined in GHC.Core.Subst to avoid circular module dependency.

Instances

Instances details
Outputable Subst Source # 
Instance details

Defined in GHC.Core.TyCo.Subst

Methods

ppr :: Subst -> SDoc Source #

type TvSubstEnv = TyVarEnv Type Source #

A substitution of Types for TyVars and Kinds for KindVars

data InScopeSet Source #

A set of variables that are in scope at some point.

Note that this is a superset of the variables that are currently in scope. See Note [The InScopeSet invariant].

"Secrets of the Glasgow Haskell Compiler inliner" Section 3.2 provides the motivation for this abstraction.

Instances

Instances details
Outputable InScopeSet Source # 
Instance details

Defined in GHC.Types.Var.Env

Methods

ppr :: InScopeSet -> SDoc Source #

closeOverKindsDSet :: DTyVarSet -> DTyVarSet Source #

Add the kind variables free in the kinds of the tyvars in the given set. Returns a deterministic set.

closeOverKindsList :: [TyVar] -> [TyVar] Source #

Add the kind variables free in the kinds of the tyvars in the given set. Returns a deterministically ordered list.

scopedSort :: [TyCoVar] -> [TyCoVar] Source #

Do a topological sort on a list of tyvars, so that binders occur before occurrences E.g. given [ a::k, k::*, b::k ] it'll return a well-scoped list [ k::*, a::k, b::k ]

This is a deterministic sorting operation (that is, doesn't depend on Uniques).

It is also meant to be stable: that is, variables should not be reordered unnecessarily. This is specified in Note [ScopedSort] See also Note [Ordering of implicit variables] in GHC.Rename.HsType

tyCoFVsOfType :: Type -> FV Source #

The worker for tyCoFVsOfType and tyCoFVsOfTypeList. The previous implementation used unionVarSet which is O(n+m) and can make the function quadratic. It's exported, so that it can be composed with other functions that compute free variables. See Note [FV naming conventions] in GHC.Utils.FV.

Eta-expanded because that makes it run faster (apparently) See Note [FV eta expansion] in GHC.Utils.FV for explanation.

tyCoVarsOfTypeDSet :: Type -> DTyCoVarSet Source #

tyCoFVsOfType that returns free variables of a type in a deterministic set. For explanation of why using VarSet is not deterministic see Note [Deterministic FV] in GHC.Utils.FV.

tyCoVarsOfTypeWellScoped :: Type -> [TyVar] Source #

Get the free vars of a type in scoped order

tyCoVarsOfTypesWellScoped :: [Type] -> [TyVar] Source #

Get the free vars of types in scoped order

tyConsOfType :: Type -> UniqSet TyCon Source #

All type constructors occurring in the type; looking through type synonyms, but not newtypes. When it finds a Class, it returns the class TyCon.

foldTyCo :: Monoid a => TyCoFolder env a -> env -> (Type -> a, [Type] -> a, Coercion -> a, [Coercion] -> a) Source #

mkForAllTy :: ForAllTyBinder -> Type -> Type Source #

Like mkTyCoForAllTy, but does not check the occurrence of the binder See Note [Unused coercion variable in ForAllTy]

mkForAllTys :: [ForAllTyBinder] -> Type -> Type Source #

Wraps foralls over the type using the provided TyCoVars from left to right

mkInvisForAllTys :: [InvisTVBinder] -> Type -> Type Source #

Wraps foralls over the type using the provided InvisTVBinders from left to right

mkVisFunTyMany :: HasDebugCallStack => Type -> Type -> Type infixr 3 Source #

Make nested arrow types | Special, common, case: Arrow type with mult Many

noView :: Type -> Maybe Type Source #

A view function that looks through nothing.

composeTCvSubst :: Subst -> Subst -> Subst Source #

Composes two substitutions, applying the second one provided first, like in function composition. This function leaves IdSubstEnv untouched because IdSubstEnv is not used during substitution for types.

extendCvSubst :: Subst -> CoVar -> Coercion -> Subst Source #

Add a substitution from a CoVar to a Coercion to the Subst: you must ensure that the in-scope set satisfies Note [The substitution invariant] after extending the substitution like this

extendSubstInScope :: Subst -> Var -> Subst Source #

Add the Var to the in-scope set

extendSubstInScopeList :: Subst -> [Var] -> Subst Source #

Add the Vars to the in-scope set: see also extendInScope

extendSubstInScopeSet :: Subst -> VarSet -> Subst Source #

Add the Vars to the in-scope set: see also extendInScope

getSubstInScope :: Subst -> InScopeSet Source #

Find the in-scope set: see Note [The substitution invariant]

getSubstRangeTyCoFVs :: Subst -> VarSet Source #

Returns the free variables of the types in the range of a substitution as a non-deterministic set.

isEmptyTCvSubst :: Subst -> Bool Source #

Checks whether the tyvar and covar environments are empty. This function should be used over isEmptySubst when substituting for types, because types currently do not contain expressions; we can safely disregard the expression environment when deciding whether to skip a substitution. Using isEmptyTCvSubst gives us a non-trivial performance boost (up to 70% less allocation for T18223)

mkTvSubstPrs :: [(TyVar, Type)] -> Subst Source #

Generates the in-scope set for the TCvSubst from the types in the incoming environment. No CoVars, please! The InScopeSet is just a thunk so with a bit of luck it'll never be evaluated

substCo :: HasDebugCallStack => Subst -> Coercion -> Coercion Source #

Substitute within a Coercion The substitution has to satisfy the invariants described in Note [The substitution invariant].

substCoUnchecked :: Subst -> Coercion -> Coercion Source #

Substitute within a Coercion disabling sanity checks. The problems that the sanity checks in substCo catch are described in Note [The substitution invariant]. The goal of #11371 is to migrate all the calls of substCoUnchecked to substCo and remove this function. Please don't use in new code.

substCoWithUnchecked :: [TyVar] -> [Type] -> Coercion -> Coercion Source #

Coercion substitution, see zipTvSubst. Disables sanity checks. The problems that the sanity checks in substCo catch are described in Note [The substitution invariant]. The goal of #11371 is to migrate all the calls of substCoUnchecked to substCo and remove this function. Please don't use in new code.

substTheta :: HasDebugCallStack => Subst -> ThetaType -> ThetaType Source #

Substitute within a ThetaType The substitution has to satisfy the invariants described in Note [The substitution invariant].

substThetaUnchecked :: Subst -> ThetaType -> ThetaType Source #

Substitute within a ThetaType disabling the sanity checks. The problems that the sanity checks in substTys catch are described in Note [The substitution invariant]. The goal of #11371 is to migrate all the calls of substThetaUnchecked to substTheta and remove this function. Please don't use in new code.

substTyAddInScope :: HasDebugCallStack => Subst -> Type -> Type Source #

Substitute within a Type after adding the free variables of the type to the in-scope set. This is useful for the case when the free variables aren't already in the in-scope set or easily available. See also Note [The substitution invariant].

substTyUnchecked :: Subst -> Type -> Type Source #

Substitute within a Type disabling the sanity checks. The problems that the sanity checks in substTy catch are described in Note [The substitution invariant]. The goal of #11371 is to migrate all the calls of substTyUnchecked to substTy and remove this function. Please don't use in new code.

substTyWith :: HasDebugCallStack => [TyVar] -> [Type] -> Type -> Type Source #

Type substitution, see zipTvSubst

substTyWithUnchecked :: [TyVar] -> [Type] -> Type -> Type Source #

Type substitution, see zipTvSubst. Disables sanity checks. The problems that the sanity checks in substTy catch are described in Note [The substitution invariant]. The goal of #11371 is to migrate all the calls of substTyUnchecked to substTy and remove this function. Please don't use in new code.

substTys :: HasDebugCallStack => Subst -> [Type] -> [Type] Source #

Substitute within several Types The substitution has to satisfy the invariants described in Note [The substitution invariant].

substTysUnchecked :: Subst -> [Type] -> [Type] Source #

Substitute within several Types disabling the sanity checks. The problems that the sanity checks in substTys catch are described in Note [The substitution invariant]. The goal of #11371 is to migrate all the calls of substTysUnchecked to substTys and remove this function. Please don't use in new code.

substTysWith :: HasDebugCallStack => [TyVar] -> [Type] -> [Type] -> [Type] Source #

Type substitution, see zipTvSubst

zapSubst :: Subst -> Subst Source #

Remove all substitutions that might have been built up while preserving the in-scope set originally called zapSubstEnv

zipTvSubst :: HasDebugCallStack => [TyVar] -> [Type] -> Subst Source #

Generates the in-scope set for the Subst from the types in the incoming environment. No CoVars or Ids, please!

zipTyEnv :: HasDebugCallStack => [TyVar] -> [Type] -> TvSubstEnv Source #

The InScopeSet is just a thunk so with a bit of luck it'll never be evaluated

tidyFreeTyCoVarX :: TidyEnv -> TyCoVar -> (TidyEnv, TyCoVar) Source #

Treat a new TyCoVar as a binder, and give it a fresh tidy name using the environment if one has not already been allocated. See also tidyVarBndr See Note [Tidying is idempotent]

tidyFreeTyCoVars :: TidyEnv -> [TyCoVar] -> TidyEnv Source #

Add the free TyVars to the env in tidy form, so that we can tidy the type they are free in Precondition: input free vars are closed over kinds and This function does a scopedSort, so that tidied variables have tidied kinds. See Note [Tidying is idempotent]

tidyOpenTypesX :: TidyEnv -> [Type] -> (TidyEnv, [Type]) Source #

Grabs the free type variables, tidies them and then uses tidyType to work over the type itself

tidyTopType :: Type -> Type Source #

Calls tidyType on a top-level type (i.e. with an empty tidying environment)

tidyType :: TidyEnv -> Type -> Type Source #

Tidy a Type

See Note [Strictness in tidyType and friends]

tidyTypes :: TidyEnv -> [Type] -> [Type] Source #

Tidy a list of Types

See Note [Strictness in tidyType and friends]

tidyVarBndrs :: TidyEnv -> [TyCoVar] -> (TidyEnv, [TyCoVar]) Source #

This tidies up a type for printing in an error message, or in an interface file.

It doesn't change the uniques at all, just the print names.

mkTyConTy :: TyCon -> Type Source #

(mkTyConTy tc) returns (TyConApp tc []) but arranges to share that TyConApp among all calls See Note [Sharing nullary TyConApps] So it's just an alias for tyConNullaryTy!

pattern ManyTy :: Mult Source #

pattern OneTy :: Mult Source #

appTyForAllTyFlags :: Type -> [Type] -> [ForAllTyFlag] Source #

Given a Type and a list of argument types to which the Type is applied, determine each argument's visibility (Inferred, Specified, or Required).

Most of the time, the arguments will be Required, but not always. Consider f :: forall a. a -> Type. In f Type Bool, the first argument (Type) is Specified and the second argument (Bool) is Required. It is precisely this sort of higher-rank situation in which appTyForAllTyFlags comes in handy, since f Type Bool would be represented in Core using AppTys. (See also #15792).

buildSynTyCon Source #

Arguments

:: Name 
-> [KnotTied TyConBinder] 
-> Kind

result kind

-> [Role] 
-> KnotTied Type 
-> TyCon 

chooseFunTyFlag :: HasDebugCallStack => Type -> Type -> FunTyFlag Source #

See GHC.Types.Var Note [FunTyFlag]

coAxNthLHS :: forall (br :: BranchFlag). CoAxiom br -> Int -> Type Source #

Get the type on the LHS of a coercion induced by a type/data family instance.

coreFullView :: Type -> Type Source #

Iterates coreView until there is no more to synonym to expand. NB: coreFullView is non-recursive and can be inlined; core_full_view is the recursive one See Note [Inlining coreView].

coreView :: Type -> Maybe Type Source #

This function strips off the top layer only of a type synonym application (if any) its underlying representation type. Returns Nothing if there is nothing to look through.

This function does not look through type family applications.

By being non-recursive and inlined, this case analysis gets efficiently joined onto the case analysis that the caller is already doing

dropForAlls :: Type -> Type Source #

Drops all ForAllTys

dropRuntimeRepArgs :: [Type] -> [Type] Source #

Drops prefix of RuntimeRep constructors in TyConApps. Useful for e.g. dropping 'LiftedRep arguments of unboxed tuple TyCon applications:

dropRuntimeRepArgs [ 'LiftedRep, 'IntRep , String, Int# ] == [String, Int#]

expandSynTyConApp_maybe :: TyCon -> [Type] -> Maybe Type Source #

expandSynTyConApp_maybe tc tys expands the RHS of type synonym tc instantiated at arguments tys, or returns Nothing if tc is not a synonym.

expandTypeSynonyms :: Type -> Type Source #

Expand out all type synonyms. Actually, it'd suffice to expand out just the ones that discard type variables (e.g. type Funny a = Int) But we don't know which those are currently, so we just expand all.

expandTypeSynonyms only expands out type synonyms mentioned in the type, not in the kinds of any TyCon or TyVar mentioned in the type.

Keep this synchronized with synonymTyConsOfType

filterOutInferredTypes :: TyCon -> [Type] -> [Type] Source #

Given a TyCon and a list of argument types, filter out any Inferred arguments.

filterOutInvisibleTypes :: TyCon -> [Type] -> [Type] Source #

Given a TyCon and a list of argument types, filter out any invisible (i.e., Inferred or Specified) arguments.

funArgTy :: HasDebugCallStack => Type -> Type Source #

Extract the function argument type and panic if that is not possible

Just like piResultTys but for a single argument Try not to iterate piResultTy, because it's inefficient to substitute one variable at a time; instead use 'piResultTys"

funResultTy :: HasDebugCallStack => Type -> Type Source #

Extract the function result type and panic if that is not possible

funTyConAppTy_maybe :: FunTyFlag -> Type -> Type -> Type -> Maybe (TyCon, [Type]) Source #

Given the components of a FunTy figure out the corresponding TyConApp.

getCastedTyVar_maybe :: Type -> Maybe (TyVar, CoercionN) Source #

If the type is a tyvar, possibly under a cast, returns it, along with the coercion. Thus, the co is :: kind tv ~N kind ty

getLevity :: HasDebugCallStack => Type -> Type Source #

Extract the Levity of a type. For example, getLevity Int = Lifted, or getLevity (Array# Int) = Unlifted.

Panics if this is not possible. Does not look through type family applications.

getRuntimeArgTys :: Type -> [(Scaled Type, FunTyFlag)] Source #

Extracts a list of run-time arguments from a function type, looking through newtypes to the right of arrows.

Examples:

   newtype Identity a = I a

   getRuntimeArgTys (Int -> Bool -> Double) == [(Int, FTF_T_T), (Bool, FTF_T_T)]
   getRuntimeArgTys (Identity Int -> Bool -> Double) == [(Identity Int, FTF_T_T), (Bool, FTF_T_T)]
   getRuntimeArgTys (Int -> Identity (Bool -> Identity Double)) == [(Int, FTF_T_T), (Bool, FTF_T_T)]
   getRuntimeArgTys (forall a. Show a => Identity a -> a -> Int -> Bool)
            == [(Show a, FTF_C_T), (Identity a, FTF_T_T),(a, FTF_T_T),(Int, FTF_T_T)]

Note that, in the last case, the returned types might mention an out-of-scope type variable. This function is used only when we really care about the kinds of the returned types, so this is OK.

  • *Warning**: this function can return an infinite list. For example:
  newtype N a = MkN (a -> N a)
  getRuntimeArgTys (N a) == repeat (a, FTF_T_T)

getRuntimeRep :: HasDebugCallStack => Type -> RuntimeRepType Source #

Extract the RuntimeRep classifier of a type. For instance, getRuntimeRep_maybe Int = LiftedRep. Panics if this is not possible.

getTyVar :: HasDebugCallStack => Type -> TyVar Source #

Attempts to obtain the type variable underlying a Type, and panics with the given message if this is not a type variable type. See also getTyVar_maybe

getTyVar_maybe :: Type -> Maybe TyVar Source #

Attempts to obtain the type variable underlying a Type

isAlgType :: Type -> Bool Source #

See Type for what an algebraic type is. Should only be applied to types, as opposed to e.g. partially saturated type constructors

isBoxedRuntimeRep :: RuntimeRepType -> Bool Source #

See isBoxedRuntimeRep_maybe.

isBoxedType :: Type -> Bool Source #

See Type for what a boxed type is. Panics on representation-polymorphic types; See mightBeUnliftedType for a more approximate predicate that behaves better in the presence of representation polymorphism.

isCharLitTy :: Type -> Maybe Char Source #

Is this a char literal? We also look through type synonyms.

isConcreteType :: Type -> Bool Source #

Tests whether the given type is concrete, i.e. it whether it consists only of concrete type constructors, concrete type variables, and applications.

See Note [Concrete types] in GHC.Tc.Utils.Concrete.

isDataFamilyAppType :: Type -> Bool Source #

Check whether a type is a data family type

isFixedRuntimeRepKind :: HasDebugCallStack => Kind -> Bool Source #

Checks that a kind of the form Type, Constraint or 'TYPE r is concrete. See isConcreteType.

Precondition: The type has kind `TYPE blah` or `CONSTRAINT blah`

isForAllTy :: Type -> Bool Source #

Checks whether this is a proper forall (with a named binder)

isForAllTy_co :: Type -> Bool Source #

Like isForAllTy, but returns True only if it is a covar binder

isForAllTy_invis_ty :: Type -> Bool Source #

Like isForAllTy, but returns True only if it is an inferred tyvar binder

isForAllTy_ty :: Type -> Bool Source #

Like isForAllTy, but returns True only if it is a tyvar binder

isFunTy :: Type -> Bool Source #

Is this a function? Note: `forall {b}. Show b => b -> IO b` will not be considered a function by this function. It would merely be a forall wrapping a function type.

isLevityTy :: Type -> Bool Source #

Is this the type Levity?

isLevityVar :: TyVar -> Bool Source #

Is a tyvar of type Levity?

isLiftedRuntimeRep :: RuntimeRepType -> Bool Source #

Check whether a type of kind RuntimeRep is lifted.

isLiftedRuntimeRep is:

  • True of LiftedRep :: RuntimeRep
  • False of type variables, type family applications, and of other reps such as IntRep :: RuntimeRep.

isLiftedTypeKind :: Kind -> Bool Source #

Returns True if the argument is (lifted) Type or Constraint See Note [TYPE and CONSTRAINT] in GHC.Builtin.Types.Prim

isLinearType :: Type -> Bool Source #

isLinear t returns True of a if t is a type of (curried) function where at least one argument is linear (or otherwise non-unrestricted). We use this function to check whether it is safe to eta reduce an Id in CorePrep. It is always safe to return True, because True deactivates the optimisation.

isLitTy :: Type -> Maybe TyLit Source #

Is this a type literal (symbol, numeric, or char)?

isMultiplicityTy :: Type -> Bool Source #

Is this the type Multiplicity?

isMultiplicityVar :: TyVar -> Bool Source #

Is a tyvar of type Multiplicity?

isNumLitTy :: Type -> Maybe Integer Source #

Is this a numeric literal. We also look through type synonyms.

isPiTy :: Type -> Bool Source #

Is this a function or forall?

isPrimitiveType :: Type -> Bool Source #

Returns true of types that are opaque to Haskell.

isRuntimeRepKindedTy :: Type -> Bool Source #

Is this a type of kind RuntimeRep? (e.g. LiftedRep)

isRuntimeRepTy :: Type -> Bool Source #

Is this the type RuntimeRep?

isRuntimeRepVar :: TyVar -> Bool Source #

Is a tyvar of type RuntimeRep?

isStrLitTy :: Type -> Maybe FastString Source #

Is this a symbol literal. We also look through type synonyms.

isStrictType :: HasDebugCallStack => Type -> Bool Source #

Computes whether an argument (or let right hand side) should be computed strictly or lazily, based only on its type. Currently, it's just isUnliftedType. Panics on representation-polymorphic types.

isTYPEorCONSTRAINT :: Kind -> Bool Source #

Does this classify a type allowed to have values? Responds True to things like *, TYPE Lifted, TYPE IntRep, TYPE v, Constraint.

True of a kind `TYPE _` or `CONSTRAINT _`

isTerminatingType :: HasDebugCallStack => Type -> Bool Source #

True = a term of this type cannot be bottom This identifies the types described by Note [NON-BOTTOM-DICTS invariant] in GHC.Core NB: unlifted types are not terminating types! e.g. you can write a term (loop 1)::Int# that diverges.

isTypeLikeKind :: Kind -> Bool Source #

Is this kind equivalent to TYPE r (for some unknown r)?

This considers Constraint to be distinct from *.

isUnliftedRuntimeRep :: RuntimeRepType -> Bool Source #

Check whether a type of kind RuntimeRep is unlifted.

  • True of definitely unlifted RuntimeReps such as UnliftedRep, IntRep, FloatRep, ...
  • False of LiftedRep,
  • False for type variables and type family applications.

isUnliftedType :: HasDebugCallStack => Type -> Bool Source #

Is the given type definitely unlifted? See Type for what an unlifted type is.

Panics on representation-polymorphic types; See mightBeUnliftedType for a more approximate predicate that behaves better in the presence of representation polymorphism.

isUnliftedTypeKind :: Kind -> Bool Source #

Returns True if the kind classifies unlifted types (like 'Int#') and False otherwise. Note that this returns False for representation-polymorphic kinds, which may be specialized to a kind that classifies unlifted types.

isValidJoinPointType :: JoinArity -> Type -> Bool Source #

Determine whether a type could be the type of a join point of given total arity, according to the polymorphism rule. A join point cannot be polymorphic in its return type, since given join j a b x y z = e1 in e2, the types of e1 and e2 must be the same, and a and b are not in scope for e2. (See Note [The polymorphism rule of join points] in GHC.Core.) Returns False also if the type simply doesn't have enough arguments.

Note that we need to know how many arguments (type *and* value) the putative join point takes; for instance, if j :: forall a. a -> Int then j could be a binary join point returning an Int, but it could *not* be a unary join point returning a -> Int.

TODO: See Note [Excess polymorphism and join points]

kindBoxedRepLevity_maybe :: Type -> Maybe Levity Source #

Check whether a kind is of the form `TYPE (BoxedRep Lifted)` or `TYPE (BoxedRep Unlifted)`.

Returns:

  • `Just Lifted` for `TYPE (BoxedRep Lifted)` and Type,
  • `Just Unlifted` for `TYPE (BoxedRep Unlifted)` and UnliftedType,
  • Nothing for anything else, e.g. `TYPE IntRep`, `TYPE (BoxedRep l)`, etc.

kindRep :: HasDebugCallStack => Kind -> RuntimeRepType Source #

Extract the RuntimeRep classifier of a type from its kind. For example, kindRep * = LiftedRep; Panics if this is not possible. Treats * and Constraint as the same

kindRep_maybe :: HasDebugCallStack => Kind -> Maybe RuntimeRepType Source #

Given a kind (TYPE rr) or (CONSTRAINT rr), extract its RuntimeRep classifier rr. For example, kindRep_maybe * = Just LiftedRep Returns Nothing if the kind is not of form (TYPE rr)

levityType_maybe :: LevityType -> Maybe Levity Source #

levityType_maybe takes a Type of kind Levity, and returns its levity May not be possible for a type variable or type family application

linear :: a -> Scaled a Source #

Scale a payload by One

mapTyCo :: Monad m => TyCoMapper () m -> (Type -> m Type, [Type] -> m [Type], Coercion -> m Coercion, [Coercion] -> m [Coercion]) Source #

mapTyCoX :: Monad m => TyCoMapper env m -> (env -> Type -> m Type, env -> [Type] -> m [Type], env -> Coercion -> m Coercion, env -> [Coercion] -> m [Coercion]) Source #

mightBeLiftedType :: Type -> Bool Source #

Returns:

  • False if the type is guaranteed unlifted or
  • True if it lifted, OR we aren't sure (e.g. in a representation-polymorphic case)

mightBeUnliftedType :: Type -> Bool Source #

Returns:

  • False if the type is guaranteed lifted or
  • True if it is unlifted, OR we aren't sure (e.g. in a representation-polymorphic case)

mkAppTy :: Type -> Type -> Type Source #

Applies a type to another, as in e.g. k a

mkBoxedRepApp_maybe :: LevityType -> Maybe Type Source #

Given a Levity, apply BoxedRep to it On the fly, rewrite BoxedRep Lifted --> liftedRepTy (a synonym) BoxedRep Unlifted --> unliftedRepTy (ditto) See Note [TYPE and CONSTRAINT] in GHC.Builtin.Types.Prim. See Note [Using synonyms to compress types] in GHC.Core.Type

mkCONSTRAINTapp :: RuntimeRepType -> Type Source #

Just like mkTYPEapp

mkCONSTRAINTapp_maybe :: RuntimeRepType -> Maybe Type Source #

Just like mkTYPEapp_maybe

mkCastTy :: Type -> Coercion -> Type Source #

Make a CastTy. The Coercion must be nominal. Checks the Coercion for reflexivity, dropping it if it's reflexive. See Note [Respecting definitional equality] in GHC.Core.TyCo.Rep

mkFamilyTyConApp :: TyCon -> [Type] -> Type Source #

Given a family instance TyCon and its arg types, return the corresponding family type. E.g:

data family T a
data instance T (Maybe b) = MkT b

Where the instance tycon is :RTL, so:

mkFamilyTyConApp :RTL Int  =  T (Maybe Int)

mkFunctionType :: HasDebugCallStack => Mult -> Type -> Type -> Type Source #

This one works out the FunTyFlag from the argument type See GHC.Types.Var Note [FunTyFlag]

mkInfForAllTy :: TyVar -> Type -> Type Source #

Like mkTyCoInvForAllTy, but tv should be a tyvar

mkInfForAllTys :: [TyVar] -> Type -> Type Source #

Like mkTyCoInvForAllTys, but tvs should be a list of tyvar

mkScaled :: Mult -> a -> Scaled a Source #

mkScaledFunctionTys :: [Scaled Type] -> Type -> Type Source #

Like mkFunctionType, compute the FunTyFlag from the arguments

mkSpecForAllTy :: TyVar -> Type -> Type Source #

Like mkForAllTy, but assumes the variable is dependent and Specified, a common case

mkSpecForAllTys :: [TyVar] -> Type -> Type Source #

Like mkForAllTys, but assumes all variables are dependent and Specified, a common case

mkTYPEapp_maybe :: RuntimeRepType -> Maybe Type Source #

Given a RuntimeRep, applies TYPE to it. On the fly it rewrites TYPE LiftedRep --> liftedTypeKind (a synonym) TYPE UnliftedRep --> unliftedTypeKind (ditto) TYPE ZeroBitRep --> zeroBitTypeKind (ditto) NB: no need to check for TYPE (BoxedRep Lifted), TYPE (BoxedRep Unlifted) because those inner types should already have been rewritten to LiftedRep and UnliftedRep respectively, by mkTyConApp

see Note [TYPE and CONSTRAINT] in GHC.Builtin.Types.Prim. See Note [Using synonyms to compress types] in GHC.Core.Type

mkTupleRepApp_maybe :: Type -> Maybe Type Source #

Given a `[RuntimeRep]`, apply TupleRep to it On the fly, rewrite TupleRep [] -> zeroBitRepTy (a synonym) See Note [TYPE and CONSTRAINT] in GHC.Builtin.Types.Prim. See Note [Using synonyms to compress types] in GHC.Core.Type

mkTyCoForAllTy :: TyCoVar -> ForAllTyFlag -> Type -> Type Source #

Make a dependent forall over a TyCoVar

mkTyCoForAllTys :: [ForAllTyBinder] -> Type -> Type Source #

Make a dependent forall over a TyCoVar

mkTyCoInvForAllTy :: TyCoVar -> Type -> Type Source #

Make a dependent forall over an Inferred variable

mkTyCoInvForAllTys :: [TyCoVar] -> Type -> Type Source #

Like mkForAllTys, but assumes all variables are dependent and Inferred, a common case

mkTyConApp :: TyCon -> [Type] -> Type Source #

A key function: builds a TyConApp or FunTy as appropriate to its arguments. Applies its arguments to the constructor from left to right.

mkTyConBindersPreferAnon Source #

Arguments

:: [TyVar]

binders

-> TyCoVarSet

free variables of result

-> [TyConBinder] 

Given a list of type-level vars and the free vars of a result kind, makes PiTyBinders, preferring anonymous binders if the variable is, in fact, not dependent. e.g. mkTyConBindersPreferAnon (k:*),(b:k),(c:k) We want (k:*) Named, (b:k) Anon, (c:k) Anon

All non-coercion binders are visible.

mkVisForAllTys :: [TyVar] -> Type -> Type Source #

Like mkForAllTys, but assumes all variables are dependent and visible

newTyConInstRhs :: TyCon -> [Type] -> Type Source #

Unwrap one layer of newtype on a type constructor and its arguments, using an eta-reduced version of the newtype if possible. This requires tys to have at least newTyConInstArity tycon elements.

partitionInvisibleTypes :: TyCon -> [Type] -> ([Type], [Type]) Source #

Given a TyCon and a list of argument types, partition the arguments into:

  1. Inferred or Specified (i.e., invisible) arguments and
  2. Required (i.e., visible) arguments

partitionInvisibles :: [(a, ForAllTyFlag)] -> ([a], [a]) Source #

Given a list of things paired with their visibilities, partition the things into (invisible things, visible things).

piResultTys :: HasDebugCallStack => Type -> [Type] -> Type Source #

(piResultTys f_ty [ty1, .., tyn]) gives the type of (f ty1 .. tyn) where f :: f_ty piResultTys is interesting because: 1. f_ty may have more for-alls than there are args 2. Less obviously, it may have fewer for-alls For case 2. think of: piResultTys (forall a.a) [forall b.b, Int] This really can happen, but only (I think) in situations involving undefined. For example: undefined :: forall a. a Term: undefined (forall b. b->b) Int This term should have type (Int -> Int), but notice that there are more type args than foralls in undefineds type.

pprUserTypeErrorTy :: ErrorMsgType -> SDoc Source #

Render a type corresponding to a user type error into a SDoc.

repGetTyVar_maybe :: Type -> Maybe TyVar Source #

Attempts to obtain the type variable underlying a Type, without any expansion

runtimeRepLevity_maybe :: RuntimeRepType -> Maybe Levity Source #

Check whether a type (usually of kind RuntimeRep) is lifted, unlifted, or unknown. Returns Nothing if the type isn't of kind RuntimeRep.

`runtimeRepLevity_maybe rr` returns:

  • `Just Lifted` if rr is `LiftedRep :: RuntimeRep`
  • `Just Unlifted` if rr is definitely unlifted, e.g. IntRep
  • Nothing if not known (e.g. it's a type variable or a type family application).

scaledSet :: Scaled a -> b -> Scaled b Source #

seqType :: Type -> () Source #

seqTypes :: [Type] -> () Source #

splitAppTy :: Type -> (Type, Type) Source #

Attempts to take a type application apart, as in splitAppTy_maybe, and panics if this is not possible

splitAppTyNoView_maybe :: HasDebugCallStack => Type -> Maybe (Type, Type) Source #

Does the AppTy split as in splitAppTy_maybe, but assumes that any coreView stuff is already done

splitAppTy_maybe :: Type -> Maybe (Type, Type) Source #

Attempt to take a type application apart, whether it is a function, type constructor, or plain type application. Note that type family applications are NEVER unsaturated by this!

splitAppTys :: HasDebugCallStack => Type -> (Type, [Type]) Source #

Recursively splits a type as far as is possible, leaving a residual type being applied to and the type arguments applied to it. Never fails, even if that means returning an empty list of type applications.

splitAppTysNoView :: HasDebugCallStack => Type -> (Type, [Type]) Source #

Like splitAppTys, but doesn't look through type synonyms

splitForAllCoVar_maybe :: Type -> Maybe (CoVar, Type) Source #

Like splitForAllTyCoVar_maybe, but only returns Just if it is a covar binder.

splitForAllForAllTyBinder_maybe :: Type -> Maybe (ForAllTyBinder, Type) Source #

Attempts to take a ForAllTy apart, returning the full ForAllTyBinder

splitForAllForAllTyBinders :: Type -> ([ForAllTyBinder], Type) Source #

Take a ForAllTy apart, returning the binders and result type

splitForAllInvisTyBinders :: Type -> ([InvisTyBinder], Type) Source #

Like splitForAllTyCoVars, but only splits ForAllTys with Invisible type variable binders. Furthermore, each returned tyvar is annotated with its Specificity.

splitForAllReqTyBinders :: Type -> ([ReqTyBinder], Type) Source #

Like splitForAllTyCoVars, but only splits ForAllTys with Required type variable binders. Furthermore, each returned tyvar is annotated with ().

splitForAllTyCoVar :: Type -> (TyCoVar, Type) Source #

Take a forall type apart, or panics if that is not possible.

splitForAllTyCoVar_maybe :: Type -> Maybe (TyCoVar, Type) Source #

Attempts to take a ForAllTy apart, returning the Var

splitForAllTyCoVars :: Type -> ([TyCoVar], Type) Source #

Take a ForAllTy apart, returning the list of tycovars and the result type. This always succeeds, even if it returns only an empty list. Note that the result type returned may have free variables that were bound by a forall.

splitForAllTyVar_maybe :: Type -> Maybe (TyVar, Type) Source #

Attempts to take a ForAllTy apart, but only if the binder is a TyVar

splitForAllTyVars :: Type -> ([TyVar], Type) Source #

Like splitForAllTyCoVars, but split only for tyvars. This always succeeds, even if it returns only an empty list. Note that the result type returned may have free variables that were bound by a forall.

splitFunTy :: Type -> (Mult, Type, Type) Source #

Attempts to extract the multiplicity, argument and result types from a type, and panics if that is not possible. See also splitFunTy_maybe

splitFunTy_maybe :: Type -> Maybe (FunTyFlag, Mult, Type, Type) Source #

Attempts to extract the multiplicity, argument and result types from a type

splitInvisPiTys :: Type -> ([PiTyBinder], Type) Source #

Like splitPiTys, but returns only *invisible* binders, including constraints. Stops at the first visible binder.

splitInvisPiTysN :: Int -> Type -> ([PiTyBinder], Type) Source #

Same as splitInvisPiTys, but stop when - you have found n PiTyBinders, - or you run out of invisible binders

splitPiTy :: Type -> (PiTyBinder, Type) Source #

Takes a forall type apart, or panics

splitPiTy_maybe :: Type -> Maybe (PiTyBinder, Type) Source #

Attempts to take a forall type apart; works with proper foralls and functions

splitPiTys :: Type -> ([PiTyBinder], Type) Source #

Split off all PiTyBinders to a type, splitting both proper foralls and functions

splitRuntimeRep_maybe :: RuntimeRepType -> Maybe (TyCon, [Type]) Source #

(splitRuntimeRep_maybe rr) takes a Type rr :: RuntimeRep, and returns the (TyCon,[Type]) for the RuntimeRep, if possible, where the TyCon is one of the promoted DataCons of RuntimeRep. Remember: the unique on TyCon that is a a promoted DataCon is the same as the unique on the DataCon See Note [Promoted data constructors] in GHC.Core.TyCon May not be possible if rr is a type variable or type family application

splitTyConApp :: Type -> (TyCon, [Type]) Source #

Attempts to tease a type apart into a type constructor and the application of a number of arguments to that constructor. Panics if that is not possible. See also splitTyConApp_maybe

splitTyConApp_maybe :: HasDebugCallStack => Type -> Maybe (TyCon, [Type]) Source #

Attempts to tease a type apart into a type constructor and the application of a number of arguments to that constructor

tcIsBoxedTypeKind :: Kind -> Bool Source #

Is this kind equivalent to TYPE (BoxedRep l) for some l :: Levity?

tcIsLiftedTypeKind :: Kind -> Bool Source #

Is this kind equivalent to Type i.e. TYPE LiftedRep?

tcSplitAppTyNoView_maybe :: Type -> Maybe (Type, Type) Source #

Just like splitAppTyNoView_maybe, but does not split (c => t) See Note [Decomposing fat arrow c=>t]

tcSplitTyConApp_maybe :: HasDebugCallStack => Type -> Maybe (TyCon, [Type]) Source #

tcSplitTyConApp_maybe splits a type constructor application into its type constructor and applied types.

Differs from splitTyConApp_maybe in that it does *not* split types headed with (=>), as that's not a TyCon in the type-checker.

Note that this may fail (in funTyConAppTy_maybe) in the case of a FunTy with an argument of unknown kind FunTy (e.g. `FunTy (a :: k) Int`, since the kind of a isn't of the form `TYPE rep`. This isn't usually a problem but may be temporarily the case during canonicalization: see Note [Decomposing FunTy] in GHC.Tc.Solver.Equality and Note [The Purely Kinded Type Invariant (PKTI)] in GHC.Tc.Gen.HsType, Wrinkle around FunTy

Consequently, you may need to zonk your type before using this function.

tyConAppArgs_maybe :: Type -> Maybe [Type] Source #

The same as snd . splitTyConApp

tyConAppFunCo_maybe :: HasDebugCallStack => Role -> TyCon -> [Coercion] -> Maybe Coercion Source #

Return Just if this TyConAppCo should be represented as a FunCo

tyConAppFunTy_maybe :: HasDebugCallStack => TyCon -> [Type] -> Maybe Type Source #

Return Just if this TyConApp should be represented as a FunTy

tyConAppNeedsKindSig Source #

Arguments

:: Bool

Should specified binders count towards injective positions in the kind of the TyCon? (If you're using visible kind applications, then you want True here.

-> TyCon 
-> Int

The number of args the TyCon is applied to.

-> Bool

Does T t_1 ... t_n need a kind signature? (Where n is the number of arguments)

Does a TyCon (that is applied to some number of arguments) need to be ascribed with an explicit kind signature to resolve ambiguity if rendered as a source-syntax type? (See Note [When does a tycon application need an explicit kind signature?] for a full explanation of what this function checks for.)

tyConAppTyConPicky_maybe :: Type -> Maybe TyCon Source #

Retrieve the tycon heading this type, if there is one. Does not look through synonyms.

tyConAppTyCon_maybe :: Type -> Maybe TyCon Source #

The same as fst . splitTyConApp We can short-cut the FunTy case

tyConForAllTyFlags :: TyCon -> [Type] -> [ForAllTyFlag] Source #

Given a TyCon and a list of argument types to which the TyCon is applied, determine each argument's visibility (Inferred, Specified, or Required).

Wrinkle: consider the following scenario:

T :: forall k. k -> k
tyConForAllTyFlags T [forall m. m -> m -> m, S, R, Q]

After substituting, we get

T (forall m. m -> m -> m) :: (forall m. m -> m -> m) -> forall n. n -> n -> n

Thus, the first argument is invisible, S is visible, R is invisible again, and Q is visible.

tymult :: a -> Scaled a Source #

Scale a payload by Many; used for type arguments in core

typeHasFixedRuntimeRep :: HasDebugCallStack => Type -> Bool Source #

Returns True if a type has a syntactically fixed runtime rep, as per Note [Fixed RuntimeRep] in GHC.Tc.Utils.Concrete.

This function is equivalent to `isFixedRuntimeRepKind . typeKind` but much faster.

Precondition: The type has kind (TYPE blah)

typeLevity_maybe :: HasDebugCallStack => Type -> Maybe Levity Source #

Tries to compute the Levity of the given type. Returns either a definite Levity, or Nothing if we aren't sure (e.g. the type is representation-polymorphic).

Panics if the kind does not have the shape TYPE r.

unrestricted :: a -> Scaled a Source #

Scale a payload by Many

userTypeError_maybe :: Type -> Maybe ErrorMsgType Source #

Is this type a custom user error? If so, give us the error message.

anonPiTyBinderType_maybe :: PiTyBinder -> Maybe Type Source #

Extract a relevant type, if there is one.

binderFlag :: VarBndr tv argf -> argf Source #

binderFlags :: [VarBndr tv argf] -> [argf] Source #

binderVar :: VarBndr tv argf -> tv Source #

binderVars :: [VarBndr tv argf] -> [tv] Source #

isAnonPiTyBinder :: PiTyBinder -> Bool Source #

Does this binder bind a variable that is not erased? Returns True for anonymous binders.

isInvisiblePiTyBinder :: PiTyBinder -> Bool Source #

Does this binder bind an invisible argument?

isTyVar :: Var -> Bool Source #

Is this a type-level (i.e., computationally irrelevant, thus erasable) variable? Satisfies isTyVar = not . isId.

isVisiblePiTyBinder :: PiTyBinder -> Bool Source #

Does this binder bind a visible argument?

mkForAllTyBinder :: vis -> TyCoVar -> VarBndr TyCoVar vis Source #

Make a named binder

mkForAllTyBinders :: vis -> [TyCoVar] -> [VarBndr TyCoVar vis] Source #

Make many named binders

mkTyVarBinder :: vis -> TyVar -> VarBndr TyVar vis Source #

Make a named binder var should be a type variable

mkTyVarBinders :: vis -> [TyVar] -> [VarBndr TyVar vis] Source #

Make many named binders Input vars should be type variables

isInvisibleForAllTyFlag :: ForAllTyFlag -> Bool Source #

Does this ForAllTyFlag classify an argument that is not written in Haskell?

isVisibleForAllTyFlag :: ForAllTyFlag -> Bool Source #

Does this ForAllTyFlag classify an argument that is written in Haskell?

type Kind = Type Source #

The key type representing kinds in the compiler.

type KindOrType = Type Source #

The key representation of types within the compiler

type KnotTied (ty :: k) = ty Source #

A type labeled KnotTied might have knot-tied tycons in it. See Note [Type checking recursive type and class declarations] in GHC.Tc.TyCl

type Mult = Type Source #

Mult is a type alias for Type.

Mult must contain Type because multiplicity variables are mere type variables (of kind Multiplicity) in Haskell. So the simplest implementation is to make Mult be Type.

Multiplicities can be formed with: - One: GHC.Types.One (= oneDataCon) - Many: GHC.Types.Many (= manyDataCon) - Multiplication: GHC.Types.MultMul (= multMulTyCon)

So that Mult feels a bit more structured, we provide pattern synonyms and smart constructors for these.

type PredType = Type Source #

A type of the form p of constraint kind represents a value whose type is the Haskell predicate p, where a predicate is what occurs before the => in a Haskell type.

We use PredType as documentation to mark those types that we guarantee to have this kind.

It can be expanded into its representation, but:

  • The type checker must treat it as opaque
  • The rest of the compiler treats it as transparent

Consider these examples:

f :: (Eq a) => a -> Int
g :: (?x :: Int -> Int) => a -> Int
h :: (r\l) => {r} => {l::Int | r}

Here the Eq a and ?x :: Int -> Int and rl are all called "predicates"

type RuntimeRepType = Type Source #

Type synonym used for types of kind RuntimeRep.

data Scaled a Source #

A shorthand for data with an attached Mult element (the multiplicity).

Instances

Instances details
Outputable a => Outputable (Scaled a) Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Scaled a -> SDoc Source #

Data a => Data (Scaled a) Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: Scaled a -> Constr #

dataTypeOf :: Scaled a -> DataType #

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

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

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

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

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

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

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

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

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

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

type ThetaType = [PredType] Source #

A collection of PredTypes

data TyCoFolder env a Source #

Constructors

TyCoFolder 

Fields

data Type Source #

Instances

Instances details
Outputable Type Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Type -> SDoc Source #

Data Type Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: Type -> Constr #

dataTypeOf :: Type -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq (DeBruijn Type) Source # 
Instance details

Defined in GHC.Core.Map.Type

type IdSubstEnv = IdEnv CoreExpr Source #

A substitution of Exprs for non-coercion Ids

data Subst Source #

Type & coercion & id substitution

The Subst data type defined in this module contains substitution for tyvar, covar and id. However, operations on IdSubstEnv (mapping from Id to CoreExpr) that require the definition of the Expr data type are defined in GHC.Core.Subst to avoid circular module dependency.

Instances

Instances details
Outputable Subst Source # 
Instance details

Defined in GHC.Core.TyCo.Subst

Methods

ppr :: Subst -> SDoc Source #

type TvSubstEnv = TyVarEnv Type Source #

A substitution of Types for TyVars and Kinds for KindVars

type ErrorMsgType = Type Source #

A type of kind ErrorMessage (from the TypeError module).

data TyCoMapper env (m :: Type -> Type) Source #

This describes how a "map" operation over a type/coercion should behave

Constructors

TyCoMapper 

Fields

type ForAllTyBinder = VarBndr TyCoVar ForAllTyFlag Source #

Variable Binder

A ForAllTyBinder is the binder of a ForAllTy It's convenient to define this synonym here rather its natural home in GHC.Core.TyCo.Rep, because it's used in GHC.Core.DataCon.hs-boot

A TyVarBinder is a binder with only TyVar

data FunTyFlag Source #

The non-dependent version of ForAllTyFlag. See Note [FunTyFlag] Appears here partly so that it's together with its friends ForAllTyFlag and ForallVisFlag, but also because it is used in IfaceType, rather early in the compilation chain

Constructors

FTF_T_T 
FTF_T_C 
FTF_C_T 
FTF_C_C 

Instances

Instances details
Binary FunTyFlag Source # 
Instance details

Defined in GHC.Types.Var

Outputable FunTyFlag Source # 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: FunTyFlag -> SDoc Source #

Data FunTyFlag Source # 
Instance details

Defined in GHC.Types.Var

Methods

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

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

toConstr :: FunTyFlag -> Constr #

dataTypeOf :: FunTyFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq FunTyFlag Source # 
Instance details

Defined in GHC.Types.Var

Ord FunTyFlag Source # 
Instance details

Defined in GHC.Types.Var

data PiTyBinder Source #

A PiTyBinder represents an argument to a function. PiTyBinders can be dependent (Named) or nondependent (Anon). They may also be visible or not. See Note [PiTyBinders]

Instances

Instances details
Outputable PiTyBinder Source # 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: PiTyBinder -> SDoc Source #

Data PiTyBinder Source # 
Instance details

Defined in GHC.Types.Var

Methods

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

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

toConstr :: PiTyBinder -> Constr #

dataTypeOf :: PiTyBinder -> DataType #

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

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

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

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

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

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

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

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

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

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

type TyCoVar = Id Source #

Type or Coercion Variable

type TyVar = Var Source #

Type or kind Variable

data Var Source #

Variable

Essentially a typed Name, that may also contain some additional information about the Var and its use sites.

Instances

Instances details
NamedThing Var Source # 
Instance details

Defined in GHC.Types.Var

HasOccName Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

occName :: Var -> OccName Source #

Uniquable Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

getUnique :: Var -> Unique Source #

Outputable Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: Var -> SDoc Source #

OutputableBndr Var Source # 
Instance details

Defined in GHC.Core.Ppr

Data Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

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

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

toConstr :: Var -> Constr #

dataTypeOf :: Var -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

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

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

Ord Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

compare :: Var -> Var -> Ordering #

(<) :: Var -> Var -> Bool #

(<=) :: Var -> Var -> Bool #

(>) :: Var -> Var -> Bool #

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

max :: Var -> Var -> Var #

min :: Var -> Var -> Var #

Eq (DeBruijn CoreAlt) Source # 
Instance details

Defined in GHC.Core.Map.Expr

Eq (DeBruijn CoreExpr) Source # 
Instance details

Defined in GHC.Core.Map.Expr

Eq (DeBruijn Var) Source # 
Instance details

Defined in GHC.Core.Map.Type

OutputableBndr (Id, TagSig) Source # 
Instance details

Defined in GHC.Stg.InferTags.TagSig

type Anno Id Source # 
Instance details

Defined in GHC.Hs.Extension

data ForAllTyFlag Source #

ForAllTyFlag

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, ForAllTyBinders, TyConBinders, and visibility] in GHC.Core.TyCo.Rep

Bundled Patterns

pattern Inferred :: ForAllTyFlag 
pattern Specified :: ForAllTyFlag 

Instances

Instances details
NFData ForAllTyFlag Source # 
Instance details

Defined in GHC.Hs.Specificity

Methods

rnf :: ForAllTyFlag -> () Source #

Binary ForAllTyFlag Source # 
Instance details

Defined in GHC.Hs.Specificity

Outputable ForAllTyFlag Source # 
Instance details

Defined in GHC.Hs.Specificity

Data ForAllTyFlag Source # 
Instance details

Defined in Language.Haskell.Syntax.Specificity

Methods

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

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

toConstr :: ForAllTyFlag -> Constr #

dataTypeOf :: ForAllTyFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq ForAllTyFlag Source # 
Instance details

Defined in Language.Haskell.Syntax.Specificity

Ord ForAllTyFlag Source # 
Instance details

Defined in Language.Haskell.Syntax.Specificity

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

Defined in GHC.Types.Var

data Specificity Source #

Whether an Invisible argument may appear in source Haskell.

Constructors

InferredSpec

the argument may not appear in source Haskell, it is only inferred.

SpecifiedSpec

the argument may appear in source Haskell, but isn't required.

Instances

Instances details
NFData Specificity Source # 
Instance details

Defined in GHC.Hs.Specificity

Methods

rnf :: Specificity -> () Source #

Binary Specificity Source # 
Instance details

Defined in GHC.Hs.Specificity

Data Specificity Source # 
Instance details

Defined in Language.Haskell.Syntax.Specificity

Methods

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

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

toConstr :: Specificity -> Constr #

dataTypeOf :: Specificity -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq Specificity Source # 
Instance details

Defined in Language.Haskell.Syntax.Specificity

Ord Specificity Source # 
Instance details

Defined in Language.Haskell.Syntax.Specificity

OutputableBndrFlag Specificity p Source # 
Instance details

Defined in GHC.Hs.Type

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

Defined in GHC.Types.Var

buildCoercion :: Type -> Type -> CoercionN Source #

Assuming that two types are the same, ignoring coercions, find a nominal coercion between the types. This is useful when optimizing transitivity over coercion applications, where splitting two AppCos might yield different kinds. See Note [EtaAppCo] in GHC.Core.Coercion.Opt.

castCoercionKind :: Coercion -> CoercionN -> CoercionN -> Coercion Source #

Creates a new coercion with both of its types casted by different casts castCoercionKind g h1 h2, where g :: t1 ~r t2, has type (t1 |> h1) ~r (t2 |> h2). h1 and h2 must be nominal. It calls coercionKindRole, so it's quite inefficient (which I stands for) Use castCoercionKind2 instead if t1, t2, and r are known beforehand.

castCoercionKind1 :: Coercion -> Role -> Type -> Type -> CoercionN -> Coercion Source #

castCoercionKind1 g r t1 t2 h = coercionKind g r t1 t2 h h That is, it's a specialised form of castCoercionKind, where the two kind coercions are identical castCoercionKind1 g r t1 t2 h, where g :: t1 ~r t2, has type (t1 |> h) ~r (t2 |> h). h must be nominal. See Note [castCoercionKind1]

castCoercionKind2 :: Coercion -> Role -> Type -> Type -> CoercionN -> CoercionN -> Coercion Source #

Creates a new coercion with both of its types casted by different casts castCoercionKind2 g r t1 t2 h1 h2, where g :: t1 ~r t2, has type (t1 |> h1) ~r (t2 |> h2). h1 and h2 must be nominal.

coercionKind :: Coercion -> Pair Type Source #

If it is the case that

c :: (t1 ~ t2)

i.e. the kind of c relates t1 and t2, then coercionKind c = Pair t1 t2.

coercionKindRole :: Coercion -> (Pair Type, Role) Source #

Get a coercion's kind and role.

coercionRole :: Coercion -> Role Source #

Retrieve the role from a coercion.

composeSteppers :: NormaliseStepper ev -> NormaliseStepper ev -> NormaliseStepper ev Source #

Try one stepper and then try the next, if the first doesn't make progress. So if it returns NS_Done, it means that both steppers are satisfied

decomposeCo :: Arity -> Coercion -> Infinite Role -> [Coercion] Source #

This breaks a Coercion with type T A B C ~ T D E F into a list of Coercions of kinds A ~ D, B ~ E and E ~ F. Hence:

decomposeCo 3 c [r1, r2, r3] = [nth r1 0 c, nth r2 1 c, nth r3 2 c]

downgradeRole :: Role -> Role -> Coercion -> Coercion Source #

Like downgradeRole_maybe, but panics if the change isn't a downgrade. See Note [Role twiddling functions]

eqCoercion :: Coercion -> Coercion -> Bool Source #

Syntactic equality of coercions

eqCoercionX :: RnEnv2 -> Coercion -> Coercion -> Bool Source #

Compare two Coercions, with respect to an RnEnv2

extendLiftingContext Source #

Arguments

:: LiftingContext

original LC

-> TyCoVar

new variable to map...

-> Coercion

...to this lifted version

-> LiftingContext 

Extend a lifting context with a new mapping.

extendLiftingContextAndInScope Source #

Arguments

:: LiftingContext

Original LC

-> TyCoVar

new variable to map...

-> Coercion

to this coercion

-> LiftingContext 

Extend a lifting context with a new mapping, and extend the in-scope set

extendLiftingContextCvSubst :: LiftingContext -> CoVar -> Coercion -> LiftingContext Source #

Extend the substitution component of a lifting context with a new binding for a coercion variable. Used during coercion optimisation.

getCoVar_maybe :: Coercion -> Maybe CoVar Source #

Extract a covar, if possible. This check is dirty. Be ashamed of yourself. (It's dirty because it cares about the structure of a coercion, which is morally reprehensible.)

getNthFun Source #

Arguments

:: FunSel 
-> a

multiplicity

-> a

argument

-> a

result

-> a

One of the above three

Extract the nth field of a FunCo

hasCoercionHoleCo :: Coercion -> Bool Source #

Is there a hetero-kind coercion hole in this coercion?

hasCoercionHoleTy :: Type -> Bool Source #

Is there a hetero-kind coercion hole in this type? (That is, a coercion hole with ch_hetero_kind=True.) See wrinkle (EIK2) of Note [Equalities with incompatible kinds] in GHC.Tc.Solver.Equality

instNewTyCon_maybe :: TyCon -> [Type] -> Maybe (Type, Coercion) Source #

If `instNewTyCon_maybe T ts = Just (rep_ty, co)` then `co :: T ts ~R# rep_ty`

Checks for a newtype, and for being saturated

isGReflCo :: Coercion -> Bool Source #

Tests if this coercion is obviously a generalized reflexive coercion. Guaranteed to work very quickly.

isGReflCo_maybe :: Coercion -> Maybe (Type, Role) Source #

Returns the type coerced if this coercion is a generalized reflexive coercion. Guaranteed to work very quickly.

isGReflMCo :: MCoercion -> Bool Source #

Tests if this MCoercion is obviously generalized reflexive Guaranteed to work very quickly.

isMappedByLC :: TyCoVar -> LiftingContext -> Bool Source #

Is a var in the domain of a lifting context?

isReflCo :: Coercion -> Bool Source #

Tests if this coercion is obviously reflexive. Guaranteed to work very quickly. Sometimes a coercion can be reflexive, but not obviously so. c.f. isReflexiveCo

isReflCo_maybe :: Coercion -> Maybe (Type, Role) Source #

Returns the type coerced if this coercion is reflexive. Guaranteed to work very quickly. Sometimes a coercion can be reflexive, but not obviously so. c.f. isReflexiveCo_maybe

isReflexiveCo :: Coercion -> Bool Source #

Slowly checks if the coercion is reflexive. Don't call this in a loop, as it walks over the entire coercion.

isReflexiveCo_maybe :: Coercion -> Maybe (Type, Role) Source #

Extracts the coerced type from a reflexive coercion. This potentially walks over the entire coercion, so avoid doing this in a loop.

lcLookupCoVar :: LiftingContext -> CoVar -> Maybe Coercion Source #

Lookup a CoVar in the substitution in a LiftingContext

liftCoSubst :: HasDebugCallStack => Role -> LiftingContext -> Type -> Coercion Source #

liftCoSubst role lc ty produces a coercion (at role role) that coerces between lc_left(ty) and lc_right(ty), where lc_left is a substitution mapping type variables to the left-hand types of the mapped coercions in lc, and similar for lc_right.

liftCoSubstVarBndrUsing Source #

Arguments

:: (r -> CoercionN)

coercion getter

-> (LiftingContext -> Type -> r)

callback

-> LiftingContext 
-> TyCoVar 
-> (LiftingContext, TyCoVar, r) 

mkAppCo Source #

Arguments

:: Coercion

:: t1 ~r t2

-> Coercion

:: s1 ~N s2, where s1 :: k1, s2 :: k2

-> Coercion

:: t1 s1 ~r t2 s2

Apply a Coercion to another Coercion. The second coercion must be Nominal, unless the first is Phantom. If the first is Phantom, then the second can be either Phantom or Nominal.

mkAppCos :: Coercion -> [Coercion] -> Coercion Source #

Applies multiple Coercions to another Coercion, from left to right. See also mkAppCo.

mkAxInstCo :: forall (br :: BranchFlag). Role -> CoAxiom br -> BranchIndex -> [Type] -> [Coercion] -> Coercion Source #

mkAxInstLHS :: forall (br :: BranchFlag). CoAxiom br -> BranchIndex -> [Type] -> [Coercion] -> Type Source #

Return the left-hand type of the axiom, when the axiom is instantiated at the types given.

mkAxInstRHS :: forall (br :: BranchFlag). CoAxiom br -> BranchIndex -> [Type] -> [Coercion] -> Type Source #

mkCastTyMCo :: Type -> MCoercion -> Type Source #

Cast a type by an MCoercion

mkCoercionType :: Role -> Type -> Type -> Type Source #

Makes a coercion type from two types: the types whose equality is proven by the relevant Coercion

mkCoherenceLeftCo :: Role -> Type -> CoercionN -> Coercion -> Coercion Source #

Given ty :: k1, co :: k1 ~ k2, co2:: ty ~r ty', produces @co' :: (ty |> co) ~r ty' It is not only a utility function, but it saves allocation when co is a GRefl coercion.

mkCoherenceRightCo :: Role -> Type -> CoercionN -> Coercion -> Coercion Source #

Given ty :: k1, co :: k1 ~ k2, co2:: ty' ~r ty, produces @co' :: ty' ~r (ty |> co) It is not only a utility function, but it saves allocation when co is a GRefl coercion.

mkForAllCo :: HasDebugCallStack => TyCoVar -> ForAllTyFlag -> ForAllTyFlag -> CoercionN -> Coercion -> Coercion Source #

Make a Coercion from a tycovar, a kind coercion, and a body coercion.

mkFunCo :: Role -> FunTyFlag -> CoercionN -> Coercion -> Coercion -> Coercion Source #

Build a function Coercion from two other Coercions. That is, given co1 :: a ~ b and co2 :: x ~ y produce co :: (a -> x) ~ (b -> y) or (a => x) ~ (b => y), depending on the kind of a/b. This (most common) version takes a single FunTyFlag, which is used for both fco_afl and ftf_afr of the FunCo

mkGReflCo :: Role -> Type -> MCoercionN -> Coercion Source #

Make a generalized reflexive coercion

mkGReflLeftCo :: Role -> Type -> CoercionN -> Coercion Source #

Given r, ty :: k1, and co :: k1 ~N k2, produces co' :: (ty |> co) ~r ty

mkGReflRightCo :: Role -> Type -> CoercionN -> Coercion Source #

Given ty :: k1, co :: k1 ~ k2, produces co' :: ty ~r (ty |> co)

mkHoleCo :: CoercionHole -> Coercion Source #

Make a coercion from a coercion hole

mkHomoForAllCos :: [ForAllTyBinder] -> Coercion -> Coercion Source #

Make a Coercion quantified over a type/coercion variable; the variable has the same kind and visibility in both sides of the coercion

mkInstCo :: Coercion -> CoercionN -> Coercion Source #

Instantiates a Coercion. Works for both tyvar and covar

mkKindCo :: Coercion -> Coercion Source #

Given co :: (a :: k) ~ (b :: k') produce co' :: k ~ k'.

mkNomPrimEqPred :: Kind -> Type -> Type -> Type Source #

Creates a primitive nominal type equality predicate with an explicit (but homogeneous) kind: (~#) k k ty1 ty2

mkNomReflCo :: Type -> Coercion Source #

Make a nominal reflexive coercion

mkPhantomCo :: Coercion -> Type -> Type -> Coercion Source #

Make a phantom coercion between two types. The coercion passed in must be a nominal coercion between the kinds of the types.

mkPiCo :: Role -> Var -> Coercion -> Coercion Source #

Make a forall Coercion, where both types related by the coercion are quantified over the same variable.

mkPrimEqPred :: Type -> Type -> Type Source #

Creates a primitive nominal type equality predicate. t1 ~# t2 Invariant: the types are not Coercions

mkPrimEqPredRole :: Role -> Type -> Type -> PredType Source #

Makes a lifted equality predicate at the given role

mkProofIrrelCo Source #

Arguments

:: Role

role of the created coercion, "r"

-> CoercionN

:: phi1 ~N phi2

-> Coercion

g1 :: phi1

-> Coercion

g2 :: phi2

-> Coercion

:: g1 ~r g2

Make a "coercion between coercions".

mkReflCo :: Role -> Type -> Coercion Source #

Make a reflexive coercion

mkRepReflCo :: Type -> Coercion Source #

Make a representational reflexive coercion

mkReprPrimEqPred :: Type -> Type -> Type Source #

Creates a primitive representational type equality predicate. t1 ~R# t2 Invariant: the types are not Coercions

mkRuntimeRepCo :: HasDebugCallStack => Coercion -> Coercion Source #

Given a coercion `co :: (t1 :: TYPE r1) ~ (t2 :: TYPE r2)` produce a coercion `rep_co :: r1 ~ r2` But actually it is possible that co :: (t1 :: CONSTRAINT r1) ~ (t2 :: CONSTRAINT r2) or co :: (t1 :: TYPE r1) ~ (t2 :: CONSTRAINT r2) or co :: (t1 :: CONSTRAINT r1) ~ (t2 :: TYPE r2) See Note [mkRuntimeRepCo]

mkSymCo :: Coercion -> Coercion Source #

Create a symmetric version of the given Coercion that asserts equality between the same types but in the other "direction", so a kind of t1 ~ t2 becomes the kind t2 ~ t1.

mkSymMCo :: MCoercion -> MCoercion Source #

Get the reverse of an MCoercion

mkTransCo :: Coercion -> Coercion -> Coercion Source #

Create a new Coercion by composing the two given Coercions transitively. (co1 ; co2)

mkTransMCo :: MCoercion -> MCoercion -> MCoercion Source #

Compose two MCoercions via transitivity

mkTyConAppCo :: HasDebugCallStack => Role -> TyCon -> [Coercion] -> Coercion Source #

Apply a type constructor to a list of coercions. It is the caller's responsibility to get the roles correct on argument coercions.

mkUnbranchedAxInstLHS :: CoAxiom Unbranched -> [Type] -> [Coercion] -> Type Source #

Instantiate the left-hand side of an unbranched axiom

mkUnivCo Source #

Arguments

:: UnivCoProvenance 
-> Role

role of the built coercion, "r"

-> Type

t1 :: k1

-> Type

t2 :: k2

-> Coercion

:: t1 ~r t2

Make a universal coercion between two arbitrary types.

pprCoAxiom :: forall (br :: BranchFlag). CoAxiom br -> SDoc Source #

promoteCoercion :: HasDebugCallStack => Coercion -> CoercionN Source #

like mkKindCo, but aggressively & recursively optimizes to avoid using a KindCo constructor. The output role is nominal.

setNominalRole_maybe :: Role -> Coercion -> Maybe CoercionN Source #

Converts a coercion to be nominal, if possible. See Note [Role twiddling functions]

splitAppCo_maybe :: Coercion -> Maybe (Coercion, Coercion) Source #

Attempt to take a coercion application apart.

swapLiftCoEnv :: LiftCoEnv -> LiftCoEnv Source #

Apply "sym" to all coercions in a LiftCoEnv

topNormaliseNewType_maybe :: Type -> Maybe (Coercion, Type) Source #

Sometimes we want to look through a newtype and get its associated coercion. This function strips off newtype layers enough to reveal something that isn't a newtype. Specifically, here's the invariant:

topNormaliseNewType_maybe rec_nts ty = Just (co, ty')

then (a) co : ty ~R ty'. (b) ty' is not a newtype.

The function returns Nothing for non-newtypes, or unsaturated applications

This function does *not* look through type families, because it has no access to the type family environment. If you do have that at hand, consider to use topNormaliseType_maybe, which should be a drop-in replacement for topNormaliseNewType_maybe If topNormliseNewType_maybe ty = Just (co, ty'), then co : ty ~R ty'

topNormaliseTypeX :: NormaliseStepper ev -> (ev -> ev -> ev) -> Type -> Maybe (ev, Type) Source #

A general function for normalising the top-level of a type. It continues to use the provided NormaliseStepper until that function fails, and then this function returns. The roles of the coercions produced by the NormaliseStepper must all be the same, which is the role returned from the call to topNormaliseTypeX.

Typically ev is Coercion.

If topNormaliseTypeX step plus ty = Just (ev, ty') then ty ~ev1~ t1 ~ev2~ t2 ... ~evn~ ty' and ev = ev1 plus ev2 plus ... plus evn If it returns Nothing then no newtype unwrapping could happen

unwrapNewTypeStepper :: NormaliseStepper Coercion Source #

A NormaliseStepper that unwraps newtypes, careful not to fall into a loop. If it would fall into a loop, it produces NS_Abort.

zapLiftingContext :: LiftingContext -> LiftingContext Source #

Erase the environments in a lifting context

tyCoVarsOfCoDSet :: Coercion -> DTyCoVarSet Source #

Get a deterministic set of the vars free in a coercion

substCoWith :: HasDebugCallStack => [TyVar] -> [Type] -> Coercion -> Coercion Source #

Coercion substitution, see zipTvSubst

substCos :: HasDebugCallStack => Subst -> [Coercion] -> [Coercion] Source #

Substitute within several Coercions The substitution has to satisfy the invariants described in Note [The substitution invariant].

tidyCo :: TidyEnv -> Coercion -> Coercion Source #

Tidy a Coercion

See Note [Strictness in tidyType and friends]

pickLR :: LeftOrRight -> (a, a) -> a Source #

isCoVar :: Var -> Bool Source #

Is this a coercion variable? Satisfies isId v ==> isCoVar v == not (isNonCoVarId v).

data LiftingContext Source #

Constructors

LC Subst LiftCoEnv 

Instances

Instances details
Outputable LiftingContext Source # 
Instance details

Defined in GHC.Core.Coercion

data NormaliseStepResult ev Source #

The result of stepping in a normalisation function. See topNormaliseTypeX.

Constructors

NS_Done

Nothing more to do

NS_Abort

Utter failure. The outer function should fail too.

NS_Step RecTcChecker Type ev

We stepped, yielding new bits; ^ ev is evidence; Usually a co :: old type ~ new type

Instances

Instances details
Functor NormaliseStepResult Source # 
Instance details

Defined in GHC.Core.Coercion

Outputable ev => Outputable (NormaliseStepResult ev) Source # 
Instance details

Defined in GHC.Core.Coercion

type NormaliseStepper ev = RecTcChecker -> TyCon -> [Type] -> NormaliseStepResult ev Source #

A function to check if we can reduce a type by one step. Used with topNormaliseTypeX.

data CoSel Source #

Instances

Instances details
NFData CoSel Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

rnf :: CoSel -> () Source #

Binary CoSel Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Outputable CoSel Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: CoSel -> SDoc Source #

Data CoSel Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: CoSel -> Constr #

dataTypeOf :: CoSel -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq CoSel Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

Ord CoSel Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

compare :: CoSel -> CoSel -> Ordering #

(<) :: CoSel -> CoSel -> Bool #

(<=) :: CoSel -> CoSel -> Bool #

(>) :: CoSel -> CoSel -> Bool #

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

max :: CoSel -> CoSel -> CoSel #

min :: CoSel -> CoSel -> CoSel #

data Coercion Source #

A Coercion is concrete evidence of the equality/convertibility of two types.

Instances

Instances details
Outputable Coercion Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Coercion -> SDoc Source #

Data Coercion Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: Coercion -> Constr #

dataTypeOf :: Coercion -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq (DeBruijn Coercion) Source # 
Instance details

Defined in GHC.Core.Map.Type

data CoercionHole Source #

A coercion to be filled in by the type-checker. See Note [Coercion holes]

Instances

Instances details
Uniquable CoercionHole Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Outputable CoercionHole Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Data CoercionHole Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: CoercionHole -> Constr #

dataTypeOf :: CoercionHole -> DataType #

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

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

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

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

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

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

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

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

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

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

data FunSel Source #

Constructors

SelMult 
SelArg 
SelRes 

Instances

Instances details
Outputable FunSel Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: FunSel -> SDoc Source #

Data FunSel Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: FunSel -> Constr #

dataTypeOf :: FunSel -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq FunSel Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

Ord FunSel Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

data MCoercion Source #

A semantically more meaningful type to represent what may or may not be a useful Coercion.

Constructors

MRefl 
MCo Coercion 

Instances

Instances details
Outputable MCoercion Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: MCoercion -> SDoc Source #

Data MCoercion Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: MCoercion -> Constr #

dataTypeOf :: MCoercion -> DataType #

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

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

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

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

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

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

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

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

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

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

data UnivCoProvenance Source #

For simplicity, we have just one UnivCo that represents a coercion from some type to some other type, with (in general) no restrictions on the type. The UnivCoProvenance specifies more exactly what the coercion really is and why a program should (or shouldn't!) trust the coercion. It is reasonable to consider each constructor of UnivCoProvenance as a totally independent coercion form; their only commonality is that they don't tell you what types they coercion between. (That info is in the UnivCo constructor of Coercion.

Instances

Instances details
Outputable UnivCoProvenance Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Data UnivCoProvenance Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: UnivCoProvenance -> Constr #

dataTypeOf :: UnivCoProvenance -> DataType #

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

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

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

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

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

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

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

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

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

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

type CvSubstEnv = CoVarEnv Coercion Source #

A substitution of Coercions for CoVars

data LeftOrRight Source #

Constructors

CLeft 
CRight 

Instances

Instances details
Binary LeftOrRight Source # 
Instance details

Defined in GHC.Types.Basic

Outputable LeftOrRight Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: LeftOrRight -> SDoc Source #

Data LeftOrRight Source # 
Instance details

Defined in GHC.Types.Basic

Methods

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

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

toConstr :: LeftOrRight -> Constr #

dataTypeOf :: LeftOrRight -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq LeftOrRight Source # 
Instance details

Defined in GHC.Types.Basic

Ord LeftOrRight Source # 
Instance details

Defined in GHC.Types.Basic

type CoVar = Id Source #

Coercion Variable

type TyCoVar = Id Source #

Type or Coercion Variable

data Var Source #

Variable

Essentially a typed Name, that may also contain some additional information about the Var and its use sites.

Instances

Instances details
NamedThing Var Source # 
Instance details

Defined in GHC.Types.Var

HasOccName Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

occName :: Var -> OccName Source #

Uniquable Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

getUnique :: Var -> Unique Source #

Outputable Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: Var -> SDoc Source #

OutputableBndr Var Source # 
Instance details

Defined in GHC.Core.Ppr

Data Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

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

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

toConstr :: Var -> Constr #

dataTypeOf :: Var -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

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

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

Ord Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

compare :: Var -> Var -> Ordering #

(<) :: Var -> Var -> Bool #

(<=) :: Var -> Var -> Bool #

(>) :: Var -> Var -> Bool #

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

max :: Var -> Var -> Var #

min :: Var -> Var -> Var #

Eq (DeBruijn CoreAlt) Source # 
Instance details

Defined in GHC.Core.Map.Expr

Eq (DeBruijn CoreExpr) Source # 
Instance details

Defined in GHC.Core.Map.Expr

Eq (DeBruijn Var) Source # 
Instance details

Defined in GHC.Core.Map.Type

OutputableBndr (Id, TagSig) Source # 
Instance details

Defined in GHC.Stg.InferTags.TagSig

type Anno Id Source # 
Instance details

Defined in GHC.Hs.Extension

data Role Source #

See Note [Roles] in GHC.Core.Coercion

Order of constructors matters: the Ord instance coincides with the *super*typing relation on roles.

Instances

Instances details
Binary Role Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Outputable Role Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

ppr :: Role -> SDoc Source #

Data Role Source # 
Instance details

Defined in Language.Haskell.Syntax.Basic

Methods

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

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

toConstr :: Role -> Constr #

dataTypeOf :: Role -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq Role Source # 
Instance details

Defined in Language.Haskell.Syntax.Basic

Methods

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

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

Ord Role Source # 
Instance details

Defined in Language.Haskell.Syntax.Basic

Methods

compare :: Role -> Role -> Ordering #

(<) :: Role -> Role -> Bool #

(<=) :: Role -> Role -> Bool #

(>) :: Role -> Role -> Bool #

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

max :: Role -> Role -> Role #

min :: Role -> Role -> Role #

type Anno (Maybe Role) Source # 
Instance details

Defined in GHC.Hs.Decls

class Uniquable a where Source #

Class of things that we can obtain a Unique from

Methods

getUnique :: a -> Unique Source #

Instances

Instances details
Uniquable Label Source # 
Instance details

Defined in GHC.Cmm.Dataflow.Label

Uniquable LocalReg Source # 
Instance details

Defined in GHC.Cmm.Reg

Uniquable Reg Source #

so we can put regs in UniqSets

Instance details

Defined in GHC.CmmToAsm.Reg.Graph.Base

Methods

getUnique :: Reg -> Unique Source #

Uniquable SymName Source # 
Instance details

Defined in GHC.CmmToAsm.Wasm.Types

Uniquable Class Source # 
Instance details

Defined in GHC.Core.Class

Uniquable CoAxiomRule Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Uniquable ConLike Source # 
Instance details

Defined in GHC.Core.ConLike

Uniquable DataCon Source # 
Instance details

Defined in GHC.Core.DataCon

Uniquable PatSyn Source # 
Instance details

Defined in GHC.Core.PatSyn

Uniquable CoercionHole Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Uniquable TyCon Source # 
Instance details

Defined in GHC.Core.TyCon

Uniquable FastString Source # 
Instance details

Defined in GHC.Types.Unique

Uniquable Ident Source # 
Instance details

Defined in GHC.JS.Ident

Uniquable RealReg Source # 
Instance details

Defined in GHC.Platform.Reg

Uniquable Reg Source # 
Instance details

Defined in GHC.Platform.Reg

Methods

getUnique :: Reg -> Unique Source #

Uniquable VirtualReg Source # 
Instance details

Defined in GHC.Platform.Reg

Uniquable RegClass Source # 
Instance details

Defined in GHC.Platform.Reg.Class

Uniquable EvBindsVar Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Uniquable SkolemInfo Source # 
Instance details

Defined in GHC.Tc.Types.Origin

Uniquable ConLikeName Source # 
Instance details

Defined in GHC.Types.GREInfo

Uniquable Name Source # 
Instance details

Defined in GHC.Types.Name

Uniquable NameSpace Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Uniquable Unique Source # 
Instance details

Defined in GHC.Types.Unique

Uniquable Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

getUnique :: Var -> Unique Source #

Uniquable PackageId Source # 
Instance details

Defined in GHC.Unit.Info

Uniquable PackageName Source # 
Instance details

Defined in GHC.Unit.Info

Uniquable WarningCategory Source # 
Instance details

Defined in GHC.Unit.Module.Warnings

Uniquable Module Source # 
Instance details

Defined in GHC.Unit.Types

Uniquable UnitId Source # 
Instance details

Defined in GHC.Unit.Types

Uniquable FieldLabelString Source # 
Instance details

Defined in GHC.Types.FieldLabel

Uniquable ModuleName Source # 
Instance details

Defined in GHC.Types.Unique

Uniquable Int Source # 
Instance details

Defined in GHC.Types.Unique

Methods

getUnique :: Int -> Unique Source #

Uniquable (CoAxiom br) Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

getUnique :: CoAxiom br -> Unique Source #

Uniquable unit => Uniquable (Definite unit) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: Definite unit -> Unique Source #

IsUnitId u => Uniquable (GenUnit u) Source # 
Instance details

Defined in GHC.Unit.Types

data Unique Source #

Unique identifier.

The type of unique identifiers that are used in many places in GHC for fast ordering and equality tests. You should generate these with the functions from the UniqSupply module

These are sometimes also referred to as "keys" in comments in GHC.

Instances

Instances details
Uniquable Unique Source # 
Instance details

Defined in GHC.Types.Unique

Outputable Unique Source # 
Instance details

Defined in GHC.Types.Unique

Methods

ppr :: Unique -> SDoc Source #

Show Unique Source # 
Instance details

Defined in GHC.Types.Unique

Eq Unique Source # 
Instance details

Defined in GHC.Types.Unique

Methods

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

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

data Messages e Source #

A collection of messages emitted by GHC during error reporting. A diagnostic message is typically a warning or an error. See Note [Messages].

INVARIANT: All the messages in this collection must be relevant, i.e. their Severity should not be SevIgnore. The smart constructor mkMessages will filter out any message which Severity is SevIgnore.

Instances

Instances details
Functor Messages Source # 
Instance details

Defined in GHC.Types.Error

Methods

fmap :: (a -> b) -> Messages a -> Messages b #

(<$) :: a -> Messages b -> Messages a #

Foldable Messages Source # 
Instance details

Defined in GHC.Types.Error

Methods

fold :: Monoid m => Messages m -> m #

foldMap :: Monoid m => (a -> m) -> Messages a -> m #

foldMap' :: Monoid m => (a -> m) -> Messages a -> m #

foldr :: (a -> b -> b) -> b -> Messages a -> b #

foldr' :: (a -> b -> b) -> b -> Messages a -> b #

foldl :: (b -> a -> b) -> b -> Messages a -> b #

foldl' :: (b -> a -> b) -> b -> Messages a -> b #

foldr1 :: (a -> a -> a) -> Messages a -> a #

foldl1 :: (a -> a -> a) -> Messages a -> a #

toList :: Messages a -> [a] #

null :: Messages a -> Bool #

length :: Messages a -> Int #

elem :: Eq a => a -> Messages a -> Bool #

maximum :: Ord a => Messages a -> a #

minimum :: Ord a => Messages a -> a #

sum :: Num a => Messages a -> a #

product :: Num a => Messages a -> a #

Traversable Messages Source # 
Instance details

Defined in GHC.Types.Error

Methods

traverse :: Applicative f => (a -> f b) -> Messages a -> f (Messages b) #

sequenceA :: Applicative f => Messages (f a) -> f (Messages a) #

mapM :: Monad m => (a -> m b) -> Messages a -> m (Messages b) #

sequence :: Monad m => Messages (m a) -> m (Messages a) #

Diagnostic e => ToJson (Messages e) Source # 
Instance details

Defined in GHC.Types.Error

Methods

json :: Messages e -> JsonDoc Source #

Diagnostic e => Outputable (Messages e) Source # 
Instance details

Defined in GHC.Types.Error

Methods

ppr :: Messages e -> SDoc Source #

Monoid (Messages e) Source # 
Instance details

Defined in GHC.Types.Error

Methods

mempty :: Messages e #

mappend :: Messages e -> Messages e -> Messages e #

mconcat :: [Messages e] -> Messages e #

Semigroup (Messages e) Source # 
Instance details

Defined in GHC.Types.Error

Methods

(<>) :: Messages e -> Messages e -> Messages e #

sconcat :: NonEmpty (Messages e) -> Messages e #

stimes :: Integral b => b -> Messages e -> Messages e #

Getting Names

thNameToGhcName :: Name -> CoreM (Maybe Name) Source #

Attempt to convert a Template Haskell name to one that GHC can understand. Original TH names such as those you get when you use the 'foo syntax will be translated to their equivalent GHC name exactly. Qualified or unqualified TH names will be dynamically bound to names in the module being compiled, if possible. Exact TH names will be bound to the name they represent, exactly.

thNameToGhcNameIO :: NameCache -> Name -> IO (Maybe Name) Source #

Attempt to convert a Template Haskell name to one that GHC can understand. Original TH names such as those you get when you use the 'foo syntax will be translated to their equivalent GHC name exactly. Qualified or unqualified TH names will be dynamically bound to names in the module being compiled, if possible. Exact TH names will be bound to the name they represent, exactly.

One must be careful to consistently use the same NameCache to create identifier that might be compared. (C.f. how the ST Monad enforces that variables from separate runST invocations are never intermingled; it would be valid to use the same tricks for Names and NameCaches.)

For now, the easiest and recommended way to ensure a consistent NameCache is used it to retrieve the preexisting one from an active HscEnv. A single HscEnv is created per GHC "session", and this ensures everything in that session will get the same name cache.

Orphan instances