Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Set
. Import as:
import qualified RIO.Set as Set
This module does not export any partial or unchecked functions. For those, see RIO.Set.Partial and RIO.Set.Unchecked
Synopsis
- data Set a
- (\\) :: Ord a => Set a -> Set a -> Set a
- null :: Set a -> Bool
- size :: Set a -> Int
- member :: Ord a => a -> Set a -> Bool
- notMember :: Ord a => a -> Set a -> Bool
- lookupLT :: Ord a => a -> Set a -> Maybe a
- lookupGT :: Ord a => a -> Set a -> Maybe a
- lookupLE :: Ord a => a -> Set a -> Maybe a
- lookupGE :: Ord a => a -> Set a -> Maybe a
- isSubsetOf :: Ord a => Set a -> Set a -> Bool
- isProperSubsetOf :: Ord a => Set a -> Set a -> Bool
- empty :: Set a
- singleton :: a -> Set a
- insert :: Ord a => a -> Set a -> Set a
- delete :: Ord a => a -> Set a -> Set a
- union :: Ord a => Set a -> Set a -> Set a
- unions :: (Foldable f, Ord a) => f (Set a) -> Set a
- difference :: Ord a => Set a -> Set a -> Set a
- intersection :: Ord a => Set a -> Set a -> Set a
- filter :: (a -> Bool) -> Set a -> Set a
- takeWhileAntitone :: (a -> Bool) -> Set a -> Set a
- dropWhileAntitone :: (a -> Bool) -> Set a -> Set a
- spanAntitone :: (a -> Bool) -> Set a -> (Set a, Set a)
- partition :: (a -> Bool) -> Set a -> (Set a, Set a)
- split :: Ord a => a -> Set a -> (Set a, Set a)
- splitMember :: Ord a => a -> Set a -> (Set a, Bool, Set a)
- splitRoot :: Set a -> [Set a]
- lookupIndex :: Ord a => a -> Set a -> Maybe Int
- take :: Int -> Set a -> Set a
- drop :: Int -> Set a -> Set a
- splitAt :: Int -> Set a -> (Set a, Set a)
- map :: Ord b => (a -> b) -> Set a -> Set b
- foldr :: (a -> b -> b) -> b -> Set a -> b
- foldl :: (a -> b -> a) -> a -> Set b -> a
- foldr' :: (a -> b -> b) -> b -> Set a -> b
- foldl' :: (a -> b -> a) -> a -> Set b -> a
- lookupMin :: Set a -> Maybe a
- lookupMax :: Set a -> Maybe a
- deleteMin :: Set a -> Set a
- deleteMax :: Set a -> Set a
- maxView :: Set a -> Maybe (a, Set a)
- minView :: Set a -> Maybe (a, Set a)
- elems :: Set a -> [a]
- toList :: Set a -> [a]
- fromList :: Ord a => [a] -> Set a
- toAscList :: Set a -> [a]
- toDescList :: Set a -> [a]
- showTree :: Show a => Set a -> String
- showTreeWith :: Show a => Bool -> Bool -> Set a -> String
- valid :: Ord a => Set a -> Bool
Set type
A set of values a
.
Instances
Foldable Set | |
Defined in Data.Set.Internal fold :: Monoid m => Set m -> m # foldMap :: Monoid m => (a -> m) -> Set a -> m # foldr :: (a -> b -> b) -> b -> Set a -> b # foldr' :: (a -> b -> b) -> b -> Set a -> b # foldl :: (b -> a -> b) -> b -> Set a -> b # foldl' :: (b -> a -> b) -> b -> Set a -> b # foldr1 :: (a -> a -> a) -> Set a -> a # foldl1 :: (a -> a -> a) -> Set a -> a # elem :: Eq a => a -> Set a -> Bool # maximum :: Ord a => Set a -> a # | |
Eq1 Set | Since: containers-0.5.9 |
Ord1 Set | Since: containers-0.5.9 |
Defined in Data.Set.Internal | |
Show1 Set | Since: containers-0.5.9 |
Ord a => IsList (Set a) | Since: containers-0.5.6.2 |
Eq a => Eq (Set a) | |
(Data a, Ord a) => Data (Set a) | |
Defined in Data.Set.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Set a -> c (Set a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Set a) # dataTypeOf :: Set a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Set a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Set a)) # gmapT :: (forall b. Data b => b -> b) -> Set a -> Set a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r # gmapQ :: (forall d. Data d => d -> u) -> Set a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Set a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # | |
Ord a => Ord (Set a) | |
(Read a, Ord a) => Read (Set a) | |
Show a => Show (Set a) | |
Ord a => Semigroup (Set a) | Since: containers-0.5.7 |
Ord a => Monoid (Set a) | |
NFData a => NFData (Set a) | |
Defined in Data.Set.Internal | |
type Item (Set a) | |
Defined in Data.Set.Internal |
Operators
Query
lookupLT :: Ord a => a -> Set a -> Maybe a #
O(log n). Find largest element smaller than the given one.
lookupLT 3 (fromList [3, 5]) == Nothing lookupLT 5 (fromList [3, 5]) == Just 3
lookupGT :: Ord a => a -> Set a -> Maybe a #
O(log n). Find smallest element greater than the given one.
lookupGT 4 (fromList [3, 5]) == Just 5 lookupGT 5 (fromList [3, 5]) == Nothing
lookupLE :: Ord a => a -> Set a -> Maybe a #
O(log n). Find largest element smaller or equal to the given one.
lookupLE 2 (fromList [3, 5]) == Nothing lookupLE 4 (fromList [3, 5]) == Just 3 lookupLE 5 (fromList [3, 5]) == Just 5
lookupGE :: Ord a => a -> Set a -> Maybe a #
O(log n). Find smallest element greater or equal to the given one.
lookupGE 3 (fromList [3, 5]) == Just 3 lookupGE 4 (fromList [3, 5]) == Just 5 lookupGE 6 (fromList [3, 5]) == Nothing
isSubsetOf :: Ord a => Set a -> Set a -> Bool #
O(n+m). Is this a subset?
(s1 `isSubsetOf` s2)
tells whether s1
is a subset of s2
.
isProperSubsetOf :: Ord a => Set a -> Set a -> Bool #
O(n+m). Is this a proper subset? (ie. a subset but not equal).
Construction
insert :: Ord a => a -> Set a -> Set a #
O(log n). Insert an element in a set. If the set already contains an element equal to the given value, it is replaced with the new value.
Combine
union :: Ord a => Set a -> Set a -> Set a #
O(m*log(n/m + 1)), m <= n. The union of two sets, preferring the first set when equal elements are encountered.
intersection :: Ord a => Set a -> Set a -> Set a #
O(m*log(n/m + 1)), m <= n. The intersection of two sets. Elements of the result come from the first set, so for example
import qualified Data.Set as S data AB = A | B deriving Show instance Ord AB where compare _ _ = EQ instance Eq AB where _ == _ = True main = print (S.singleton A `S.intersection` S.singleton B, S.singleton B `S.intersection` S.singleton A)
prints (fromList [A],fromList [B])
.
Filter
takeWhileAntitone :: (a -> Bool) -> Set a -> Set a #
O(log n). Take while a predicate on the elements holds.
The user is responsible for ensuring that for all elements j
and k
in the set,
j < k ==> p j >= p k
. See note at spanAntitone
.
takeWhileAntitone p =fromDistinctAscList
.takeWhile
p .toList
takeWhileAntitone p =filter
p
Since: containers-0.5.8
dropWhileAntitone :: (a -> Bool) -> Set a -> Set a #
O(log n). Drop while a predicate on the elements holds.
The user is responsible for ensuring that for all elements j
and k
in the set,
j < k ==> p j >= p k
. See note at spanAntitone
.
dropWhileAntitone p =fromDistinctAscList
.dropWhile
p .toList
dropWhileAntitone p =filter
(not . p)
Since: containers-0.5.8
spanAntitone :: (a -> Bool) -> Set a -> (Set a, Set a) #
O(log n). Divide a set at the point where a predicate on the elements stops holding.
The user is responsible for ensuring that for all elements j
and k
in the set,
j < k ==> p j >= p k
.
spanAntitone p xs = (takeWhileAntitone
p xs,dropWhileAntitone
p xs) spanAntitone p xs = partition p xs
Note: if p
is not actually antitone, then spanAntitone
will split the set
at some unspecified point where the predicate switches from holding to not
holding (where the predicate is seen to hold before the first element and to fail
after the last element).
Since: containers-0.5.8
partition :: (a -> Bool) -> Set a -> (Set a, Set a) #
O(n). Partition the set into two sets, one with all elements that satisfy
the predicate and one with all elements that don't satisfy the predicate.
See also split
.
split :: Ord a => a -> Set a -> (Set a, Set a) #
O(log n). The expression (
) is a pair split
x set(set1,set2)
where set1
comprises the elements of set
less than x
and set2
comprises the elements of set
greater than x
.
splitMember :: Ord a => a -> Set a -> (Set a, Bool, Set a) #
O(log n). Performs a split
but also returns whether the pivot
element was found in the original set.
splitRoot :: Set a -> [Set a] #
O(1). Decompose a set into pieces based on the structure of the underlying tree. This function is useful for consuming a set in parallel.
No guarantee is made as to the sizes of the pieces; an internal, but deterministic process determines this. However, it is guaranteed that the pieces returned will be in ascending order (all elements in the first subset less than all elements in the second, and so on).
Examples:
splitRoot (fromList [1..6]) == [fromList [1,2,3],fromList [4],fromList [5,6]]
splitRoot empty == []
Note that the current implementation does not return more than three subsets, but you should not depend on this behaviour because it can change in the future without notice.
Since: containers-0.5.4
Indexed
lookupIndex :: Ord a => a -> Set a -> Maybe Int #
O(log n). Lookup the index of an element, which is its zero-based index in
the sorted sequence of elements. The index is a number from 0 up to, but not
including, the size
of the set.
isJust (lookupIndex 2 (fromList [5,3])) == False fromJust (lookupIndex 3 (fromList [5,3])) == 0 fromJust (lookupIndex 5 (fromList [5,3])) == 1 isJust (lookupIndex 6 (fromList [5,3])) == False
Since: containers-0.5.4
take :: Int -> Set a -> Set a #
Take a given number of elements in order, beginning with the smallest ones.
take n =fromDistinctAscList
.take
n .toAscList
Since: containers-0.5.8
drop :: Int -> Set a -> Set a #
Drop a given number of elements in order, beginning with the smallest ones.
drop n =fromDistinctAscList
.drop
n .toAscList
Since: containers-0.5.8
Map
map :: Ord b => (a -> b) -> Set a -> Set b #
O(n*log n).
is the set obtained by applying map
f sf
to each element of s
.
It's worth noting that the size of the result may be smaller if,
for some (x,y)
, x /= y && f x == f y
Folds
Strict folds
foldr' :: (a -> b -> b) -> b -> Set a -> b #
O(n). A strict version of foldr
. Each application of the operator is
evaluated before using the result in the next application. This
function is strict in the starting value.
foldl' :: (a -> b -> a) -> a -> Set b -> a #
O(n). A strict version of foldl
. Each application of the operator is
evaluated before using the result in the next application. This
function is strict in the starting value.
Min/Max
O(log n). Delete the minimal element. Returns an empty set if the set is empty.
O(log n). Delete the maximal element. Returns an empty set if the set is empty.
maxView :: Set a -> Maybe (a, Set a) #
O(log n). Retrieves the maximal key of the set, and the set
stripped of that element, or Nothing
if passed an empty set.
minView :: Set a -> Maybe (a, Set a) #
O(log n). Retrieves the minimal key of the set, and the set
stripped of that element, or Nothing
if passed an empty set.
Conversion
List
O(n). An alias of toAscList
. The elements of a set in ascending order.
Subject to list fusion.
fromList :: Ord a => [a] -> Set a #
O(n*log n). Create a set from a list of elements.
If the elements are ordered, a linear-time implementation is used,
with the performance equal to fromDistinctAscList
.
Ordered list
O(n). Convert the set to an ascending list of elements. Subject to list fusion.
toDescList :: Set a -> [a] #
O(n). Convert the set to a descending list of elements. Subject to list fusion.
Debugging
showTree :: Show a => Set a -> String #
O(n). Show the tree that implements the set. The tree is shown in a compressed, hanging format.
showTreeWith :: Show a => Bool -> Bool -> Set a -> String #
O(n). The expression (showTreeWith hang wide map
) shows
the tree that implements the set. If hang
is
True
, a hanging tree is shown otherwise a rotated tree is shown. If
wide
is True
, an extra wide version is shown.
Set> putStrLn $ showTreeWith True False $ fromDistinctAscList [1..5] 4 +--2 | +--1 | +--3 +--5 Set> putStrLn $ showTreeWith True True $ fromDistinctAscList [1..5] 4 | +--2 | | | +--1 | | | +--3 | +--5 Set> putStrLn $ showTreeWith False True $ fromDistinctAscList [1..5] +--5 | 4 | | +--3 | | +--2 | +--1