Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data UniqSet a
- getUniqSet :: UniqSet a -> UniqFM a a
- pprUniqSet :: (a -> SDoc) -> UniqSet a -> SDoc
- emptyUniqSet :: UniqSet a
- unitUniqSet :: Uniquable a => a -> UniqSet a
- mkUniqSet :: Uniquable a => [a] -> UniqSet a
- addOneToUniqSet :: Uniquable a => UniqSet a -> a -> UniqSet a
- addListToUniqSet :: Uniquable a => UniqSet a -> [a] -> UniqSet a
- delOneFromUniqSet :: Uniquable a => UniqSet a -> a -> UniqSet a
- delOneFromUniqSet_Directly :: UniqSet a -> Unique -> UniqSet a
- delListFromUniqSet :: Uniquable a => UniqSet a -> [a] -> UniqSet a
- delListFromUniqSet_Directly :: UniqSet a -> [Unique] -> UniqSet a
- unionUniqSets :: UniqSet a -> UniqSet a -> UniqSet a
- unionManyUniqSets :: [UniqSet a] -> UniqSet a
- minusUniqSet :: UniqSet a -> UniqSet a -> UniqSet a
- uniqSetMinusUFM :: UniqSet key -> UniqFM key b -> UniqSet key
- uniqSetMinusUDFM :: UniqSet key -> UniqDFM key b -> UniqSet key
- intersectUniqSets :: UniqSet a -> UniqSet a -> UniqSet a
- disjointUniqSets :: UniqSet a -> UniqSet a -> Bool
- restrictUniqSetToUFM :: UniqSet key -> UniqFM key b -> UniqSet key
- uniqSetAny :: (a -> Bool) -> UniqSet a -> Bool
- uniqSetAll :: (a -> Bool) -> UniqSet a -> Bool
- elementOfUniqSet :: Uniquable a => a -> UniqSet a -> Bool
- elemUniqSet_Directly :: Unique -> UniqSet a -> Bool
- filterUniqSet :: (a -> Bool) -> UniqSet a -> UniqSet a
- filterUniqSet_Directly :: (Unique -> elt -> Bool) -> UniqSet elt -> UniqSet elt
- sizeUniqSet :: UniqSet a -> Int
- isEmptyUniqSet :: UniqSet a -> Bool
- lookupUniqSet :: Uniquable key => UniqSet key -> key -> Maybe key
- lookupUniqSet_Directly :: UniqSet a -> Unique -> Maybe a
- partitionUniqSet :: (a -> Bool) -> UniqSet a -> (UniqSet a, UniqSet a)
- mapUniqSet :: Uniquable b => (a -> b) -> UniqSet a -> UniqSet b
- unsafeUFMToUniqSet :: UniqFM a a -> UniqSet a
- nonDetEltsUniqSet :: UniqSet elt -> [elt]
- nonDetKeysUniqSet :: UniqSet elt -> [Unique]
- nonDetStrictFoldUniqSet :: (elt -> a -> a) -> a -> UniqSet elt -> a
Unique set type
Instances
Data a => Data (UniqSet a) Source # | |
Defined in GHC.Types.Unique.Set gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UniqSet a -> c (UniqSet a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (UniqSet a) Source # toConstr :: UniqSet a -> Constr Source # dataTypeOf :: UniqSet a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (UniqSet a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (UniqSet a)) Source # gmapT :: (forall b. Data b => b -> b) -> UniqSet a -> UniqSet a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UniqSet a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UniqSet a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> UniqSet a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> UniqSet a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UniqSet a -> m (UniqSet a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UniqSet a -> m (UniqSet a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UniqSet a -> m (UniqSet a) Source # | |
Monoid (UniqSet a) Source # | |
Semigroup (UniqSet a) Source # | |
Outputable a => Outputable (UniqSet a) Source # | |
Eq (UniqSet a) Source # | |
getUniqSet :: UniqSet a -> UniqFM a a Source #
Manipulating these sets
emptyUniqSet :: UniqSet a Source #
unitUniqSet :: Uniquable a => a -> UniqSet a Source #
unionManyUniqSets :: [UniqSet a] -> UniqSet a Source #
sizeUniqSet :: UniqSet a -> Int Source #
isEmptyUniqSet :: UniqSet a -> Bool Source #
lookupUniqSet :: Uniquable key => UniqSet key -> key -> Maybe key Source #
What's the point you might ask? We might have changed an object without it's key changing. In which case this lookup makes sense.
unsafeUFMToUniqSet :: UniqFM a a -> UniqSet a Source #
unsafeUFMToUniqSet
converts a
into a UniqFM
a
assuming, without checking, that it maps each UniqSet
aUnique
to a value
that has that Unique
. See Note [UniqSet invariant].
nonDetEltsUniqSet :: UniqSet elt -> [elt] Source #
nonDetKeysUniqSet :: UniqSet elt -> [Unique] Source #
nonDetStrictFoldUniqSet :: (elt -> a -> a) -> a -> UniqSet elt -> a Source #