never executed always true always false
    1 -- (c) Bartosz Nitka, Facebook, 2015
    2 
    3 -- |
    4 -- Specialised deterministic sets, for things with @Uniques@
    5 --
    6 -- Based on 'UniqDFM's (as you would expect).
    7 -- See Note [Deterministic UniqFM] in "GHC.Types.Unique.DFM" for explanation why we need it.
    8 --
    9 -- Basically, the things need to be in class 'Uniquable'.
   10 
   11 {-# LANGUAGE DeriveDataTypeable #-}
   12 
   13 module GHC.Types.Unique.DSet (
   14         -- * Unique set type
   15         UniqDSet,    -- type synonym for UniqFM a
   16         getUniqDSet,
   17         pprUniqDSet,
   18 
   19         -- ** Manipulating these sets
   20         delOneFromUniqDSet, delListFromUniqDSet,
   21         emptyUniqDSet,
   22         unitUniqDSet,
   23         mkUniqDSet,
   24         addOneToUniqDSet, addListToUniqDSet,
   25         unionUniqDSets, unionManyUniqDSets,
   26         minusUniqDSet, uniqDSetMinusUniqSet,
   27         intersectUniqDSets, uniqDSetIntersectUniqSet,
   28         nonDetStrictFoldUniqDSet,
   29         elementOfUniqDSet,
   30         filterUniqDSet,
   31         sizeUniqDSet,
   32         isEmptyUniqDSet,
   33         lookupUniqDSet,
   34         uniqDSetToList,
   35         partitionUniqDSet,
   36         mapUniqDSet
   37     ) where
   38 
   39 import GHC.Prelude
   40 
   41 import GHC.Utils.Outputable
   42 import GHC.Types.Unique.DFM
   43 import GHC.Types.Unique.Set
   44 import GHC.Types.Unique
   45 
   46 import Data.Coerce
   47 import Data.Data
   48 
   49 -- See Note [UniqSet invariant] in GHC.Types.Unique.Set for why we want a newtype here.
   50 -- Beyond preserving invariants, we may also want to 'override' typeclass
   51 -- instances.
   52 
   53 newtype UniqDSet a = UniqDSet {getUniqDSet' :: UniqDFM a a}
   54                    deriving (Data)
   55 
   56 emptyUniqDSet :: UniqDSet a
   57 emptyUniqDSet = UniqDSet emptyUDFM
   58 
   59 unitUniqDSet :: Uniquable a => a -> UniqDSet a
   60 unitUniqDSet x = UniqDSet (unitUDFM x x)
   61 
   62 mkUniqDSet :: Uniquable a => [a] -> UniqDSet a
   63 mkUniqDSet = foldl' addOneToUniqDSet emptyUniqDSet
   64 
   65 -- The new element always goes to the right of existing ones.
   66 addOneToUniqDSet :: Uniquable a => UniqDSet a -> a -> UniqDSet a
   67 addOneToUniqDSet (UniqDSet set) x = UniqDSet (addToUDFM set x x)
   68 
   69 addListToUniqDSet :: Uniquable a => UniqDSet a -> [a] -> UniqDSet a
   70 addListToUniqDSet = foldl' addOneToUniqDSet
   71 
   72 delOneFromUniqDSet :: Uniquable a => UniqDSet a -> a -> UniqDSet a
   73 delOneFromUniqDSet (UniqDSet s) = UniqDSet . delFromUDFM s
   74 
   75 delListFromUniqDSet :: Uniquable a => UniqDSet a -> [a] -> UniqDSet a
   76 delListFromUniqDSet (UniqDSet s) = UniqDSet . delListFromUDFM s
   77 
   78 unionUniqDSets :: UniqDSet a -> UniqDSet a -> UniqDSet a
   79 unionUniqDSets (UniqDSet s) (UniqDSet t) = UniqDSet (plusUDFM s t)
   80 
   81 unionManyUniqDSets :: [UniqDSet a] -> UniqDSet a
   82 unionManyUniqDSets []     = emptyUniqDSet
   83 unionManyUniqDSets (x:xs) = foldl' unionUniqDSets x xs
   84 
   85 minusUniqDSet :: UniqDSet a -> UniqDSet a -> UniqDSet a
   86 minusUniqDSet (UniqDSet s) (UniqDSet t) = UniqDSet (minusUDFM s t)
   87 
   88 uniqDSetMinusUniqSet :: UniqDSet a -> UniqSet a -> UniqDSet a
   89 uniqDSetMinusUniqSet xs ys
   90   = UniqDSet (udfmMinusUFM (getUniqDSet xs) (getUniqSet ys))
   91 
   92 intersectUniqDSets :: UniqDSet a -> UniqDSet a -> UniqDSet a
   93 intersectUniqDSets (UniqDSet s) (UniqDSet t) = UniqDSet (intersectUDFM s t)
   94 
   95 uniqDSetIntersectUniqSet :: UniqDSet a -> UniqSet a -> UniqDSet a
   96 uniqDSetIntersectUniqSet xs ys
   97   = UniqDSet (udfmIntersectUFM (getUniqDSet xs) (getUniqSet ys))
   98 
   99 -- See Note [Deterministic UniqFM] to learn about nondeterminism.
  100 -- If you use this please provide a justification why it doesn't introduce
  101 -- nondeterminism.
  102 nonDetStrictFoldUniqDSet :: (a -> b -> b) -> b -> UniqDSet a -> b
  103 nonDetStrictFoldUniqDSet f acc (UniqDSet s) = nonDetStrictFoldUDFM f acc s
  104 
  105 elementOfUniqDSet :: Uniquable a => a -> UniqDSet a -> Bool
  106 elementOfUniqDSet k = elemUDFM k . getUniqDSet
  107 
  108 filterUniqDSet :: (a -> Bool) -> UniqDSet a -> UniqDSet a
  109 filterUniqDSet p (UniqDSet s) = UniqDSet (filterUDFM p s)
  110 
  111 sizeUniqDSet :: UniqDSet a -> Int
  112 sizeUniqDSet = sizeUDFM . getUniqDSet
  113 
  114 isEmptyUniqDSet :: UniqDSet a -> Bool
  115 isEmptyUniqDSet = isNullUDFM . getUniqDSet
  116 
  117 lookupUniqDSet :: Uniquable a => UniqDSet a -> a -> Maybe a
  118 lookupUniqDSet = lookupUDFM . getUniqDSet
  119 
  120 uniqDSetToList :: UniqDSet a -> [a]
  121 uniqDSetToList = eltsUDFM . getUniqDSet
  122 
  123 partitionUniqDSet :: (a -> Bool) -> UniqDSet a -> (UniqDSet a, UniqDSet a)
  124 partitionUniqDSet p = coerce . partitionUDFM p . getUniqDSet
  125 
  126 -- See Note [UniqSet invariant] in GHC.Types.Unique.Set
  127 mapUniqDSet :: Uniquable b => (a -> b) -> UniqDSet a -> UniqDSet b
  128 mapUniqDSet f = mkUniqDSet . map f . uniqDSetToList
  129 
  130 -- Two 'UniqDSet's are considered equal if they contain the same
  131 -- uniques.
  132 instance Eq (UniqDSet a) where
  133   UniqDSet a == UniqDSet b = equalKeysUDFM a b
  134 
  135 getUniqDSet :: UniqDSet a -> UniqDFM a a
  136 getUniqDSet = getUniqDSet'
  137 
  138 instance Outputable a => Outputable (UniqDSet a) where
  139   ppr = pprUniqDSet ppr
  140 
  141 pprUniqDSet :: (a -> SDoc) -> UniqDSet a -> SDoc
  142 pprUniqDSet f = braces . pprWithCommas f . uniqDSetToList