Copyright | (c) Oleg Grenrus 2014 |
---|---|
License | MIT |
Maintainer | oleg.grenrus@iki.fi |
Stability | experimental |
Portability | non-portable (tested with GHC only) |
Safe Haskell | Safe |
Language | Haskell2010 |
A trivial implementation of range sets.
This module is intended to be imported qualified, to avoid name clashes with Prelude functions, e.g.
import Data.RangeSet.List (RSet) import qualified Data.RangeSet.List as RSet
The implementation of RSet
is based on list.
Compared to Set
, this module imposes also Enum
restriction for many
functions. We must be able to identify consecutive elements to be able to
glue and split ranges properly.
The implementation assumes that
x < succ x pred x < x
and there aren't elements in between (not true for Float
and Double
). Also
succ
and pred
are never called for largest or smallest value respectively.
Synopsis
- data RSet a
- (\\) :: (Ord a, Enum a) => RSet a -> RSet a -> RSet a
- null :: RSet a -> Bool
- isFull :: (Eq a, Bounded a) => RSet a -> Bool
- size :: Enum a => RSet a -> Int
- member :: Ord a => a -> RSet a -> Bool
- notMember :: Ord a => a -> RSet a -> Bool
- lookupLT :: (Ord a, Enum a) => a -> RSet a -> Maybe a
- lookupGT :: (Ord a, Enum a) => a -> RSet a -> Maybe a
- lookupLE :: Ord a => a -> RSet a -> Maybe a
- lookupGE :: Ord a => a -> RSet a -> Maybe a
- containsRange :: Ord a => (a, a) -> RSet a -> Bool
- isSubsetOf :: Ord a => RSet a -> RSet a -> Bool
- valid :: (Ord a, Enum a, Bounded a) => RSet a -> Bool
- empty :: RSet a
- full :: Bounded a => RSet a
- singleton :: a -> RSet a
- singletonRange :: Ord a => (a, a) -> RSet a
- insert :: (Ord a, Enum a) => a -> RSet a -> RSet a
- insertRange :: (Ord a, Enum a) => (a, a) -> RSet a -> RSet a
- delete :: (Ord a, Enum a) => a -> RSet a -> RSet a
- deleteRange :: (Ord a, Enum a) => (a, a) -> RSet a -> RSet a
- union :: (Ord a, Enum a) => RSet a -> RSet a -> RSet a
- difference :: (Ord a, Enum a) => RSet a -> RSet a -> RSet a
- intersection :: Ord a => RSet a -> RSet a -> RSet a
- split :: (Ord a, Enum a) => a -> RSet a -> (RSet a, RSet a)
- splitMember :: (Ord a, Enum a) => a -> RSet a -> (RSet a, Bool, RSet a)
- findMin :: RSet a -> a
- findMax :: RSet a -> a
- complement :: (Ord a, Enum a, Bounded a) => RSet a -> RSet a
- elems :: Enum a => RSet a -> [a]
- toList :: Enum a => RSet a -> [a]
- fromList :: (Ord a, Enum a) => [a] -> RSet a
- fromAscList :: (Ord a, Enum a) => [a] -> RSet a
- toAscList :: Enum a => RSet a -> [a]
- toRangeList :: RSet a -> [(a, a)]
- fromRangeList :: (Ord a, Enum a) => [(a, a)] -> RSet a
- fromNormalizedRangeList :: [(a, a)] -> RSet a
- toSet :: Enum a => RSet a -> Set a
Range set type
Internally set is represented as sorted list of distinct inclusive ranges.
Instances
Eq a => Eq (RSet a) Source # | |
Ord a => Ord (RSet a) Source # | |
Show a => Show (RSet a) Source # | |
(Ord a, Enum a) => Semigroup (RSet a) Source # | |
(Ord a, Enum a) => Monoid (RSet a) Source # | |
NFData a => NFData (RSet a) Source # | |
Defined in Data.RangeSet.List | |
Hashable a => Hashable (RSet a) Source # | |
Defined in Data.RangeSet.List |
Operators
Query
lookupLT :: (Ord a, Enum a) => a -> RSet a -> Maybe a Source #
O(n). Find largest element smaller than the given one.
lookupGT :: (Ord a, Enum a) => a -> RSet a -> Maybe a Source #
O(n). Find smallest element greater than the given one.
lookupLE :: Ord a => a -> RSet a -> Maybe a Source #
O(n). Find largest element smaller or equal to than the given one.
lookupGE :: Ord a => a -> RSet a -> Maybe a Source #
O(n). Find smallest element greater or equal to than the given one.
containsRange :: Ord a => (a, a) -> RSet a -> Bool Source #
O(n). Is the entire range contained within the set?
isSubsetOf :: Ord a => RSet a -> RSet a -> Bool Source #
O(n+m). Is this a subset?
(s1
tells whether isSubsetOf
s2)s1
is a subset of s2
.
valid :: (Ord a, Enum a, Bounded a) => RSet a -> Bool Source #
O(n). Ensure that a set is valid. All functions should return valid sets
except those with unchecked preconditions: fromAscList
,
fromNormalizedRangeList
Construction
singletonRange :: Ord a => (a, a) -> RSet a Source #
O(1). Create a continuos range set.
insertRange :: (Ord a, Enum a) => (a, a) -> RSet a -> RSet a Source #
O(n). Insert a continuos range in a set.
deleteRange :: (Ord a, Enum a) => (a, a) -> RSet a -> RSet a Source #
/O(n). Delete a continuos range from a set.
Combine
Filter
split :: (Ord a, Enum a) => a -> RSet a -> (RSet a, RSet a) Source #
O(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, Enum a) => a -> RSet a -> (RSet a, Bool, RSet a) Source #
O(n). Performs a split
but also returns whether the pivot
element was found in the original set.
Min/Max
Complement
Conversion
elems :: Enum a => RSet a -> [a] Source #
O(n*r). An alias of toAscList
. The elements of a set in ascending
order. r is the size of longest range.
toList :: Enum a => RSet a -> [a] Source #
O(n*r). Convert the set to a list of elements. r is the size of longest range.
fromList :: (Ord a, Enum a) => [a] -> RSet a Source #
O(n*log n). Create a set from a list of elements.
fromAscList :: (Ord a, Enum a) => [a] -> RSet a Source #
O(n). Create a set from a list of ascending elements.
The precondition is not checked. You may use valid
to check the result.
toAscList :: Enum a => RSet a -> [a] Source #
O(n*r). Convert the set to an ascending list of elements.
toRangeList :: RSet a -> [(a, a)] Source #
O(1). Convert the set to a list of range pairs.
fromRangeList :: (Ord a, Enum a) => [(a, a)] -> RSet a Source #
O(n*log n). Create a set from a list of range pairs.
fromNormalizedRangeList :: [(a, a)] -> RSet a Source #
O(1). Convert a normalized, non-adjacent, ascending list of ranges to a set.
The precondition is not checked. In general you should only use this
function on the result of toRangeList
or ensure valid
on the result.