ghc-8.6.4: The GHC API

Safe HaskellNone
LanguageHaskell2010

GhcPlugins

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 GhcPlugins".

Particularly interesting modules for plugin writers include CoreSyn and CoreMonad.

Synopsis

Documentation

module Plugins

module RdrName

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

Defined in OccName

Methods

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

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

Data OccName # 
Instance details

Defined in OccName

Methods

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

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

toConstr :: OccName -> Constr Source #

dataTypeOf :: OccName -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord OccName # 
Instance details

Defined in OccName

NFData OccName # 
Instance details

Defined in OccName

Methods

rnf :: OccName -> () Source #

OutputableBndr OccName # 
Instance details

Defined in OccName

Outputable OccName # 
Instance details

Defined in OccName

Uniquable OccName # 
Instance details

Defined in OccName

Binary OccName # 
Instance details

Defined in OccName

HasOccName OccName # 
Instance details

Defined in OccName

type FastStringEnv a = UniqFM a Source #

A non-deterministic set of FastStrings. See Note [Deterministic UniqFM] in UniqDFM 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 OccEnv a Source #

Instances
Data a => Data (OccEnv a) # 
Instance details

Defined in OccName

Methods

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

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

toConstr :: OccEnv a -> Constr Source #

dataTypeOf :: OccEnv a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

Defined in OccName

Methods

ppr :: OccEnv a -> SDoc Source #

pprPrec :: Rational -> OccEnv a -> SDoc Source #

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
HasOccName Name # 
Instance details

Defined in Name

Methods

occName :: Name -> OccName Source #

HasOccName OccName # 
Instance details

Defined in OccName

HasOccName GlobalRdrElt # 
Instance details

Defined in TcHoleErrors

HasOccName RdrName # 
Instance details

Defined in RdrName

HasOccName Var # 
Instance details

Defined in Var

Methods

occName :: Var -> OccName Source #

HasOccName IfaceConDecl # 
Instance details

Defined in IfaceSyn

HasOccName IfaceClassOp # 
Instance details

Defined in IfaceSyn

HasOccName IfaceDecl # 
Instance details

Defined in IfaceSyn

HasOccName TcBinder # 
Instance details

Defined in TcRnTypes

HasOccName name => HasOccName (IEWrappedName name) # 
Instance details

Defined in HsImpExp

(HasOccName a, HasOccName b) => HasOccName (Either a b) # 
Instance details

Defined in TcHoleErrors

Methods

occName :: Either a b -> OccName Source #

data NameSpace Source #

Instances
Eq NameSpace # 
Instance details

Defined in OccName

Ord NameSpace # 
Instance details

Defined in OccName

Binary NameSpace # 
Instance details

Defined in OccName

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

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

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

extendOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccName -> a -> OccEnv a Source #

extendOccEnv_Acc :: (a -> b -> b) -> (a -> b) -> OccEnv b -> OccName -> a -> OccEnv b Source #

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

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

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

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

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

isValOcc :: OccName -> Bool Source #

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

isDataSymOcc :: OccName -> Bool Source #

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

isSymOcc :: OccName -> Bool Source #

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

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

Wrap parens around an operator

startsWithUnderscore :: OccName -> Bool Source #

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

isDerivedOccName :: OccName -> Bool Source #

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

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 TcTypeable.

mkSuperDictSelOcc Source #

Arguments

:: Int

Index of superclass, e.g. 3

-> OccName

Class, e.g. Ord

-> OccName

Derived Occname, e.g. $p3Ord

mkLocalOcc Source #

Arguments

:: Unique

Unique to combine with the OccName

-> OccName

Local name, e.g. sat

-> OccName

Nice unique version, e.g. $L23sat

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.

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

mkDataTOcc Source #

Arguments

:: OccName

TyCon or data con string

-> OccSet

avoid these Occs

-> OccName

E.g. $f3OrdMaybe data T = MkT ... deriving( Data ) needs definitions for $tT :: Data.Generics.Basics.DataType $cMkT :: Data.Generics.Basics.Constr

mkDataCOcc Source #

Arguments

:: OccName

TyCon or data con string

-> OccSet

avoid these Occs

-> OccName

E.g. $f3OrdMaybe data T = MkT ... deriving( Data ) needs definitions for $tT :: Data.Generics.Basics.DataType $cMkT :: Data.Generics.Basics.Constr

data Name Source #

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

Instances
Eq Name #

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

Instance details

Defined in Name

Methods

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

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

Data Name # 
Instance details

Defined in Name

Methods

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

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

toConstr :: Name -> Constr Source #

dataTypeOf :: Name -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord Name #

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 trac #15240 for a bug caused by improper use of this instance.

Instance details

Defined in 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 #

NFData Name # 
Instance details

Defined in Name

Methods

rnf :: Name -> () Source #

OutputableBndr Name # 
Instance details

Defined in Name

Outputable Name # 
Instance details

Defined in Name

Uniquable Name # 
Instance details

Defined in Name

Binary Name #

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 Name

HasOccName Name # 
Instance details

Defined in Name

Methods

occName :: Name -> OccName Source #

NamedThing Name # 
Instance details

Defined in Name

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

Defined in OccName

Methods

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

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

Data OccName # 
Instance details

Defined in OccName

Methods

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

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

toConstr :: OccName -> Constr Source #

dataTypeOf :: OccName -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord OccName # 
Instance details

Defined in OccName

NFData OccName # 
Instance details

Defined in OccName

Methods

rnf :: OccName -> () Source #

OutputableBndr OccName # 
Instance details

Defined in OccName

Outputable OccName # 
Instance details

Defined in OccName

Uniquable OccName # 
Instance details

Defined in OccName

Binary OccName # 
Instance details

Defined in OccName

HasOccName OccName # 
Instance details

Defined in OccName

type FastStringEnv a = UniqFM a Source #

A non-deterministic set of FastStrings. See Note [Deterministic UniqFM] in UniqDFM 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 OccEnv a Source #

Instances
Data a => Data (OccEnv a) # 
Instance details

Defined in OccName

Methods

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

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

toConstr :: OccEnv a -> Constr Source #

dataTypeOf :: OccEnv a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

Defined in OccName

Methods

ppr :: OccEnv a -> SDoc Source #

pprPrec :: Rational -> OccEnv a -> SDoc Source #

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
HasOccName Name # 
Instance details

Defined in Name

Methods

occName :: Name -> OccName Source #

HasOccName OccName # 
Instance details

Defined in OccName

HasOccName GlobalRdrElt # 
Instance details

Defined in TcHoleErrors

HasOccName RdrName # 
Instance details

Defined in RdrName

HasOccName Var # 
Instance details

Defined in Var

Methods

occName :: Var -> OccName Source #

HasOccName IfaceConDecl # 
Instance details

Defined in IfaceSyn

HasOccName IfaceClassOp # 
Instance details

Defined in IfaceSyn

HasOccName IfaceDecl # 
Instance details

Defined in IfaceSyn

HasOccName TcBinder # 
Instance details

Defined in TcRnTypes

HasOccName name => HasOccName (IEWrappedName name) # 
Instance details

Defined in HsImpExp

(HasOccName a, HasOccName b) => HasOccName (Either a b) # 
Instance details

Defined in TcHoleErrors

Methods

occName :: Either a b -> OccName Source #

data NameSpace Source #

Instances
Eq NameSpace # 
Instance details

Defined in OccName

Ord NameSpace # 
Instance details

Defined in OccName

Binary NameSpace # 
Instance details

Defined in OccName

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

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

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

extendOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccName -> a -> OccEnv a Source #

extendOccEnv_Acc :: (a -> b -> b) -> (a -> b) -> OccEnv b -> OccName -> a -> OccEnv b Source #

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

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

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

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

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

isValOcc :: OccName -> Bool Source #

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

isDataSymOcc :: OccName -> Bool Source #

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

isSymOcc :: OccName -> Bool Source #

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

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

Wrap parens around an operator

startsWithUnderscore :: OccName -> Bool Source #

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

isDerivedOccName :: OccName -> Bool Source #

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

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 TcTypeable.

mkSuperDictSelOcc Source #

Arguments

:: Int

Index of superclass, e.g. 3

-> OccName

Class, e.g. Ord

-> OccName

Derived Occname, e.g. $p3Ord

mkLocalOcc Source #

Arguments

:: Unique

Unique to combine with the OccName

-> OccName

Local name, e.g. sat

-> OccName

Nice unique version, e.g. $L23sat

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.

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

mkDataTOcc Source #

Arguments

:: OccName

TyCon or data con string

-> OccSet

avoid these Occs

-> OccName

E.g. $f3OrdMaybe data T = MkT ... deriving( Data ) needs definitions for $tT :: Data.Generics.Basics.DataType $cMkT :: Data.Generics.Basics.Constr

mkDataCOcc Source #

Arguments

:: OccName

TyCon or data con string

-> OccSet

avoid these Occs

-> OccName

E.g. $f3OrdMaybe data T = MkT ... deriving( Data ) needs definitions for $tT :: Data.Generics.Basics.DataType $cMkT :: Data.Generics.Basics.Constr

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
NamedThing Name # 
Instance details

Defined in Name

NamedThing TyCon # 
Instance details

Defined in TyCon

NamedThing TyThing # 
Instance details

Defined in TyCoRep

NamedThing Var # 
Instance details

Defined in Var

NamedThing PatSyn # 
Instance details

Defined in PatSyn

NamedThing DataCon # 
Instance details

Defined in DataCon

NamedThing ConLike # 
Instance details

Defined in ConLike

NamedThing Class # 
Instance details

Defined in Class

NamedThing IfaceConDecl # 
Instance details

Defined in IfaceSyn

NamedThing IfaceClassOp # 
Instance details

Defined in IfaceSyn

NamedThing IfaceDecl # 
Instance details

Defined in IfaceSyn

NamedThing FamInst # 
Instance details

Defined in FamInstEnv

NamedThing ClsInst # 
Instance details

Defined in InstEnv

NamedThing (CoAxiom br) # 
Instance details

Defined in CoAxiom

NamedThing e => NamedThing (GenLocated l e) # 
Instance details

Defined in Name

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 

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 HscTypes

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

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

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

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

Create a name which definitely originates in the given module

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

Create a name which is actually defined by the compiler itself

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

Create a name brought into being by the compiler

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

Make a name for a foreign call

localiseName :: Name -> Name Source #

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

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

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

pprNameUnqualified :: Name -> SDoc Source #

Print the string of Name unqualifiedly directly.

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"

module Var

data Var Source #

Variable

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

Instances
Eq Var # 
Instance details

Defined in Var

Methods

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

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

Data Var # 
Instance details

Defined in Var

Methods

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

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

toConstr :: Var -> Constr Source #

dataTypeOf :: Var -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord Var # 
Instance details

Defined in 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 #

OutputableBndr Var # 
Instance details

Defined in PprCore

Outputable Var # 
Instance details

Defined in Var

Methods

ppr :: Var -> SDoc Source #

pprPrec :: Rational -> Var -> SDoc Source #

Uniquable Var # 
Instance details

Defined in Var

Methods

getUnique :: Var -> Unique Source #

HasOccName Var # 
Instance details

Defined in Var

Methods

occName :: Var -> OccName Source #

NamedThing Var # 
Instance details

Defined in Var

type OutId = Id Source #

type InId = Id Source #

type InVar = Var Source #

type JoinId = Id Source #

type DictId = EvId Source #

Dictionary Identifier

type Id = Var Source #

Identifier

globaliseId :: Id -> Id Source #

If it's a local, make it global

isExportedId :: Var -> Bool Source #

isExportedIdVar means "don't throw this away"

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

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

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

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

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

Make a global Id without any extra information at all

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

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

mkLocalId :: Name -> Type -> Id Source #

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

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

Make a local CoVar

mkLocalIdOrCoVar :: Name -> Type -> Id Source #

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

mkLocalIdOrCoVarWithInfo :: Name -> Type -> IdInfo -> Id Source #

Make a local id, with the IdDetails set to CoVarId if the type indicates so.

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]

mkSysLocal :: FastString -> Unique -> 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 -> Type -> Id Source #

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

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

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

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

Like mkUserLocal, but checks if we have a coercion type

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

Workers get local names. CoreTidy will externalise these if necessary

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

recordSelectorTyCon :: Id -> RecSelParent Source #

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

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

hasNoBinding :: Id -> Bool Source #

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

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.

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

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

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

isBottomingId :: Var -> Bool Source #

Returns true if an application to n args would diverge

isStrictId :: Id -> Bool Source #

This predicate says whether the Id has a strict demand placed on it or has a type such that it can always be evaluated strictly (i.e an unlifted type, as of GHC 7.6). We need to check separately whether the Id has a so-called "strict type" because if 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.

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

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

idCafInfo :: Id -> CafInfo infixl 1 Source #

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

idStateHackOneShotInfo :: Id -> OneShotInfo Source #

Like idOneShotInfo, but taking the Horrible State Hack in to account See Note [The state-transformer hack] in CoreArity

isOneShotBndr :: Var -> Bool Source #

Returns whether the lambda associated with the Id is certainly applied at most once This one is the "business end", called externally. It works on type variables as well as Ids, returning True Its main purpose is to encapsulate the Horrible State Hack See Note [The state-transformer hack] in CoreArity

stateHackOneShot :: OneShotInfo Source #

Should we apply the state hack to values of this Type?

module IdInfo

module CoreMonad

module CoreSyn

module Literal

module DataCon

module CoreUtils

module MkCore

module CoreFVs

data InScopeSet Source #

A set of variables that are in scope at some point "Secrets of the Glasgow Haskell Compiler inliner" Section 3.2 provides the motivation for this abstraction.

Instances
Outputable InScopeSet # 
Instance details

Defined in VarEnv

type TvSubstEnv = TyVarEnv Type Source #

A substitution of Types for TyVars and Kinds for KindVars

type IdSubstEnv = IdEnv CoreExpr Source #

An environment for substituting for Ids

data Subst Source #

A substitution environment, containing Id, TyVar, and CoVar substitutions.

Some invariants apply to how you use the substitution:

  1. Note [The substitution invariant] in TyCoRep
  2. Note [Substitutions apply only once] in TyCoRep
Instances
Outputable Subst # 
Instance details

Defined in CoreSubst

substInScope :: Subst -> InScopeSet Source #

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

zapSubstEnv :: Subst -> Subst Source #

Remove all substitutions for Ids and Exprs that might have been built up while preserving the in-scope set

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 TyCORep 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

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 TyCORep 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

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 :: SDoc -> Subst -> Id -> CoreExpr Source #

Find the substitution for an Id in the Subst

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

Find the substitution for a TyVar in the Subst

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

addInScopeSet :: Subst -> VarSet -> Subst Source #

Add the Expr to the in-scope set, but do not remove any existing substitutions for it

extendInScope :: Subst -> Var -> Subst Source #

Add the Expr to the in-scope set: as a side effect, and remove any existing substitutions for it

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

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

extendInScopeIds :: Subst -> [Id] -> Subst Source #

Optimized version of extendInScopeList that can be used if you are certain all the things being added are Ids and hence none are TyVars or CoVars

substExprSC :: SDoc -> Subst -> CoreExpr -> CoreExpr Source #

Apply a substitution to an entire CoreExpr. Remember, you may only apply the substitution once: see Note [Substitutions apply only once] in TyCoRep

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

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

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

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

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

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

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

Substitutes a Expr 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 :: Subst -> [Var] -> (Subst, [Var]) Source #

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

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

Substitute in a mutually recursive group of Ids

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.

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

Applies cloneIdBndr to a number of Ids, accumulating a final substitution from left to right

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

Clone a mutually recursive group of Ids

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

Substitute into some IdInfo with regard to the supplied new Id.

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

Substitutes for the Ids within an unfolding

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

Substitutes for the Ids within an unfolding

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

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

module Rules

module DynFlags

module Packages

module Module

type ThetaType = [PredType] Source #

A collection of PredTypes

type Kind = Type Source #

The key type representing kinds in the compiler.

type PredType = Type Source #

A type of the form p of kind Constraint 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"

data TyBinder Source #

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

Instances
Data TyBinder # 
Instance details

Defined in TyCoRep

Methods

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

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

toConstr :: TyBinder -> Constr Source #

dataTypeOf :: TyBinder -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable TyBinder # 
Instance details

Defined in TyCoRep

data TCvSubst Source #

Type & coercion substitution

The following invariants must hold of a TCvSubst:

  1. The in-scope set is needed only to guide the generation of fresh uniques
  2. In particular, the kind of the type variables in the in-scope set is not relevant
  3. The substitution is only applied ONCE! This is because in general such application will not reach a fixed point.
Instances
Outputable TCvSubst # 
Instance details

Defined in TyCoRep

data TyThing Source #

A global typecheckable-thing, essentially anything that has a name. Not to be confused with a TcTyThing, which is also a typecheckable thing but in the *local* context. See TcEnv for how to retrieve a TyThing given a Name.

Instances
Outputable TyThing # 
Instance details

Defined in TyCoRep

NamedThing TyThing # 
Instance details

Defined in TyCoRep

data Type Source #

Instances
Data Type # 
Instance details

Defined in TyCoRep

Methods

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

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

toConstr :: Type -> Constr Source #

dataTypeOf :: Type -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable Type # 
Instance details

Defined in TyCoRep

isRuntimeRepTy :: Type -> Bool Source #

Is this the type RuntimeRep?

newtype PprPrec Source #

A general-purpose pretty-printing precedence type.

Constructors

PprPrec Int 
Instances
Eq PprPrec # 
Instance details

Defined in BasicTypes

Methods

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

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

Ord PprPrec # 
Instance details

Defined in BasicTypes

Show PprPrec # 
Instance details

Defined in BasicTypes

type TyVarBinder = TyVarBndr TyVar ArgFlag Source #

Type Variable Binder

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

data ArgFlag Source #

Argument Flag

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

Constructors

Inferred 
Specified 
Required 
Instances
Eq ArgFlag # 
Instance details

Defined in Var

Methods

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

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

Data ArgFlag # 
Instance details

Defined in Var

Methods

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

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

toConstr :: ArgFlag -> Constr Source #

dataTypeOf :: ArgFlag -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord ArgFlag # 
Instance details

Defined in Var

Outputable ArgFlag # 
Instance details

Defined in Var

Binary ArgFlag # 
Instance details

Defined in Var

Outputable tv => Outputable (TyVarBndr tv ArgFlag) # 
Instance details

Defined in Var

data Var Source #

Variable

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

Instances
Eq Var # 
Instance details

Defined in Var

Methods

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

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

Data Var # 
Instance details

Defined in Var

Methods

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

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

toConstr :: Var -> Constr Source #

dataTypeOf :: Var -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord Var # 
Instance details

Defined in 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 #

OutputableBndr Var # 
Instance details

Defined in PprCore

Outputable Var # 
Instance details

Defined in Var

Methods

ppr :: Var -> SDoc Source #

pprPrec :: Rational -> Var -> SDoc Source #

Uniquable Var # 
Instance details

Defined in Var

Methods

getUnique :: Var -> Unique Source #

HasOccName Var # 
Instance details

Defined in Var

Methods

occName :: Var -> OccName Source #

NamedThing Var # 
Instance details

Defined in Var

type TyCoVar = Id Source #

Type or Coercion Variable

type TyVar = Var Source #

Type or kind Variable

isVisibleArgFlag :: ArgFlag -> Bool Source #

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

isInvisibleArgFlag :: ArgFlag -> Bool Source #

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

sameVis :: ArgFlag -> ArgFlag -> Bool Source #

Do these denote the same level of visibility? Required arguments are visible, others are not. So this function equates Specified and Inferred. Used for printing.

binderVar :: TyVarBndr tv argf -> tv Source #

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

binderArgFlag :: TyVarBndr tv argf -> argf Source #

mkTyVarBinder :: ArgFlag -> Var -> TyVarBinder Source #

Make a named binder

mkTyVarBinders :: ArgFlag -> [TyVar] -> [TyVarBinder] Source #

Make many named binders

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

toposortTyVars :: [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).

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

tcView :: Type -> Maybe Type Source #

Gives the typechecker view of a type. This unwraps synonyms but leaves Constraint alone. c.f. coreView, which turns Constraint into TYPE LiftedRep. Returns Nothing if no unwrapping happens. See also Note [coreView vs tcView]

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 considers Constraint to be a synonym of TYPE LiftedRep.

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

eqType :: Type -> Type -> Bool Source #

Type equality on source types. Does not look through newtypes or PredTypes, but it does look through type synonyms. This first checks that the kinds of the types are equal and then checks whether the types are equal, ignoring casts and coercions. (The kind check is a recursive call, but since all kinds have type Type, there is no need to check the types of kinds.) See also Note [Non-trivial definitional equality] in TyCoRep.

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 TyCoRep

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

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

isPredTy :: Type -> Bool Source #

Is the type suitable to classify a given/wanted in the typechecker?

type TvSubstEnv = TyVarEnv Type Source #

A substitution of Types for TyVars and Kinds for KindVars

type KnotTied ty = ty Source #

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

type KindOrType = Type Source #

The key representation of types within the compiler

isInvisibleBinder :: TyBinder -> Bool Source #

Does this binder bind an invisible argument?

isVisibleBinder :: TyBinder -> Bool Source #

Does this binder bind a visible argument?

mkFunTy :: Type -> Type -> Type infixr 3 Source #

Make an arrow type

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

Make nested arrow types

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

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

isCoercionType :: Type -> Bool Source #

Does this type classify a core (unlifted) Coercion? At either role nominal or representational (t1 ~ t2)

mkTyConTy :: TyCon -> Type Source #

Create the plain type constructor type which has been applied to no type arguments at all.

isRuntimeRepVar :: TyVar -> Bool Source #

Is a tyvar of type RuntimeRep?

tyCoVarsOfType :: Type -> TyCoVarSet Source #

Returns free variables of a type, including kind variables as a non-deterministic set. For type synonyms it does not expand the synonym.

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 FV.

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 FV.

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

tyCoVarsOfTypes :: [Type] -> TyCoVarSet Source #

Returns free variables of types, including kind variables as a non-deterministic set. For type synonyms it does not expand the synonym.

closeOverKinds :: TyVarSet -> TyVarSet Source #

Add the kind variables free in the kinds of the tyvars in the given set. Returns a non-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.

noFreeVarsOfType :: Type -> Bool Source #

Returns True if this type has no free variables. Should be the same as isEmptyVarSet . tyCoVarsOfType, but faster in the non-forall case.

composeTCvSubstEnv :: InScopeSet -> (TvSubstEnv, CvSubstEnv) -> (TvSubstEnv, CvSubstEnv) -> (TvSubstEnv, CvSubstEnv) Source #

(compose env1 env2)(x) is env1(env2(x)); i.e. apply env2 then env1. It assumes that both are idempotent. Typically, env1 is the refinement to a base substitution env2

composeTCvSubst :: TCvSubst -> TCvSubst -> TCvSubst Source #

Composes two substitutions, applying the second one provided first, like in function composition.

getTCvSubstRangeFVs :: TCvSubst -> VarSet Source #

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

zipTvSubst :: [TyVar] -> [Type] -> TCvSubst Source #

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

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

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

substTyWith :: HasCallStack => [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.

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.

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

Type substitution, see zipTvSubst

substTyAddInScope :: TCvSubst -> 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 :: TCvSubst -> 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.

substTys :: HasCallStack => TCvSubst -> [Type] -> [Type] Source #

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

substTysUnchecked :: TCvSubst -> [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.

substTheta :: HasCallStack => TCvSubst -> ThetaType -> ThetaType Source #

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

substThetaUnchecked :: TCvSubst -> 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.

substCoUnchecked :: TCvSubst -> 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.

pprUserForAll :: [TyVarBinder] -> SDoc Source #

Print a user-level forall; see Note [When to print foralls]

tidyTyCoVarBndrs :: 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.

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

tidyOpenTyCoVar :: 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 tidyTyCoVarBndr

tidyOpenTypes :: 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)

funTyCon :: TyCon Source #

The (->) type constructor.

(->) :: forall (rep1 :: RuntimeRep) (rep2 :: RuntimeRep).
        TYPE rep1 -> TYPE rep2 -> *

data EqRel Source #

A choice of equality relation. This is separate from the type Role because Phantom does not define a (non-trivial) equality relation.

Constructors

NomEq 
ReprEq 
Instances
Eq EqRel # 
Instance details

Defined in Type

Methods

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

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

Ord EqRel # 
Instance details

Defined in Type

Methods

compare :: EqRel -> EqRel -> Ordering #

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

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

(>) :: EqRel -> EqRel -> Bool #

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

max :: EqRel -> EqRel -> EqRel #

min :: EqRel -> EqRel -> EqRel #

Outputable EqRel # 
Instance details

Defined in Type

data TyCoMapper env m Source #

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

Constructors

TyCoMapper 

Fields

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

mapType :: Monad m => TyCoMapper env m -> env -> Type -> m Type Source #

mapCoercion :: Monad m => TyCoMapper env m -> env -> Coercion -> m Coercion Source #

getTyVar :: String -> 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

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 type

repGetTyVar_maybe :: Type -> Maybe TyVar Source #

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

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!

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

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

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

Does the AppTy split as in tcSplitAppTy_maybe, but assumes that any coreView stuff is already done. Refuses to look through (c => t)

tcRepSplitTyConApp_maybe :: HasCallStack => Type -> Maybe (TyCon, [Type]) Source #

Like tcSplitTyConApp_maybe but doesn't look through type synonyms.

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

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

splitAppTys :: 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.

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

Like splitAppTys, but doesn't look through type synonyms

isNumLitTy :: Type -> Maybe Integer Source #

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

isStrLitTy :: Type -> Maybe FastString Source #

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

userTypeError_maybe :: Type -> Maybe Type Source #

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

pprUserTypeErrorTy :: Type -> SDoc Source #

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

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

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

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

Attempts to extract the argument and result types from a type

funResultTy :: Type -> Type Source #

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

funArgTy :: Type -> Type Source #

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

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.

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

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.

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

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

The same as snd . splitTyConApp

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

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

Like splitTyConApp_maybe, but doesn't look through synonyms. This assumes the synonyms have already been dealt with.

splitListTyConApp_maybe :: Type -> Maybe Type Source #

Attempts to tease a list type apart and gives the type of the elements if successful (looks through type synonyms)

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.

mkInvForAllTy :: TyVar -> Type -> Type Source #

Make a dependent forall over an Inferred (as opposed to Specified) variable

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

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

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

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

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

Like mkForAllTys, but assumes all variables are dependent and visible

mkLamType :: Var -> Type -> Type Source #

Makes a (->) type or an implicit forall type, depending on whether it is given a type variable or a term variable. This is used, for example, when producing the type of a lambda. Always uses Inferred binders.

mkLamTypes :: [Var] -> Type -> Type Source #

mkLamType for multiple type or value arguments

mkTyConBindersPreferAnon :: [TyVar] -> Type -> [TyConBinder] Source #

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

All binders are visible.

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

Take a ForAllTy apart, returning the list of tyvars 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.

splitForAllTyVarBndrs :: Type -> ([TyVarBinder], Type) Source #

Like splitPiTys but split off only named binders.

isForAllTy :: Type -> Bool Source #

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

isPiTy :: Type -> Bool Source #

Is this a function or forall?

splitForAllTy :: Type -> (TyVar, Type) Source #

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

dropForAlls :: Type -> Type Source #

Drops all ForAllTys

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

Attempts to take a forall type apart, but only if it's a proper forall, with a named binder

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

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

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

Takes a forall type apart, or panics

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

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

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

Given a tycon and its arguments, filters out any invisible arguments

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

Given a tycon and a list of things (which correspond to arguments), partitions the things into Inferred or Specified ones and Required ones The callback function is necessary for this scenario:

T :: forall k. k -> k
partitionInvisibles 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.

If you're absolutely sure that your tycon's kind doesn't end in a variable, it's OK if the callback function panics, as that's the only time it's consulted.

mkAnonBinder :: Type -> TyBinder Source #

Make an anonymous binder

isAnonTyBinder :: TyBinder -> Bool Source #

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

binderRelevantType_maybe :: TyBinder -> Maybe Type Source #

Extract a relevant type, if there is one.

caseBinder Source #

Arguments

:: TyBinder

binder to scrutinize

-> (TyVarBinder -> a)

named case

-> (Type -> a)

anonymous case

-> a 

Like maybe, but for binders.

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

Split a type constructor application into its type constructor and applied types. Note that this may fail 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). Consequently, you may need to zonk your type before using this function.

If you only need the TyCon, consider using tcTyConAppTyCon_maybe.

tcIsLiftedTypeKind :: Kind -> Bool Source #

Is this kind equivalent to *?

This considers Constraint to be distinct from *. For a version that treats them as the same type, see isLiftedTypeKind.

mkPrimEqPredRole :: Role -> Type -> Type -> PredType Source #

Makes a lifted equality predicate at the given role

mkPrimEqPred :: Type -> Type -> Type Source #

Creates a primitive type equality predicate. Invariant: the types are not Coercions

mkHeteroPrimEqPred :: Kind -> Kind -> Type -> Type -> Type Source #

Creates a primite type equality predicate with explicit kinds

mkHeteroReprPrimEqPred :: Kind -> Kind -> Type -> Type -> Type Source #

Creates a primitive representational type equality predicate with explicit kinds

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

Try to split up a coercion type into the types that it coerces

predTypeEqRel :: PredType -> EqRel Source #

Get the equality relation relevant for a pred type.

dVarSetElemsWellScoped :: DVarSet -> [Var] Source #

Extract a well-scoped list of variables from a deterministic set of variables. The result is deterministic. NB: There used to exist varSetElemsWellScoped :: VarSet -> [Var] which took a non-deterministic set and produced a non-deterministic well-scoped list. If you care about the list being well-scoped you also most likely care about it being in deterministic order.

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)

coAxNthLHS :: CoAxiom br -> Int -> Type Source #

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

pprSourceTyCon :: TyCon -> SDoc Source #

Pretty prints a TyCon, using the family instance in case of a representation tycon. For example:

data T [a] = ...

In that case we want to print T [a], where T is the family TyCon

isLiftedType_maybe :: HasDebugCallStack => Type -> Maybe Bool Source #

Returns Just True if this type is surely lifted, Just False if it is surely unlifted, Nothing if we can't be sure (i.e., it is levity polymorphic), and panics if the kind does not have the shape TYPE r.

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

See Type for what an unlifted type is. Panics on levity polymorphic types.

isRuntimeRepKindedTy :: Type -> Bool Source #

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

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]

getRuntimeRep_maybe :: HasDebugCallStack => Type -> Maybe Type Source #

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

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

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

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

Extract the RuntimeRep classifier of a type from its kind. For example, getRuntimeRepFromKind * = LiftedRep; Panics if this is not possible.

getRuntimeRepFromKind_maybe :: HasDebugCallStack => Type -> Maybe Type Source #

Extract the RuntimeRep classifier of a type from its kind. For example, getRuntimeRepFromKind * = LiftedRep; Returns Nothing if this is not possible.

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

isDataFamilyAppType :: Type -> Bool Source #

Check whether a type is a data family type

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 levity-polymorphic types.

isPrimitiveType :: Type -> Bool Source #

Returns true of types that are opaque to Haskell.

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 CoreSyn.) 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]

seqType :: Type -> () Source #

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

eqTypeX :: RnEnv2 -> Type -> Type -> Bool Source #

Compare types with respect to a (presumably) non-empty RnEnv2.

eqTypes :: [Type] -> [Type] -> Bool Source #

Type equality on lists of types, looking through type synonyms but not newtypes.

nonDetCmpTc :: TyCon -> TyCon -> Ordering Source #

Compare two TyCons. NB: This should never see Constraint (as recognized by Kind.isConstraintKindCon) which is considered a synonym for Type in Core. See Note [Kind Constraint and kind Type] in Kind. See Note [nonDetCmpType nondeterminism]

isTypeLevPoly :: Type -> Bool Source #

Returns True if a type is levity polymorphic. Should be the same as (isKindLevPoly . typeKind) but much faster. Precondition: The type has kind (TYPE blah)

resultIsLevPoly :: Type -> Bool Source #

Looking past all pi-types, is the end result potentially levity polymorphic? Example: True for (forall r (a :: TYPE r). String -> a) Example: False for (forall r1 r2 (a :: TYPE r1) (b :: TYPE r2). a -> b -> Type)

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.

synTyConResKind :: TyCon -> Kind Source #

Find the result Kind of a type synonym, after applying it to its arity number of type variables Actually this function works fine on data types too, but they'd always return *, so we never need to ask

splitVisVarsOfType :: Type -> Pair TyCoVarSet Source #

Retrieve the free variables in this type, splitting them based on whether they are used visibly or invisibly. Invisible ones come first.

pprWithTYPE :: Type -> SDoc Source #

This variant preserves any use of TYPE in a type, effectively locally setting -fprint-explicit-runtime-reps.

module TyCon

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

Defined in TyCoRep

Methods

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

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

toConstr :: UnivCoProvenance -> Constr Source #

dataTypeOf :: UnivCoProvenance -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable UnivCoProvenance # 
Instance details

Defined in TyCoRep

data Coercion Source #

A Coercion is concrete evidence of the equality/convertibility of two types.

Instances
Data Coercion # 
Instance details

Defined in TyCoRep

Methods

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

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

toConstr :: Coercion -> Constr Source #

dataTypeOf :: Coercion -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable Coercion # 
Instance details

Defined in TyCoRep

data LeftOrRight Source #

Constructors

CLeft 
CRight 
Instances
Eq LeftOrRight # 
Instance details

Defined in BasicTypes

Data LeftOrRight # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: LeftOrRight -> Constr Source #

dataTypeOf :: LeftOrRight -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable LeftOrRight # 
Instance details

Defined in BasicTypes

Binary LeftOrRight # 
Instance details

Defined in Binary

pickLR :: LeftOrRight -> (a, a) -> a Source #

data Var Source #

Variable

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

Instances
Eq Var # 
Instance details

Defined in Var

Methods

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

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

Data Var # 
Instance details

Defined in Var

Methods

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

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

toConstr :: Var -> Constr Source #

dataTypeOf :: Var -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord Var # 
Instance details

Defined in 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 #

OutputableBndr Var # 
Instance details

Defined in PprCore

Outputable Var # 
Instance details

Defined in Var

Methods

ppr :: Var -> SDoc Source #

pprPrec :: Rational -> Var -> SDoc Source #

Uniquable Var # 
Instance details

Defined in Var

Methods

getUnique :: Var -> Unique Source #

HasOccName Var # 
Instance details

Defined in Var

Methods

occName :: Var -> OccName Source #

NamedThing Var # 
Instance details

Defined in Var

type TyCoVar = Id Source #

Type or Coercion Variable

type CoVar = Id Source #

Coercion Variable

data Role Source #

Instances
Eq Role # 
Instance details

Defined in CoAxiom

Methods

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

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

Data Role # 
Instance details

Defined in CoAxiom

Methods

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

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

toConstr :: Role -> Constr Source #

dataTypeOf :: Role -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord Role # 
Instance details

Defined in CoAxiom

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 #

Outputable Role # 
Instance details

Defined in CoAxiom

Binary Role # 
Instance details

Defined in CoAxiom

data LiftingContext Source #

Constructors

LC TCvSubst LiftCoEnv 
Instances
Outputable LiftingContext # 
Instance details

Defined in Coercion

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.

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.

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

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

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.

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

mkProofIrrelCo Source #

Arguments

:: Role

role of the created coercion, "r"

-> Coercion

:: phi1 ~N phi2

-> Coercion

g1 :: phi1

-> Coercion

g2 :: phi2

-> Coercion

:: g1 ~r g2

Make a "coercion between coercions".

mkKindCo :: Coercion -> Coercion Source #

Given co :: (a :: k) ~ (b :: k') produce co' :: k ~ k'.

mkTransCo :: Coercion -> Coercion -> Coercion Source #

Create a new Coercion by composing the two given Coercions transitively. (co1 ; co2)

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.

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.

mkUnsafeCo :: Role -> Type -> Type -> Coercion Source #

Manufacture an unsafe coercion from thin air. Currently (May 14) this is used only to implement the unsafeCoerce# primitive. Optimise by pushing down through type constructors.

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.

mkFunCo :: Role -> 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).

mkForAllCo :: TyVar -> Coercion -> Coercion -> Coercion Source #

Make a Coercion from a tyvar, a kind coercion, and a body coercion. The kind of the tyvar should be the left-hand kind of the kind coercion.

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.

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.

type CvSubstEnv = CoVarEnv Coercion Source #

A substitution of Coercions for CoVars

data CoercionHole Source #

A coercion to be filled in by the type-checker. See Note [Coercion holes]

Constructors

CoercionHole 
Instances
Data CoercionHole # 
Instance details

Defined in TyCoRep

Methods

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

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

toConstr :: CoercionHole -> Constr Source #

dataTypeOf :: CoercionHole -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable CoercionHole # 
Instance details

Defined in TyCoRep

data MCoercion Source #

A semantically more meaningful type to represent what may or may not be a useful Coercion.

Constructors

MRefl 
MCo Coercion 

tyCoVarsOfCoDSet :: Coercion -> DTyCoVarSet Source #

Get a deterministic set of the vars free in a coercion

substCoWith :: HasCallStack => [TyVar] -> [Type] -> Coercion -> Coercion Source #

Coercion substitution, see zipTvSubst

substCos :: HasCallStack => TCvSubst -> [Coercion] -> [Coercion] Source #

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

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

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.

decomposeCo :: Arity -> Coercion -> [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]

getCoVar_maybe :: Coercion -> Maybe CoVar Source #

Attempts to obtain the type variable underlying a Coercion

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

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

splitAppCo_maybe :: Coercion -> Maybe (Coercion, Coercion) Source #

Attempt to take a coercion application apart.

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_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.

mkRepReflCo :: Type -> Coercion Source #

Make a representational reflexive coercion

mkNomReflCo :: Type -> Coercion Source #

Make a nominal reflexive coercion

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

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

mkTransAppCo Source #

Arguments

:: Role

r1

-> Coercion

co1 :: ty1a ~r1 ty1b

-> Type

ty1a

-> Type

ty1b

-> Role

r2

-> Coercion

co2 :: ty2a ~r2 ty2b

-> Type

ty2a

-> Type

ty2b

-> Role

r3

-> Coercion

:: ty1a ty2a ~r3 ty1b ty2b

Like mkAppCo, but allows the second coercion to be other than nominal. See Note [mkTransAppCo]. Role r3 cannot be more stringent than either r1 or r2.

mkForAllCos :: [(TyVar, Coercion)] -> Coercion -> Coercion Source #

Make nested ForAllCos

mkHomoForAllCos :: [TyVar] -> Coercion -> Coercion Source #

Make a Coercion quantified over a type variable; the variable has the same type in both sides of the coercion

mkHomoForAllCos_NoRefl :: [TyVar] -> Coercion -> Coercion Source #

Like mkHomoForAllCos, but doesn't check if the inner coercion is reflexive.

isCoVar_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.)

mkAxInstLHS :: CoAxiom br -> BranchIndex -> [Type] -> [Coercion] -> Type Source #

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

mkUnbranchedAxInstLHS :: CoAxiom Unbranched -> [Type] -> [Coercion] -> Type Source #

Instantiate the left-hand side of an unbranched axiom

mkHoleCo :: CoercionHole -> Coercion Source #

Make a coercion from a coercion hole

nthCoRole :: Int -> Coercion -> Role Source #

If you're about to call mkNthCo r n co, then r should be whatever nthCoRole n co returns.

mkCoherenceRightCo :: Coercion -> Coercion -> Coercion infixl 5 Source #

A CoherenceCo c1 c2 applies the coercion c2 to the left-hand type in the kind of c1. This function uses sym to get the coercion on the right-hand type of c1. Thus, if c1 :: s ~ t, then mkCoherenceRightCo c1 c2 has the kind (s ~ (t |> c2)) down through type constructors. The second coercion must be representational.

mkCoherenceLeftCo :: Coercion -> Coercion -> Coercion infixl 5 Source #

An explicitly directed synonym of mkCoherenceCo. The second coercion must be representational.

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

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

maybeSubCo :: EqRel -> Coercion -> Coercion Source #

If the EqRel is ReprEq, makes a SubCo; otherwise, does nothing. Note that the input coercion should always be nominal.

setNominalRole_maybe :: Role -> Coercion -> Maybe Coercion Source #

Converts a coercion to be nominal, if possible. See Note [Role twiddling functions]

promoteCoercion :: Coercion -> CoercionN Source #

like mkKindCo, but aggressively & recursively optimizes to avoid using a KindCo constructor. The output role is nominal.

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

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

mkPiCo :: Role -> Var -> Coercion -> Coercion Source #

Make a forall Coercion, where both types related by the coercion are quantified over the same type variable.

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

If co :: T ts ~ rep_ty then:

instNewTyCon_maybe T ts = Just (rep_ty, co)

Checks for a newtype, and for being saturated

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

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.

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

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 : ty0 ~ 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'

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

Syntactic equality of coercions

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

Compare two Coercions, with respect to an RnEnv2

liftCoSubstWithEx :: Role -> [TyVar] -> [Coercion] -> [TyVar] -> [Type] -> (Type -> Coercion, [Type]) Source #

extendLiftingContext Source #

Arguments

:: LiftingContext

original LC

-> TyVar

new variable to map...

-> Coercion

...to this lifted version

-> LiftingContext 

Extend a lifting context with a new type mapping.

extendLiftingContextAndInScope Source #

Arguments

:: LiftingContext

Original LC

-> TyVar

new variable to map...

-> Coercion

to this coercion

-> LiftingContext 

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

zapLiftingContext :: LiftingContext -> LiftingContext Source #

Erase the environments in a lifting context

substForAllCoBndrUsingLC :: Bool -> (Coercion -> Coercion) -> LiftingContext -> TyVar -> Coercion -> (LiftingContext, TyVar, Coercion) Source #

Like substForAllCoBndr, but works on a lifting context

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

Is a var in the domain of a lifting context?

swapLiftCoEnv :: LiftCoEnv -> LiftCoEnv Source #

Apply "sym" to all coercions in a LiftCoEnv

lcTCvSubst :: LiftingContext -> TCvSubst Source #

Extract the underlying substitution from the LiftingContext

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

Get a coercion's kind and role. Why both at once? See Note [Computing a coercion kind and role]

coercionRole :: Coercion -> Role Source #

Retrieve the role from a coercion.

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 OptCoercion.

module TysWiredIn

module HscTypes

data SpliceExplicitFlag Source #

Constructors

ExplicitSplice

= $(f x y)

ImplicitSplice

= f x y, i.e. a naked top level expression

Instances
Data SpliceExplicitFlag # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: SpliceExplicitFlag -> Constr Source #

dataTypeOf :: SpliceExplicitFlag -> DataType Source #

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

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

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

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

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

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

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

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

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

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

data FractionalLit Source #

Fractional Literal

Used (instead of Rational) to represent exactly the floating point literal that we encountered in the user's source program. This allows us to pretty-print exactly what the user wrote, which is important e.g. for floating point numbers that can't represented as Doubles (we used to via Double for pretty-printing). See also #2245.

Constructors

FL 
Instances
Eq FractionalLit # 
Instance details

Defined in BasicTypes

Data FractionalLit # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: FractionalLit -> Constr Source #

dataTypeOf :: FractionalLit -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord FractionalLit # 
Instance details

Defined in BasicTypes

Show FractionalLit # 
Instance details

Defined in BasicTypes

Outputable FractionalLit # 
Instance details

Defined in BasicTypes

data IntegralLit Source #

Integral Literal

Used (instead of Integer) to represent negative zegative zero which is required for NegativeLiterals extension to correctly parse `-0::Double` as negative zero. See also #13211.

Constructors

IL 
Instances
Eq IntegralLit # 
Instance details

Defined in BasicTypes

Data IntegralLit # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: IntegralLit -> Constr Source #

dataTypeOf :: IntegralLit -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord IntegralLit # 
Instance details

Defined in BasicTypes

Show IntegralLit # 
Instance details

Defined in BasicTypes

Outputable IntegralLit # 
Instance details

Defined in BasicTypes

data InlineSpec Source #

Inline Specification

Instances
Eq InlineSpec # 
Instance details

Defined in BasicTypes

Data InlineSpec # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: InlineSpec -> Constr Source #

dataTypeOf :: InlineSpec -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show InlineSpec # 
Instance details

Defined in BasicTypes

Outputable InlineSpec # 
Instance details

Defined in BasicTypes

Binary InlineSpec # 
Instance details

Defined in Binary

data InlinePragma Source #

Instances
Eq InlinePragma # 
Instance details

Defined in BasicTypes

Data InlinePragma # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: InlinePragma -> Constr Source #

dataTypeOf :: InlinePragma -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable InlinePragma # 
Instance details

Defined in BasicTypes

Binary InlinePragma # 
Instance details

Defined in Binary

data RuleMatchInfo Source #

Rule Match Information

Constructors

ConLike 
FunLike 
Instances
Eq RuleMatchInfo # 
Instance details

Defined in BasicTypes

Data RuleMatchInfo # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: RuleMatchInfo -> Constr Source #

dataTypeOf :: RuleMatchInfo -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show RuleMatchInfo # 
Instance details

Defined in BasicTypes

Outputable RuleMatchInfo # 
Instance details

Defined in BasicTypes

Binary RuleMatchInfo # 
Instance details

Defined in Binary

data Activation Source #

Instances
Eq Activation # 
Instance details

Defined in BasicTypes

Data Activation # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: Activation -> Constr Source #

dataTypeOf :: Activation -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable Activation # 
Instance details

Defined in BasicTypes

Binary Activation # 
Instance details

Defined in Binary

data CompilerPhase Source #

Constructors

Phase PhaseNum 
InitialPhase 
Instances
Outputable CompilerPhase # 
Instance details

Defined in BasicTypes

type PhaseNum = Int Source #

Phase Number

data SourceText Source #

Constructors

SourceText String 
NoSourceText

For when code is generated, e.g. TH, deriving. The pretty printer will then make its own representation of the item.

Instances
Eq SourceText # 
Instance details

Defined in BasicTypes

Data SourceText # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: SourceText -> Constr Source #

dataTypeOf :: SourceText -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show SourceText # 
Instance details

Defined in BasicTypes

Outputable SourceText # 
Instance details

Defined in BasicTypes

Binary SourceText # 
Instance details

Defined in Binary

data SuccessFlag Source #

Constructors

Succeeded 
Failed 
Instances
Outputable SuccessFlag # 
Instance details

Defined in BasicTypes

data DefMethSpec ty Source #

Default Method Specification

Constructors

VanillaDM 
GenericDM ty 

type InsideLam = Bool Source #

Inside Lambda

type InterestingCxt = Bool Source #

Interesting Context

data OccInfo Source #

identifier Occurrence Information

Constructors

ManyOccs

There are many occurrences, or unknown occurrences

IAmDead

Marks unused variables. Sometimes useful for lambda and case-bound variables.

OneOcc

Occurs exactly once (per branch), not inside a rule

IAmALoopBreaker

This identifier breaks a loop of mutually recursive functions. The field marks whether it is only a loop breaker due to a reference in a rule

Fields

Instances
Eq OccInfo # 
Instance details

Defined in BasicTypes

Methods

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

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

Outputable OccInfo # 
Instance details

Defined in BasicTypes

data EP a Source #

Embedding Projection pair

Constructors

EP 

Fields

data TupleSort Source #

Instances
Eq TupleSort # 
Instance details

Defined in BasicTypes

Data TupleSort # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: TupleSort -> Constr Source #

dataTypeOf :: TupleSort -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Binary TupleSort # 
Instance details

Defined in Binary

newtype PprPrec Source #

A general-purpose pretty-printing precedence type.

Constructors

PprPrec Int 
Instances
Eq PprPrec # 
Instance details

Defined in BasicTypes

Methods

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

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

Ord PprPrec # 
Instance details

Defined in BasicTypes

Show PprPrec # 
Instance details

Defined in BasicTypes

data OverlapMode Source #

Constructors

NoOverlap SourceText

This instance must not overlap another NoOverlap instance. However, it may be overlapped by Overlapping instances, and it may overlap Overlappable instances.

Overlappable SourceText

Silently ignore this instance if you find a more specific one that matches the constraint you are trying to resolve

Example: constraint (Foo [Int]) instance Foo [Int] instance {--} Foo [a]

Since the second instance has the Overlappable flag, the first instance will be chosen (otherwise its ambiguous which to choose)

Overlapping SourceText

Silently ignore any more general instances that may be used to solve the constraint.

Example: constraint (Foo [Int]) instance {--} Foo [Int] instance Foo [a]

Since the first instance has the Overlapping flag, the second---more general---instance will be ignored (otherwise it is ambiguous which to choose)

Overlaps SourceText

Equivalent to having both Overlapping and Overlappable flags.

Incoherent SourceText

Behave like Overlappable and Overlapping, and in addition pick an an arbitrary one if there are multiple matching candidates, and don't worry about later instantiation

Example: constraint (Foo [b]) instance {-# INCOHERENT -} Foo [Int] instance Foo [a] Without the Incoherent flag, we'd complain that instantiating b would change which instance was chosen. See also note [Incoherent instances] in InstEnv

Instances
Eq OverlapMode # 
Instance details

Defined in BasicTypes

Data OverlapMode # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: OverlapMode -> Constr Source #

dataTypeOf :: OverlapMode -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable OverlapMode # 
Instance details

Defined in BasicTypes

Binary OverlapMode # 
Instance details

Defined in Binary

data OverlapFlag Source #

The semantics allowed for overlapping instances for a particular instance. See Note [Safe Haskell isSafeOverlap] (in hs) for a explanation of the isSafeOverlap field.

Instances
Eq OverlapFlag # 
Instance details

Defined in BasicTypes

Data OverlapFlag # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: OverlapFlag -> Constr Source #

dataTypeOf :: OverlapFlag -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable OverlapFlag # 
Instance details

Defined in BasicTypes

Binary OverlapFlag # 
Instance details

Defined in Binary

data Origin Source #

Constructors

FromSource 
Generated 
Instances
Eq Origin # 
Instance details

Defined in BasicTypes

Methods

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

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

Data Origin # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: Origin -> Constr Source #

dataTypeOf :: Origin -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable Origin # 
Instance details

Defined in BasicTypes

data RecFlag Source #

Recursivity Flag

Constructors

Recursive 
NonRecursive 
Instances
Eq RecFlag # 
Instance details

Defined in BasicTypes

Methods

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

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

Data RecFlag # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: RecFlag -> Constr Source #

dataTypeOf :: RecFlag -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable RecFlag # 
Instance details

Defined in BasicTypes

Binary RecFlag # 
Instance details

Defined in Binary

data Boxity Source #

Constructors

Boxed 
Unboxed 
Instances
Eq Boxity # 
Instance details

Defined in BasicTypes

Methods

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

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

Data Boxity # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: Boxity -> Constr Source #

dataTypeOf :: Boxity -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable Boxity # 
Instance details

Defined in BasicTypes

data TopLevelFlag Source #

Constructors

TopLevel 
NotTopLevel 
Instances
Outputable TopLevelFlag # 
Instance details

Defined in BasicTypes

data LexicalFixity Source #

Captures the fixity of declarations as they are parsed. This is not necessarily the same as the fixity declaration, as the normal fixity may be overridden using parens or backticks.

Constructors

Prefix 
Infix 
Instances
Eq LexicalFixity # 
Instance details

Defined in BasicTypes

Data LexicalFixity # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: LexicalFixity -> Constr Source #

dataTypeOf :: LexicalFixity -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable LexicalFixity # 
Instance details

Defined in BasicTypes

data FixityDirection Source #

Constructors

InfixL 
InfixR 
InfixN 
Instances
Eq FixityDirection # 
Instance details

Defined in BasicTypes

Data FixityDirection # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: FixityDirection -> Constr Source #

dataTypeOf :: FixityDirection -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable FixityDirection # 
Instance details

Defined in BasicTypes

Binary FixityDirection # 
Instance details

Defined in Binary

data Fixity Source #

Instances
Eq Fixity # 
Instance details

Defined in BasicTypes

Methods

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

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

Data Fixity # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: Fixity -> Constr Source #

dataTypeOf :: Fixity -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable Fixity # 
Instance details

Defined in BasicTypes

Binary Fixity # 
Instance details

Defined in Binary

data WarningTxt Source #

Warning Text

reason/explanation from a WARNING or DEPRECATED pragma

Instances
Eq WarningTxt # 
Instance details

Defined in BasicTypes

Data WarningTxt # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: WarningTxt -> Constr Source #

dataTypeOf :: WarningTxt -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable WarningTxt # 
Instance details

Defined in BasicTypes

Binary WarningTxt # 
Instance details

Defined in Binary

data StringLiteral Source #

A String Literal in the source, including its original raw format for use by source to source manipulation tools.

Constructors

StringLiteral 
Instances
Eq StringLiteral # 
Instance details

Defined in BasicTypes

Data StringLiteral # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: StringLiteral -> Constr Source #

dataTypeOf :: StringLiteral -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable StringLiteral # 
Instance details

Defined in BasicTypes

Binary StringLiteral # 
Instance details

Defined in Binary

data FunctionOrData Source #

Constructors

IsFunction 
IsData 
Instances
Eq FunctionOrData # 
Instance details

Defined in BasicTypes

Data FunctionOrData # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: FunctionOrData -> Constr Source #

dataTypeOf :: FunctionOrData -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord FunctionOrData # 
Instance details

Defined in BasicTypes

Outputable FunctionOrData # 
Instance details

Defined in BasicTypes

Binary FunctionOrData # 
Instance details

Defined in Binary

data SwapFlag Source #

Constructors

NotSwapped 
IsSwapped 
Instances
Outputable SwapFlag # 
Instance details

Defined in BasicTypes

data OneShotInfo Source #

If the Id is a lambda-bound variable then it may have lambda-bound variable info. Sometimes we know whether the lambda binding this variable is a "one-shot" lambda; that is, whether it is applied at most once.

This information may be useful in optimisation, as computations may safely be floated inside such a lambda without risk of duplicating work.

Constructors

NoOneShotInfo

No information

OneShotLam

The lambda is applied at most once.

Instances
Eq OneShotInfo # 
Instance details

Defined in BasicTypes

Outputable OneShotInfo # 
Instance details

Defined in BasicTypes

type ConTagZ = Int Source #

A *zero-indexed* constructor tag

type ConTag = Int Source #

Constructor Tag

Type of the tags associated with each constructor possibility or superclass selector

type JoinArity = Int Source #

The number of arguments that a join point takes. Unlike the arity of a function, this is a purely syntactic property and is fixed when the join point is created (or converted from a value). Both type and value arguments are counted.

type RepArity = Int Source #

Representation Arity

The number of represented arguments that can be applied to a value before it does "real work". So: fib 100 has representation arity 0 x -> fib x has representation arity 1 () -> fib (x + y) has representation arity 2

type Arity = Int Source #

The number of value arguments that can be applied to a value before it does "real work". So: fib 100 has arity 0 x -> fib x has arity 1 See also Note [Definition of arity] in CoreArity

data LeftOrRight Source #

Constructors

CLeft 
CRight 
Instances
Eq LeftOrRight # 
Instance details

Defined in BasicTypes

Data LeftOrRight # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: LeftOrRight -> Constr Source #

dataTypeOf :: LeftOrRight -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable LeftOrRight # 
Instance details

Defined in BasicTypes

Binary LeftOrRight # 
Instance details

Defined in Binary

pickLR :: LeftOrRight -> (a, a) -> a Source #

fIRST_TAG :: ConTag Source #

Tags are allocated from here for real constructors or for superclass selectors

noOneShotInfo :: OneShotInfo Source #

It is always safe to assume that an Id has no lambda-bound variable information

unSwap :: SwapFlag -> (a -> a -> b) -> a -> a -> b Source #

pprAlternative Source #

Arguments

:: (a -> SDoc)

The pretty printing function to use

-> a

The things to be pretty printed

-> ConTag

Alternative (one-based)

-> Arity

Arity

-> SDoc

SDoc where the alternative havs been pretty printed and finally packed into a paragraph.

Pretty print an alternative in an unboxed sum e.g. "| a | |".

pprWithSourceText :: SourceText -> SDoc -> SDoc Source #

Special combinator for showing string literals.

infinity :: IntWithInf Source #

A representation of infinity

treatZeroAsInf :: Int -> IntWithInf Source #

Turn a positive number into an IntWithInf, where 0 represents infinity

mkIntWithInf :: Int -> IntWithInf Source #

Inject any integer into an IntWithInf

module VarSet

module VarEnv

module NameSet

module NameEnv

module UniqSet

module UniqFM

module FiniteMap

module Util

module SrcLoc

module Outputable

module UniqSupply

class Uniquable a where Source #

Class of things that we can obtain a Unique from

Methods

getUnique :: a -> Unique Source #

Instances
Uniquable Int # 
Instance details

Defined in Unique

Methods

getUnique :: Int -> Unique Source #

Uniquable Name # 
Instance details

Defined in Name

Uniquable OccName # 
Instance details

Defined in OccName

Uniquable TyCon # 
Instance details

Defined in TyCon

Uniquable FastString # 
Instance details

Defined in Unique

Uniquable ComponentId # 
Instance details

Defined in Module

Uniquable InstalledUnitId # 
Instance details

Defined in Module

Uniquable UnitId # 
Instance details

Defined in Module

Uniquable ModuleName # 
Instance details

Defined in Module

Uniquable Module # 
Instance details

Defined in Module

Uniquable Unique # 
Instance details

Defined in Unique

Uniquable RegClass # 
Instance details

Defined in RegClass

Uniquable Reg #

so we can put regs in UniqSets

Instance details

Defined in RegAlloc.Graph.ArchBase

Methods

getUnique :: Reg -> Unique Source #

Uniquable Reg # 
Instance details

Defined in Reg

Methods

getUnique :: Reg -> Unique Source #

Uniquable RealReg # 
Instance details

Defined in Reg

Uniquable VirtualReg # 
Instance details

Defined in Reg

Uniquable PackageName # 
Instance details

Defined in PackageConfig

Uniquable SourcePackageId # 
Instance details

Defined in PackageConfig

Uniquable Var # 
Instance details

Defined in Var

Methods

getUnique :: Var -> Unique Source #

Uniquable PatSyn # 
Instance details

Defined in PatSyn

Uniquable DataCon # 
Instance details

Defined in DataCon

Uniquable ConLike # 
Instance details

Defined in ConLike

Uniquable CoAxiomRule # 
Instance details

Defined in CoAxiom

Uniquable Class # 
Instance details

Defined in Class

Uniquable Label # 
Instance details

Defined in Hoopl.Label

Uniquable LocalReg # 
Instance details

Defined in CmmExpr

Uniquable EvBindsVar # 
Instance details

Defined in TcEvidence

Uniquable name => Uniquable (AnnTarget name) # 
Instance details

Defined in Annotations

Methods

getUnique :: AnnTarget name -> Unique Source #

Uniquable (CoAxiom br) # 
Instance details

Defined in CoAxiom

Methods

getUnique :: CoAxiom br -> Unique Source #

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

Defined in Unique

Methods

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

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

Show Unique # 
Instance details

Defined in Unique

Outputable Unique # 
Instance details

Defined in Unique

Uniquable Unique # 
Instance details

Defined in Unique

module FastString