Safe Haskell | None |
---|
- type DFunId = Id
- data OverlapFlag
- = NoOverlap { }
- | OverlapOk { }
- | Incoherent { }
- type InstMatch = (ClsInst, [DFunInstType])
- type ClsInstLookupResult = ([InstMatch], [ClsInst], Bool)
- data ClsInst = ClsInst {}
- type DFunInstType = Maybe Type
- pprInstance :: ClsInst -> SDoc
- pprInstanceHdr :: ClsInst -> SDoc
- pprInstances :: [ClsInst] -> SDoc
- instanceHead :: ClsInst -> ([TyVar], ThetaType, Class, [Type])
- mkLocalInstance :: DFunId -> OverlapFlag -> ClsInst
- mkImportedInstance :: Name -> [Maybe Name] -> DFunId -> OverlapFlag -> ClsInst
- instanceDFunId :: ClsInst -> DFunId
- setInstanceDFunId :: ClsInst -> DFunId -> ClsInst
- instanceRoughTcs :: ClsInst -> [Maybe Name]
- type InstEnv = UniqFM ClsInstEnv
- emptyInstEnv :: InstEnv
- extendInstEnv :: InstEnv -> ClsInst -> InstEnv
- overwriteInstEnv :: InstEnv -> ClsInst -> InstEnv
- extendInstEnvList :: InstEnv -> [ClsInst] -> InstEnv
- lookupUniqueInstEnv :: (InstEnv, InstEnv) -> Class -> [Type] -> Either MsgDoc (ClsInst, [Type])
- lookupInstEnv' :: InstEnv -> Class -> [Type] -> ([InstMatch], [ClsInst])
- lookupInstEnv :: (InstEnv, InstEnv) -> Class -> [Type] -> ClsInstLookupResult
- instEnvElts :: InstEnv -> [ClsInst]
- classInstances :: (InstEnv, InstEnv) -> Class -> [ClsInst]
- instanceBindFun :: TyVar -> BindFlag
- instanceCantMatch :: [Maybe Name] -> [Maybe Name] -> Bool
- roughMatchTcs :: [Type] -> [Maybe Name]
Documentation
data OverlapFlag Source
NoOverlap | This instance must not overlap another |
OverlapOk | Silently ignore this instance if you find a more specific one that matches the constraint you are trying to resolve Example: constraint (Foo [Int]) instances (Foo [Int]) (Foo [a]) OverlapOk Since the second instance has the OverlapOk flag, the first instance will be chosen (otherwise its ambiguous which to choose) |
Incoherent | Like OverlapOk, but also ignore this instance if it doesn't match the constraint you are trying to resolve, but could match if the type variables in the constraint were instantiated Example: constraint (Foo [b])
instances (Foo [Int]) Incoherent
(Foo [a])
Without the Incoherent flag, we'd complain that
instantiating |
type InstMatch = (ClsInst, [DFunInstType])Source
type ClsInstLookupResult = ([InstMatch], [ClsInst], Bool)Source
type DFunInstType = Maybe TypeSource
pprInstance :: ClsInst -> SDocSource
pprInstanceHdr :: ClsInst -> SDocSource
pprInstances :: [ClsInst] -> SDocSource
mkLocalInstance :: DFunId -> OverlapFlag -> ClsInstSource
mkImportedInstance :: Name -> [Maybe Name] -> DFunId -> OverlapFlag -> ClsInstSource
setInstanceDFunId :: ClsInst -> DFunId -> ClsInstSource
instanceRoughTcs :: ClsInst -> [Maybe Name]Source
extendInstEnv :: InstEnv -> ClsInst -> InstEnvSource
overwriteInstEnv :: InstEnv -> ClsInst -> InstEnvSource
extendInstEnvList :: InstEnv -> [ClsInst] -> InstEnvSource
lookupUniqueInstEnv :: (InstEnv, InstEnv) -> 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, InstEnv) -> Class -> [Type] -> ClsInstLookupResultSource
instEnvElts :: InstEnv -> [ClsInst]Source
roughMatchTcs :: [Type] -> [Maybe Name]Source