never executed always true always false
    1 {-
    2 (c) The University of Glasgow 2006
    3 (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
    4 
    5 -}
    6 
    7 
    8 
    9 module GHC.Core.TyCon.Set (
   10         -- * TyCons set type
   11         TyConSet,
   12 
   13         -- ** Manipulating these sets
   14         emptyTyConSet, unitTyConSet, mkTyConSet, unionTyConSet, unionTyConSets,
   15         minusTyConSet, elemTyConSet, extendTyConSet, extendTyConSetList,
   16         delFromTyConSet, delListFromTyConSet, isEmptyTyConSet, filterTyConSet,
   17         intersectsTyConSet, disjointTyConSet, intersectTyConSet,
   18         nameSetAny, nameSetAll
   19     ) where
   20 
   21 import GHC.Prelude
   22 
   23 import GHC.Types.Unique.Set
   24 import GHC.Core.TyCon (TyCon)
   25 
   26 type TyConSet = UniqSet TyCon
   27 
   28 emptyTyConSet       :: TyConSet
   29 unitTyConSet        :: TyCon -> TyConSet
   30 extendTyConSetList   :: TyConSet -> [TyCon] -> TyConSet
   31 extendTyConSet    :: TyConSet -> TyCon -> TyConSet
   32 mkTyConSet          :: [TyCon] -> TyConSet
   33 unionTyConSet      :: TyConSet -> TyConSet -> TyConSet
   34 unionTyConSets  :: [TyConSet] -> TyConSet
   35 minusTyConSet       :: TyConSet -> TyConSet -> TyConSet
   36 elemTyConSet        :: TyCon -> TyConSet -> Bool
   37 isEmptyTyConSet     :: TyConSet -> Bool
   38 delFromTyConSet     :: TyConSet -> TyCon -> TyConSet
   39 delListFromTyConSet :: TyConSet -> [TyCon] -> TyConSet
   40 filterTyConSet      :: (TyCon -> Bool) -> TyConSet -> TyConSet
   41 intersectTyConSet   :: TyConSet -> TyConSet -> TyConSet
   42 intersectsTyConSet  :: TyConSet -> TyConSet -> Bool
   43 -- ^ True if there is a non-empty intersection.
   44 -- @s1 `intersectsTyConSet` s2@ doesn't compute @s2@ if @s1@ is empty
   45 disjointTyConSet    :: TyConSet -> TyConSet -> Bool
   46 
   47 isEmptyTyConSet    = isEmptyUniqSet
   48 emptyTyConSet      = emptyUniqSet
   49 unitTyConSet       = unitUniqSet
   50 mkTyConSet         = mkUniqSet
   51 extendTyConSetList = addListToUniqSet
   52 extendTyConSet     = addOneToUniqSet
   53 unionTyConSet      = unionUniqSets
   54 unionTyConSets     = unionManyUniqSets
   55 minusTyConSet      = minusUniqSet
   56 elemTyConSet       = elementOfUniqSet
   57 delFromTyConSet    = delOneFromUniqSet
   58 filterTyConSet     = filterUniqSet
   59 intersectTyConSet  = intersectUniqSets
   60 disjointTyConSet   = disjointUniqSets
   61 
   62 
   63 delListFromTyConSet set ns = foldl' delFromTyConSet set ns
   64 
   65 intersectsTyConSet s1 s2 = not (isEmptyTyConSet (s1 `intersectTyConSet` s2))
   66 
   67 nameSetAny :: (TyCon -> Bool) -> TyConSet -> Bool
   68 nameSetAny = uniqSetAny
   69 
   70 nameSetAll :: (TyCon -> Bool) -> TyConSet -> Bool
   71 nameSetAll = uniqSetAll