Safe Haskell | None |
---|---|
Language | Haskell2010 |
GHC.Tc.Solver.Types
Description
Utility types used within the constraint solver
Synopsis
- type DictMap a = TcAppMap a
- emptyDictMap :: DictMap a
- findDictsByClass :: DictMap a -> Class -> Bag a
- addDict :: DictMap a -> Class -> [Type] -> a -> DictMap a
- addDictCt :: DictMap Ct -> TyCon -> [Type] -> Ct -> DictMap Ct
- addDictsByClass :: DictMap Ct -> Class -> Bag Ct -> DictMap Ct
- delDict :: DictMap a -> Class -> [Type] -> DictMap a
- foldDicts :: (a -> b -> b) -> DictMap a -> b -> b
- filterDicts :: (Ct -> Bool) -> DictMap Ct -> DictMap Ct
- findDict :: DictMap a -> CtLoc -> Class -> [Type] -> Maybe a
- dictsToBag :: DictMap a -> Bag a
- partitionDicts :: (Ct -> Bool) -> DictMap Ct -> (Bag Ct, DictMap Ct)
- type FunEqMap a = TcAppMap a
- emptyFunEqs :: TcAppMap a
- foldFunEqs :: (a -> b -> b) -> FunEqMap a -> b -> b
- findFunEq :: FunEqMap a -> TyCon -> [Type] -> Maybe a
- insertFunEq :: FunEqMap a -> TyCon -> [Type] -> a -> FunEqMap a
- findFunEqsByTyCon :: FunEqMap a -> TyCon -> [a]
- type TcAppMap a = DTyConEnv (ListMap LooseTypeMap a)
- emptyTcAppMap :: TcAppMap a
- isEmptyTcAppMap :: TcAppMap a -> Bool
- insertTcApp :: TcAppMap a -> TyCon -> [Type] -> a -> TcAppMap a
- alterTcApp :: forall a. TcAppMap a -> TyCon -> [Type] -> XT a -> TcAppMap a
- filterTcAppMap :: forall a. (a -> Bool) -> TcAppMap a -> TcAppMap a
- tcAppMapToBag :: TcAppMap a -> Bag a
- foldTcAppMap :: (a -> b -> b) -> TcAppMap a -> b -> b
- data EqualCtList
- pattern EqualCtList :: NonEmpty Ct -> EqualCtList
- equalCtListToList :: EqualCtList -> [Ct]
- filterEqualCtList :: (Ct -> Bool) -> EqualCtList -> Maybe EqualCtList
- unitEqualCtList :: Ct -> EqualCtList
- listToEqualCtList :: [Ct] -> Maybe EqualCtList
- addToEqualCtList :: Ct -> EqualCtList -> EqualCtList
Documentation
emptyDictMap :: DictMap a Source #
dictsToBag :: DictMap a -> Bag a Source #
emptyFunEqs :: TcAppMap a Source #
foldFunEqs :: (a -> b -> b) -> FunEqMap a -> b -> b Source #
findFunEqsByTyCon :: FunEqMap a -> TyCon -> [a] Source #
emptyTcAppMap :: TcAppMap a Source #
isEmptyTcAppMap :: TcAppMap a -> Bool Source #
tcAppMapToBag :: TcAppMap a -> Bag a Source #
foldTcAppMap :: (a -> b -> b) -> TcAppMap a -> b -> b Source #
data EqualCtList Source #
Instances
Outputable EqualCtList Source # | |
Defined in GHC.Tc.Solver.Types Methods ppr :: EqualCtList -> SDoc Source # |
pattern EqualCtList :: NonEmpty Ct -> EqualCtList Source #
Pattern synonym for easy unwrapping. NB: unidirectional to preserve invariants.
equalCtListToList :: EqualCtList -> [Ct] Source #
filterEqualCtList :: (Ct -> Bool) -> EqualCtList -> Maybe EqualCtList Source #
unitEqualCtList :: Ct -> EqualCtList Source #
listToEqualCtList :: [Ct] -> Maybe EqualCtList Source #
addToEqualCtList :: Ct -> EqualCtList -> EqualCtList Source #