Safe Haskell | None |
---|---|
Language | Haskell2010 |
Maps containing non-overlapping intervals.
Synopsis
- class IsBasicRangeMap a m | m -> a where
- several :: (IsBasicRangeMap a hl, Monoid hl) => [Ranges] -> a -> hl
- newtype PairInt a = PairInt (Pair Int a)
- newtype RangeMap a = RangeMap {}
- rangeMapInvariant :: RangeMap a -> Bool
- fromNonOverlappingNonEmptyAscendingList :: [(Range, a)] -> RangeMap a
- insert :: (a -> a -> a) -> Range -> a -> RangeMap a -> RangeMap a
- splitAt :: Int -> RangeMap a -> (RangeMap a, RangeMap a)
- insideAndOutside :: Range -> RangeMap a -> (RangeMap a, RangeMap a)
- restrictTo :: Range -> RangeMap a -> RangeMap a
Documentation
class IsBasicRangeMap a m | m -> a where Source #
A class that is intended to make it easy to swap between different range map implementations.
Note that some RangeMap
operations are not included in this
class.
singleton :: Ranges -> a -> m Source #
The map
contains the ranges from singleton
rs xrs
, and
every position in those ranges is associated with x
.
toMap :: m -> IntMap a Source #
Converts range maps to IntMap
s from positions to values.
toList :: m -> [(Range, a)] Source #
Converts the map to a list. The ranges are non-overlapping and non-empty, and earlier ranges precede later ones in the list.
coveringRange :: m -> Maybe Range Source #
Returns the smallest range covering everything in the map (or
Nothing
, if the range would be empty).
Note that the default implementation of this operation might be inefficient.
Instances
several :: (IsBasicRangeMap a hl, Monoid hl) => [Ranges] -> a -> hl Source #
A strict pair type where the first argument must be an Int
.
This type is included because there is no NFData
instance for
Pair
in the package strict
before version 4.
PairInt (Pair Int a) |
Maps containing non-overlapping intervals.
The implementation does not use IntMap, because IntMap does not come with a constant-time size function.
Note the invariant which RangeMap
s should satisfy
(rangeMapInvariant
).
Instances
rangeMapInvariant :: RangeMap a -> Bool Source #
Invariant for RangeMap
.
The ranges must not be empty, and they must not overlap.
fromNonOverlappingNonEmptyAscendingList :: [(Range, a)] -> RangeMap a Source #
Converts a list of pairs of ranges and values to a RangeMap
.
The ranges have to be non-overlapping and non-empty, and earlier
ranges have to precede later ones.
splitAt :: Int -> RangeMap a -> (RangeMap a, RangeMap a) Source #
The value of
is a pair splitAt
p f(f1, f2)
which contains
everything from f
. All the positions in f1
are less than p
,
and all the positions in f2
are greater than or equal to p
.