ghc-8.10.3: The GHC API
Safe HaskellNone
LanguageHaskell2010

TyCoRep

Synopsis

Documentation

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

Instances details
Outputable TyThing # 
Instance details

Defined in TyCoRep

NamedThing TyThing # 
Instance details

Defined in TyCoRep

Types

data Type Source #

Constructors

TyVarTy Var

Vanilla type or kind variable (*never* a coercion variable)

AppTy Type Type

Type application to something other than a TyCon. Parameters:

1) Function: must not be a TyConApp or CastTy, must be another AppTy, or TyVarTy See Note Respecting definitional equality about the no CastTy requirement

2) Argument type

TyConApp TyCon [KindOrType]

Application of a TyCon, including newtypes and synonyms. Invariant: saturated applications of FunTyCon must use FunTy and saturated synonyms must use their own constructors. However, unsaturated FunTyCons do appear as TyConApps. Parameters:

1) Type constructor being applied to.

2) Type arguments. Might not have enough type arguments here to saturate the constructor. Even type synonyms are not necessarily saturated; for example unsaturated type synonyms can appear as the right hand side of a type synonym.

ForAllTy !TyCoVarBinder Type

A Π type.

FunTy

t1 -> t2 Very common, so an important special case See Note [Function types]

Fields

LitTy TyLit

Type literals are similar to type constructors.

CastTy Type KindCoercion

A kind cast. The coercion is always nominal. INVARIANT: The cast is never refl. INVARIANT: The Type is not a CastTy (use TransCo instead) See Note Respecting definitional equality and (EQ3)

CoercionTy Coercion

Injection of a Coercion into a type This should only ever be used in the RHS of an AppTy, in the list of a TyConApp, when applying a promoted GADT data constructor

Instances

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

data TyLit Source #

Instances

Instances details
Eq TyLit # 
Instance details

Defined in TyCoRep

Methods

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

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

Data TyLit # 
Instance details

Defined in TyCoRep

Methods

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

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

toConstr :: TyLit -> Constr Source #

dataTypeOf :: TyLit -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord TyLit # 
Instance details

Defined in TyCoRep

Methods

compare :: TyLit -> TyLit -> Ordering #

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

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

(>) :: TyLit -> TyLit -> Bool #

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

max :: TyLit -> TyLit -> TyLit #

min :: TyLit -> TyLit -> TyLit #

Outputable TyLit # 
Instance details

Defined in TyCoRep

type KindOrType = Type Source #

The key representation of types within the compiler

type Kind = Type Source #

The key type representing kinds in the compiler.

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 PredType = Type Source #

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

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

It can be expanded into its representation, but:

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

Consider these examples:

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

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

type ThetaType = [PredType] Source #

A collection of PredTypes

data ArgFlag Source #

Argument Flag

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

Constructors

Inferred 
Specified 
Required 

Instances

Instances details
Eq ArgFlag # 
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 :: forall r r'. (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 (VarBndr tv ArgFlag) # 
Instance details

Defined in Var

data AnonArgFlag Source #

The non-dependent version of ArgFlag.

Constructors

VisArg

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

InvisArg

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

Instances

Instances details
Eq AnonArgFlag # 
Instance details

Defined in Var

Data AnonArgFlag # 
Instance details

Defined in Var

Methods

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

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

toConstr :: AnonArgFlag -> Constr Source #

dataTypeOf :: AnonArgFlag -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord AnonArgFlag # 
Instance details

Defined in Var

Outputable AnonArgFlag # 
Instance details

Defined in Var

Binary AnonArgFlag # 
Instance details

Defined in Var

data ForallVisFlag Source #

Is a forall invisible (e.g., forall a b. {...}, with a dot) or visible (e.g., forall a b -> {...}, with an arrow)?

Constructors

ForallVis

A visible forall (with an arrow)

ForallInvis

An invisible forall (with a dot)

Instances

Instances details
Eq ForallVisFlag # 
Instance details

Defined in Var

Data ForallVisFlag # 
Instance details

Defined in Var

Methods

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

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

toConstr :: ForallVisFlag -> Constr Source #

dataTypeOf :: ForallVisFlag -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord ForallVisFlag # 
Instance details

Defined in Var

Outputable ForallVisFlag # 
Instance details

Defined in Var

Coercions

data Coercion Source #

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

Instances

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

Constructors

UnsafeCoerceProv

From unsafeCoerce#. These are unsound.

PhantomProv KindCoercion

See Note [Phantom coercions]. Only in Phantom roled coercions

ProofIrrelProv KindCoercion

From the fact that any two coercions are considered equivalent. See Note [ProofIrrelProv]. Can be used in Nominal or Representational coercions

PluginProv String

From a plugin, which asserts that this coercion is sound. The string is for the use of the plugin.

Instances

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

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

Constructors

CoercionHole 

Instances

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

Instances

Instances details
Data MCoercion # 
Instance details

Defined in TyCoRep

Methods

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

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

toConstr :: MCoercion -> Constr Source #

dataTypeOf :: MCoercion -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable MCoercion # 
Instance details

Defined in TyCoRep

Functions over types

mkTyConTy :: TyCon -> Type Source #

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

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

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

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

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

Make nested arrow types

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

Make nested arrow types

mkForAllTy :: TyCoVar -> ArgFlag -> Type -> Type Source #

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

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

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

Functions over binders

data TyCoBinder Source #

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

Instances

Instances details
Data TyCoBinder # 
Instance details

Defined in TyCoRep

Methods

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

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

toConstr :: TyCoBinder -> Constr Source #

dataTypeOf :: TyCoBinder -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable TyCoBinder # 
Instance details

Defined in TyCoRep

type TyCoVarBinder = VarBndr TyCoVar ArgFlag Source #

Variable Binder

A TyCoVarBinder 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

A TyVarBinder is a binder with only TyVar

type TyBinder = TyCoBinder Source #

TyBinder is like TyCoBinder, but there can only be TyVarBinder in the Named field.

binderVar :: VarBndr tv argf -> tv Source #

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

binderArgFlag :: VarBndr tv argf -> argf Source #

delBinderVar :: VarSet -> TyCoVarBinder -> VarSet Source #

Remove the binder's variable from the set, if the binder has a variable.

isInvisibleArgFlag :: ArgFlag -> Bool Source #

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

isVisibleArgFlag :: ArgFlag -> Bool Source #

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

isInvisibleBinder :: TyCoBinder -> Bool Source #

Does this binder bind an invisible argument?

isVisibleBinder :: TyCoBinder -> Bool Source #

Does this binder bind a visible argument?

isTyBinder :: TyCoBinder -> Bool Source #

If its a named binder, is the binder a tyvar? Returns True for nondependent binder. This check that we're really returning a *Ty*Binder (as opposed to a coercion binder). That way, if/when we allow coercion quantification in more places, we'll know we missed updating some function.

Functions over coercions

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

Sizes