ghc-9.8.2: The GHC API
Safe HaskellNone
LanguageHaskell2010

GHC.Core.InstEnv

Synopsis

Documentation

type DFunId = Id Source #

Dictionary Function Identifier

data OverlapFlag Source #

The semantics allowed for overlapping instances for a particular instance. See Note [Safe Haskell isSafeOverlap] in GHC.Core.InstEnv for a explanation of the isSafeOverlap field.

Instances

Instances details
Data OverlapFlag Source # 
Instance details

Defined in GHC.Types.Basic

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> 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 :: forall r r'. (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 #

Binary OverlapFlag Source # 
Instance details

Defined in GHC.Types.Basic

Outputable OverlapFlag Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: OverlapFlag -> SDoc Source #

Eq OverlapFlag Source # 
Instance details

Defined in GHC.Types.Basic

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 {-# OVERLAPPABLE #-} 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 {-# OVERLAPPING #-} 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 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 GHC.Core.InstEnv

NonCanonical SourceText

Behave like Incoherent, but the instance choice is observable by the program behaviour. See Note [Coherence and specialisation: overview].

We don't have surface syntax for the distinction between Incoherent and NonCanonical instances; instead, the flag `-f{no-}specialise-incoherents` (on by default) controls whether INCOHERENT instances are regarded as Incoherent or NonCanonical.

Instances

Instances details
Data OverlapMode Source # 
Instance details

Defined in GHC.Types.Basic

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> 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 :: forall r r'. (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 #

Binary OverlapMode Source # 
Instance details

Defined in GHC.Types.Basic

Outputable OverlapMode Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: OverlapMode -> SDoc Source #

Eq OverlapMode Source # 
Instance details

Defined in GHC.Types.Basic

type Anno OverlapMode Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno OverlapMode Source # 
Instance details

Defined in GHC.Hs.Decls

data ClsInst Source #

A type-class instance. Note that there is some tricky laziness at work here. See Note [ClsInst laziness and the rough-match fields] for more details.

Constructors

ClsInst 

Fields

Instances

Instances details
Data ClsInst Source # 
Instance details

Defined in GHC.Core.InstEnv

Methods

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

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

toConstr :: ClsInst -> Constr Source #

dataTypeOf :: ClsInst -> DataType Source #

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

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

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

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

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

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

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

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

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

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

NamedThing ClsInst Source # 
Instance details

Defined in GHC.Core.InstEnv

Outputable ClsInst Source # 
Instance details

Defined in GHC.Core.InstEnv

Methods

ppr :: ClsInst -> SDoc Source #

mkImportedClsInst Source #

Arguments

:: Name

the name of the class

-> [RoughMatchTc]

the rough match signature of the instance

-> Name

the Name of the dictionary binding

-> DFunId

the Id of the dictionary.

-> OverlapFlag

may this instance overlap?

-> IsOrphan

is this instance an orphan?

-> ClsInst 

fuzzyClsInstCmp :: ClsInst -> ClsInst -> Ordering Source #

A fuzzy comparison function for class instances, intended for sorting instances before displaying them to the user.

orphNamesOfClsInst :: ClsInst -> NameSet Source #

Collects the names of concrete types and type constructors that make up the head of a class instance. For instance, given `class Foo a b`:

`instance Foo (Either (Maybe Int) a) Bool` would yield [Either, Maybe, Int, Bool]

Used in the implementation of ":info" in GHCi.

The tcSplitSigmaTy is because of instance Foo a => Baz T where ... The decl is an orphan if Baz and T are both not locally defined, even if Foo *is* locally defined

data InstEnvs Source #

InstEnvs represents the combination of the global type class instance environment, the local type class instance environment, and the set of transitively reachable orphan modules (according to what modules have been directly imported) used to test orphan instance visibility.

type VisibleOrphanModules = ModuleSet Source #

Set of visible orphan modules, according to what modules have been directly imported. This is based off of the dep_orphs field, which records transitively reachable orphan modules (modules that define orphan instances).

data InstEnv Source #

Instances

Instances details
Outputable InstEnv Source # 
Instance details

Defined in GHC.Core.InstEnv

Methods

ppr :: InstEnv -> SDoc Source #

data LookupInstanceErrReason Source #

Why a particular typeclass application couldn't be looked up.

Constructors

LookupInstErrNotExact

Tyvars aren't an exact match.

LookupInstErrFlexiVar

One of the tyvars is flexible.

LookupInstErrNotFound

No matching instance was found.

Instances

Instances details
Generic LookupInstanceErrReason Source # 
Instance details

Defined in GHC.Core.InstEnv

Associated Types

type Rep LookupInstanceErrReason 
Instance details

Defined in GHC.Core.InstEnv

type Rep LookupInstanceErrReason = D1 ('MetaData "LookupInstanceErrReason" "GHC.Core.InstEnv" "ghc-9.8.2-f9d1" 'False) (C1 ('MetaCons "LookupInstErrNotExact" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LookupInstErrFlexiVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LookupInstErrNotFound" 'PrefixI 'False) (U1 :: Type -> Type)))
type Rep LookupInstanceErrReason Source # 
Instance details

Defined in GHC.Core.InstEnv

type Rep LookupInstanceErrReason = D1 ('MetaData "LookupInstanceErrReason" "GHC.Core.InstEnv" "ghc-9.8.2-f9d1" 'False) (C1 ('MetaCons "LookupInstErrNotExact" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LookupInstErrFlexiVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LookupInstErrNotFound" 'PrefixI 'False) (U1 :: Type -> Type)))

unionInstEnv :: InstEnv -> InstEnv -> InstEnv Source #

Makes no particular effort to detect conflicts.

identicalClsInstHead :: ClsInst -> ClsInst -> Bool Source #

True when when the instance heads are the same e.g. both are Eq [(a,b)] Used for overriding in GHCi Obviously should be insensitive to alpha-renaming

lookupUniqueInstEnv :: InstEnvs -> Class -> [Type] -> Either LookupInstanceErrReason (ClsInst, [Type]) Source #

Look up an instance in the given instance environment. The given class application must match exactly one instance and the match may not contain any flexi type variables. If the lookup is unsuccessful, yield 'Left errorMessage'.

lookupInstEnv :: Bool -> InstEnvs -> Class -> [Type] -> ClsInstLookupResult Source #

See Note [Rules for instance lookup] ^ See Note [Safe Haskell Overlapping Instances] in GHC.Tc.Solver ^ See Note [Safe Haskell Overlapping Instances Implementation] in GHC.Tc.Solver

memberInstEnv :: InstEnv -> ClsInst -> Bool Source #

Checks for an exact match of ClsInst in the instance environment. We use this when we do signature checking in GHC.Tc.Module

instIsVisible :: VisibleOrphanModules -> ClsInst -> Bool Source #

Test if an instance is visible, by checking that its origin module is in VisibleOrphanModules. See Note [Instance lookup and orphan instances]