set-extra-1.4.2: Functions that could be added to Data.Set.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Set.Extra

Synopsis

Documentation

module Data.Set

mapM :: (Monad m, Ord b) => (a -> m b) -> Set a -> m (Set b) Source #

mapM_ :: (Monad m, Ord b) => (a -> m b) -> Set a -> m () Source #

filterM :: (Ord a, Monad m) => (a -> m Bool) -> Set a -> m (Set a) Source #

catMaybes :: Ord a => Set (Maybe a) -> Set a Source #

mapMaybe :: (Ord a, Ord b) => (a -> Maybe b) -> Set a -> Set b Source #

flatten :: Ord a => Set (Set a) -> Set a Source #

concatMap :: (Ord a, Ord b) => (a -> Set b) -> Set a -> Set b Source #

concatMapM :: (Monad m, Ord a, Ord b) => (a -> m (Set b)) -> Set a -> m (Set b) Source #

any :: Ord a => (a -> Bool) -> Set a -> Bool Source #

all :: Ord a => (a -> Bool) -> Set a -> Bool Source #

ss :: Ord a => a -> Set (Set a) Source #

Create a singleton set containing a singleton set of a.

toSS :: Ord a => [[a]] -> Set (Set a) Source #

Turn a list of lists into a set of sets.

fromSS :: Ord a => Set (Set a) -> [[a]] Source #

ssMapM :: (Monad m, Ord a, Ord b) => (a -> m b) -> Set (Set a) -> m (Set (Set b)) Source #

distrib :: Ord a => Set (Set a) -> Set (Set a) -> Set (Set a) Source #

distrib {a, b, c} {d, e, f} -> {a+d, a+e, a+f, b+d, b+e, b+f, c+d, c+e, c+f}

cartesianProduct :: Set a -> Set b -> Set (a, b) #

\(O(nm)\). Calculate the Cartesian product of two sets.

cartesianProduct xs ys = fromList $ liftA2 (,) (toList xs) (toList ys)

Example:

cartesianProduct (fromList [1,2]) (fromList ['a','b']) =
  fromList [(1,'a'), (1,'b'), (2,'a'), (2,'b')]

Since: containers-0.5.11

groupBy :: (Ord a, Ord b) => (a -> b) -> Set a -> Map b (Set a) Source #

powerset :: Ord a => Set a -> Set (Set a) Source #

partitionM :: (Monad m, Ord a) => (a -> m Bool) -> Set a -> m (Set a, Set a) Source #

unzip :: (Ord a, Ord b) => Set (a, b) -> (Set a, Set b) Source #

gFind :: forall a b. (Data a, Typeable b, Ord b) => a -> Set b Source #