Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- type DFunId = Id
- type InstMatch = (ClsInst, [DFunInstType])
- type ClsInstLookupResult = ([InstMatch], PotentialUnifiers, [InstMatch])
- data CanonicalEvidence
- data PotentialUnifiers
- getCoherentUnifiers :: PotentialUnifiers -> [ClsInst]
- nullUnifiers :: PotentialUnifiers -> Bool
- data OverlapFlag = OverlapFlag {}
- data OverlapMode
- setOverlapModeMaybe :: OverlapFlag -> Maybe OverlapMode -> OverlapFlag
- data ClsInst = ClsInst {}
- type DFunInstType = Maybe Type
- pprInstance :: ClsInst -> SDoc
- pprInstanceHdr :: ClsInst -> SDoc
- pprDFunId :: DFunId -> SDoc
- pprInstances :: [ClsInst] -> SDoc
- instanceWarning :: ClsInst -> Maybe (WarningTxt GhcRn)
- instanceHead :: ClsInst -> ([TyVar], Class, [Type])
- instanceSig :: ClsInst -> ([TyVar], [Type], Class, [Type])
- mkLocalClsInst :: DFunId -> OverlapFlag -> [TyVar] -> Class -> [Type] -> Maybe (WarningTxt GhcRn) -> ClsInst
- mkImportedClsInst :: Name -> [RoughMatchTc] -> Name -> DFunId -> OverlapFlag -> IsOrphan -> Maybe (WarningTxt GhcRn) -> ClsInst
- instanceDFunId :: ClsInst -> DFunId
- updateClsInstDFuns :: (DFunId -> DFunId) -> InstEnv -> InstEnv
- updateClsInstDFun :: (DFunId -> DFunId) -> ClsInst -> ClsInst
- fuzzyClsInstCmp :: ClsInst -> ClsInst -> Ordering
- orphNamesOfClsInst :: ClsInst -> NameSet
- data InstEnvs = InstEnvs {}
- type VisibleOrphanModules = ModuleSet
- data InstEnv
- data LookupInstanceErrReason
- mkInstEnv :: [ClsInst] -> InstEnv
- emptyInstEnv :: InstEnv
- unionInstEnv :: InstEnv -> InstEnv -> InstEnv
- extendInstEnv :: InstEnv -> ClsInst -> InstEnv
- filterInstEnv :: (ClsInst -> Bool) -> InstEnv -> InstEnv
- deleteFromInstEnv :: InstEnv -> ClsInst -> InstEnv
- deleteDFunFromInstEnv :: InstEnv -> DFunId -> InstEnv
- anyInstEnv :: (ClsInst -> Bool) -> InstEnv -> Bool
- identicalClsInstHead :: ClsInst -> ClsInst -> Bool
- extendInstEnvList :: InstEnv -> [ClsInst] -> InstEnv
- lookupUniqueInstEnv :: InstEnvs -> Class -> [Type] -> Either LookupInstanceErrReason (ClsInst, [Type])
- lookupInstEnv :: Bool -> InstEnvs -> Class -> [Type] -> ClsInstLookupResult
- instEnvElts :: InstEnv -> [ClsInst]
- instEnvClasses :: InstEnv -> UniqDSet Class
- mapInstEnv :: (ClsInst -> ClsInst) -> InstEnv -> InstEnv
- memberInstEnv :: InstEnv -> ClsInst -> Bool
- instIsVisible :: VisibleOrphanModules -> ClsInst -> Bool
- classInstances :: InstEnvs -> Class -> [ClsInst]
- instanceBindFun :: BindFun
- classNameInstances :: InstEnvs -> Name -> [ClsInst]
- instanceCantMatch :: [RoughMatchTc] -> [RoughMatchTc] -> Bool
- roughMatchTcs :: [Type] -> [RoughMatchTc]
- isOverlappable :: ClsInst -> Bool
- isOverlapping :: ClsInst -> Bool
- isIncoherent :: ClsInst -> Bool
Documentation
type InstMatch = (ClsInst, [DFunInstType]) Source #
type ClsInstLookupResult = ([InstMatch], PotentialUnifiers, [InstMatch]) Source #
data CanonicalEvidence Source #
CanonicalEvidence
says whether a piece of evidence has a singleton type;
For example, given (d1 :: C Int), will any other (d2 :: C Int) do equally well?
See Note [Coherence and specialisation: overview] above, and
Note [Desugaring non-canonical evidence] in GHC.HsToCore.Binds
Instances
Outputable CanonicalEvidence Source # | |
Defined in GHC.Core.InstEnv ppr :: CanonicalEvidence -> SDoc Source # |
data PotentialUnifiers Source #
Instances
Outputable PotentialUnifiers Source # | |
Defined in GHC.Core.InstEnv ppr :: PotentialUnifiers -> SDoc Source # | |
Semigroup PotentialUnifiers Source # | |
Defined in GHC.Core.InstEnv (<>) :: PotentialUnifiers -> PotentialUnifiers -> PotentialUnifiers # sconcat :: NonEmpty PotentialUnifiers -> PotentialUnifiers # stimes :: Integral b => b -> PotentialUnifiers -> PotentialUnifiers # |
nullUnifiers :: PotentialUnifiers -> Bool Source #
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
Binary OverlapFlag Source # | |
Defined in GHC.Types.Basic put_ :: WriteBinHandle -> OverlapFlag -> IO () Source # put :: WriteBinHandle -> OverlapFlag -> IO (Bin OverlapFlag) Source # get :: ReadBinHandle -> IO OverlapFlag Source # | |
Outputable OverlapFlag Source # | |
Defined in GHC.Types.Basic ppr :: OverlapFlag -> SDoc Source # | |
Data OverlapFlag Source # | |
Defined in GHC.Types.Basic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OverlapFlag -> c OverlapFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OverlapFlag # toConstr :: OverlapFlag -> Constr # dataTypeOf :: OverlapFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OverlapFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OverlapFlag) # gmapT :: (forall b. Data b => b -> b) -> OverlapFlag -> OverlapFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> OverlapFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OverlapFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag # | |
Eq OverlapFlag Source # | |
Defined in GHC.Types.Basic (==) :: OverlapFlag -> OverlapFlag -> Bool # (/=) :: OverlapFlag -> OverlapFlag -> Bool # |
data OverlapMode Source #
NoOverlap SourceText | This instance must not overlap another |
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 |
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 |
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 |
Instances
Binary OverlapMode Source # | |
Defined in GHC.Types.Basic put_ :: WriteBinHandle -> OverlapMode -> IO () Source # put :: WriteBinHandle -> OverlapMode -> IO (Bin OverlapMode) Source # get :: ReadBinHandle -> IO OverlapMode Source # | |
Outputable OverlapMode Source # | |
Defined in GHC.Types.Basic ppr :: OverlapMode -> SDoc Source # | |
Data OverlapMode Source # | |
Defined in GHC.Types.Basic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OverlapMode -> c OverlapMode # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OverlapMode # toConstr :: OverlapMode -> Constr # dataTypeOf :: OverlapMode -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OverlapMode) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OverlapMode) # gmapT :: (forall b. Data b => b -> b) -> OverlapMode -> OverlapMode # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverlapMode -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverlapMode -> r # gmapQ :: (forall d. Data d => d -> u) -> OverlapMode -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OverlapMode -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode # | |
Eq OverlapMode Source # | |
Defined in GHC.Types.Basic (==) :: OverlapMode -> OverlapMode -> Bool # (/=) :: OverlapMode -> OverlapMode -> Bool # | |
type Anno OverlapMode Source # | |
Defined in GHC.Hs.Decls |
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.
ClsInst | |
|
Instances
NamedThing ClsInst Source # | |
Outputable ClsInst Source # | |
Data ClsInst Source # | |
Defined in GHC.Core.InstEnv gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClsInst -> c ClsInst # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ClsInst # toConstr :: ClsInst -> Constr # dataTypeOf :: ClsInst -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ClsInst) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ClsInst) # gmapT :: (forall b. Data b => b -> b) -> ClsInst -> ClsInst # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClsInst -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClsInst -> r # gmapQ :: (forall d. Data d => d -> u) -> ClsInst -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ClsInst -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClsInst -> m ClsInst # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInst -> m ClsInst # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInst -> m ClsInst # |
type DFunInstType = Maybe Type Source #
pprInstance :: ClsInst -> SDoc Source #
pprInstanceHdr :: ClsInst -> SDoc Source #
pprInstances :: [ClsInst] -> SDoc Source #
instanceWarning :: ClsInst -> Maybe (WarningTxt GhcRn) Source #
mkLocalClsInst :: DFunId -> OverlapFlag -> [TyVar] -> Class -> [Type] -> Maybe (WarningTxt GhcRn) -> ClsInst Source #
:: Name | the name of the class |
-> [RoughMatchTc] | the rough match signature of the instance |
-> Name | the |
-> DFunId | the |
-> OverlapFlag | may this instance overlap? |
-> IsOrphan | is this instance an orphan? |
-> Maybe (WarningTxt GhcRn) | warning emitted when solved |
-> ClsInst |
instanceDFunId :: ClsInst -> DFunId Source #
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
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).
Instances
data LookupInstanceErrReason Source #
Why a particular typeclass application couldn't be looked up.
LookupInstErrNotExact | Tyvars aren't an exact match. |
LookupInstErrFlexiVar | One of the tyvars is flexible. |
LookupInstErrNotFound | No matching instance was found. |
Instances
Generic LookupInstanceErrReason Source # | |||||
Defined in GHC.Core.InstEnv
| |||||
type Rep LookupInstanceErrReason Source # | |||||
Defined in GHC.Core.InstEnv type Rep LookupInstanceErrReason = D1 ('MetaData "LookupInstanceErrReason" "GHC.Core.InstEnv" "ghc-9.13-inplace" '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
instEnvElts :: InstEnv -> [ClsInst] Source #
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]
instanceCantMatch :: [RoughMatchTc] -> [RoughMatchTc] -> Bool Source #
roughMatchTcs :: [Type] -> [RoughMatchTc] Source #
isOverlappable :: ClsInst -> Bool Source #
isOverlapping :: ClsInst -> Bool Source #
isIncoherent :: ClsInst -> Bool Source #