Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type DFunId = Id
- type InstMatch = (ClsInst, [DFunInstType])
- type ClsInstLookupResult = ([InstMatch], [ClsInst], Bool)
- data OverlapFlag = OverlapFlag {}
- data OverlapMode
- setOverlapModeMaybe :: OverlapFlag -> Maybe OverlapMode -> OverlapFlag
- data ClsInst = ClsInst {}
- type DFunInstType = Maybe Type
- pprInstance :: ClsInst -> SDoc
- pprInstanceHdr :: ClsInst -> SDoc
- pprInstances :: [ClsInst] -> SDoc
- instanceHead :: ClsInst -> ([TyVar], Class, [Type])
- instanceSig :: ClsInst -> ([TyVar], [Type], Class, [Type])
- mkLocalInstance :: DFunId -> OverlapFlag -> [TyVar] -> Class -> [Type] -> ClsInst
- mkImportedInstance :: Name -> [Maybe Name] -> DFunId -> OverlapFlag -> IsOrphan -> ClsInst
- instanceDFunId :: ClsInst -> DFunId
- tidyClsInstDFun :: (DFunId -> DFunId) -> ClsInst -> ClsInst
- instanceRoughTcs :: ClsInst -> [Maybe Name]
- fuzzyClsInstCmp :: ClsInst -> ClsInst -> Ordering
- data IsOrphan
- isOrphan :: IsOrphan -> Bool
- notOrphan :: IsOrphan -> Bool
- data InstEnvs = InstEnvs {}
- type VisibleOrphanModules = ModuleSet
- type InstEnv = UniqFM ClsInstEnv
- emptyInstEnv :: InstEnv
- extendInstEnv :: InstEnv -> ClsInst -> InstEnv
- deleteFromInstEnv :: InstEnv -> ClsInst -> InstEnv
- identicalClsInstHead :: ClsInst -> ClsInst -> Bool
- extendInstEnvList :: InstEnv -> [ClsInst] -> InstEnv
- lookupUniqueInstEnv :: InstEnvs -> Class -> [Type] -> Either MsgDoc (ClsInst, [Type])
- lookupInstEnv' :: InstEnv -> VisibleOrphanModules -> Class -> [Type] -> ([InstMatch], [ClsInst])
- lookupInstEnv :: InstEnvs -> Class -> [Type] -> ClsInstLookupResult
- instEnvElts :: InstEnv -> [ClsInst]
- memberInstEnv :: InstEnv -> ClsInst -> Bool
- instIsVisible :: VisibleOrphanModules -> ClsInst -> Bool
- classInstances :: InstEnvs -> Class -> [ClsInst]
- orphNamesOfClsInst :: ClsInst -> NameSet
- instanceBindFun :: TyVar -> BindFlag
- instanceCantMatch :: [Maybe Name] -> [Maybe Name] -> Bool
- roughMatchTcs :: [Type] -> [Maybe Name]
Documentation
type InstMatch = (ClsInst, [DFunInstType]) Source
type ClsInstLookupResult = ([InstMatch], [ClsInst], Bool) Source
data OverlapFlag Source
The semantics allowed for overlapping instances for a particular
instance. See Note [Safe Haskell isSafeOverlap] (in lhs
) for a
explanation of the isSafeOverlap
field.
AnnKeywordId
:AnnOpen
'{-# OVERLAPPABLE'
or'{-# OVERLAPPING'
or'{-# OVERLAPS'
or'{-# INCOHERENT'
,AnnClose
`#-}`
,
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 {--} 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 |
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 |
type DFunInstType = Maybe Type Source
pprInstance :: ClsInst -> SDoc Source
pprInstanceHdr :: ClsInst -> SDoc Source
pprInstances :: [ClsInst] -> SDoc Source
mkLocalInstance :: DFunId -> OverlapFlag -> [TyVar] -> Class -> [Type] -> ClsInst Source
mkImportedInstance :: Name -> [Maybe Name] -> DFunId -> OverlapFlag -> IsOrphan -> ClsInst Source
instanceDFunId :: ClsInst -> DFunId Source
instanceRoughTcs :: ClsInst -> [Maybe Name] Source
fuzzyClsInstCmp :: ClsInst -> ClsInst -> Ordering Source
A fuzzy comparison function for class instances, intended for sorting instances before displaying them to the user.
Is this instance an orphan? If it is not an orphan, contains an OccName
witnessing the instance's non-orphanhood.
See Note [Orphans]
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).
extendInstEnv :: InstEnv -> ClsInst -> InstEnv Source
deleteFromInstEnv :: InstEnv -> ClsInst -> InstEnv Source
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 insenstive to alpha-renaming
extendInstEnvList :: InstEnv -> [ClsInst] -> InstEnv Source
lookupUniqueInstEnv :: InstEnvs -> Class -> [Type] -> Either MsgDoc (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' :: InstEnv -> VisibleOrphanModules -> Class -> [Type] -> ([InstMatch], [ClsInst]) Source
lookupInstEnv :: InstEnvs -> Class -> [Type] -> ClsInstLookupResult Source
See Note [Rules for instance lookup]
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 TcRnDriver
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]
classInstances :: InstEnvs -> Class -> [ClsInst] Source
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.
instanceBindFun :: TyVar -> BindFlag Source
roughMatchTcs :: [Type] -> [Maybe Name] Source