data-interval-2.1.0: Interval datatype, interval arithmetic and interval-based containers
Copyright(c) Masahiro Sakai 2016
LicenseBSD-style
Maintainermasahiro.sakai@gmail.com
Stabilityprovisional
Portabilitynon-portable (BangPatterns, TupleSections)
Safe HaskellSafe
LanguageHaskell2010

Data.IntervalMap.Strict

Description

Mapping from intervals to values.

API of this module is strict in both the keys and the values. If you need value-lazy maps, use Data.IntervalMap.Lazy instead. The IntervalMap type itself is shared between the lazy and strict modules, meaning that the same IntervalMap value can be passed to functions in both modules (although that is rarely needed).

These modules are intended to be imported qualified, to avoid name clashes with Prelude functions, e.g.

 import Data.IntervalMap.Strict (IntervalMap)
 import qualified Data.IntervalMap.Strict as IntervalMap
Synopsis

Strictness properties

This module satisfies the following strictness properties:

  1. Key arguments are evaluated to WHNF;
  2. Keys and values are evaluated to WHNF before they are stored in the map.

Here's an example illustrating the first property:

delete undefined m  ==  undefined

Here are some examples that illustrate the second property:

map (\ v -> undefined) m  ==  undefined      -- m is not empty
mapKeysMonotonic (\ k -> undefined) m  ==  undefined  -- m is not empty

IntervalMap type

data IntervalMap r a Source #

A Map from non-empty, disjoint intervals over k to values a.

Unlike IntervalSet, IntervalMap never merge adjacent mappings, even if adjacent intervals are connected and mapped to the same value.

Instances

Instances details
Ord k => Functor (IntervalMap k) Source # 
Instance details

Defined in Data.IntervalMap.Base

Methods

fmap :: (a -> b) -> IntervalMap k a -> IntervalMap k b #

(<$) :: a -> IntervalMap k b -> IntervalMap k a #

Ord k => Foldable (IntervalMap k) Source # 
Instance details

Defined in Data.IntervalMap.Base

Methods

fold :: Monoid m => IntervalMap k m -> m #

foldMap :: Monoid m => (a -> m) -> IntervalMap k a -> m #

foldMap' :: Monoid m => (a -> m) -> IntervalMap k a -> m #

foldr :: (a -> b -> b) -> b -> IntervalMap k a -> b #

foldr' :: (a -> b -> b) -> b -> IntervalMap k a -> b #

foldl :: (b -> a -> b) -> b -> IntervalMap k a -> b #

foldl' :: (b -> a -> b) -> b -> IntervalMap k a -> b #

foldr1 :: (a -> a -> a) -> IntervalMap k a -> a #

foldl1 :: (a -> a -> a) -> IntervalMap k a -> a #

toList :: IntervalMap k a -> [a] #

null :: IntervalMap k a -> Bool #

length :: IntervalMap k a -> Int #

elem :: Eq a => a -> IntervalMap k a -> Bool #

maximum :: Ord a => IntervalMap k a -> a #

minimum :: Ord a => IntervalMap k a -> a #

sum :: Num a => IntervalMap k a -> a #

product :: Num a => IntervalMap k a -> a #

Ord k => Traversable (IntervalMap k) Source # 
Instance details

Defined in Data.IntervalMap.Base

Methods

traverse :: Applicative f => (a -> f b) -> IntervalMap k a -> f (IntervalMap k b) #

sequenceA :: Applicative f => IntervalMap k (f a) -> f (IntervalMap k a) #

mapM :: Monad m => (a -> m b) -> IntervalMap k a -> m (IntervalMap k b) #

sequence :: Monad m => IntervalMap k (m a) -> m (IntervalMap k a) #

Ord k => IsList (IntervalMap k a) Source # 
Instance details

Defined in Data.IntervalMap.Base

Associated Types

type Item (IntervalMap k a) #

Methods

fromList :: [Item (IntervalMap k a)] -> IntervalMap k a #

fromListN :: Int -> [Item (IntervalMap k a)] -> IntervalMap k a #

toList :: IntervalMap k a -> [Item (IntervalMap k a)] #

(Eq r, Eq a) => Eq (IntervalMap r a) Source # 
Instance details

Defined in Data.IntervalMap.Base

Methods

(==) :: IntervalMap r a -> IntervalMap r a -> Bool #

(/=) :: IntervalMap r a -> IntervalMap r a -> Bool #

(Data k, Data a, Ord k) => Data (IntervalMap k a) Source # 
Instance details

Defined in Data.IntervalMap.Base

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IntervalMap k a -> c (IntervalMap k a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IntervalMap k a) #

toConstr :: IntervalMap k a -> Constr #

dataTypeOf :: IntervalMap k a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IntervalMap k a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IntervalMap k a)) #

gmapT :: (forall b. Data b => b -> b) -> IntervalMap k a -> IntervalMap k a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IntervalMap k a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IntervalMap k a -> r #

gmapQ :: (forall d. Data d => d -> u) -> IntervalMap k a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IntervalMap k a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IntervalMap k a -> m (IntervalMap k a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IntervalMap k a -> m (IntervalMap k a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IntervalMap k a -> m (IntervalMap k a) #

(Ord k, Read k, Read a) => Read (IntervalMap k a) Source # 
Instance details

Defined in Data.IntervalMap.Base

(Ord k, Show k, Show a) => Show (IntervalMap k a) Source # 
Instance details

Defined in Data.IntervalMap.Base

Methods

showsPrec :: Int -> IntervalMap k a -> ShowS #

show :: IntervalMap k a -> String #

showList :: [IntervalMap k a] -> ShowS #

Ord k => Semigroup (IntervalMap k a) Source # 
Instance details

Defined in Data.IntervalMap.Base

Methods

(<>) :: IntervalMap k a -> IntervalMap k a -> IntervalMap k a #

sconcat :: NonEmpty (IntervalMap k a) -> IntervalMap k a #

stimes :: Integral b => b -> IntervalMap k a -> IntervalMap k a #

Ord k => Monoid (IntervalMap k a) Source # 
Instance details

Defined in Data.IntervalMap.Base

Methods

mempty :: IntervalMap k a #

mappend :: IntervalMap k a -> IntervalMap k a -> IntervalMap k a #

mconcat :: [IntervalMap k a] -> IntervalMap k a #

(NFData k, NFData a) => NFData (IntervalMap k a) Source # 
Instance details

Defined in Data.IntervalMap.Base

Methods

rnf :: IntervalMap k a -> () #

(Hashable k, Hashable a) => Hashable (IntervalMap k a) Source # 
Instance details

Defined in Data.IntervalMap.Base

Methods

hashWithSalt :: Int -> IntervalMap k a -> Int #

hash :: IntervalMap k a -> Int #

type Item (IntervalMap k a) Source # 
Instance details

Defined in Data.IntervalMap.Base

type Item (IntervalMap k a) = (Interval k, a)

Operators

(!) :: Ord k => IntervalMap k a -> k -> a infixl 9 Source #

Find the value at a key. Calls error when the element can not be found.

(\\) :: Ord k => IntervalMap k a -> IntervalMap k b -> IntervalMap k a infixl 9 Source #

Same as difference.

Query

null :: Ord k => IntervalMap k a -> Bool Source #

Is the map empty?

member :: Ord k => k -> IntervalMap k a -> Bool Source #

Is the key a member of the map? See also notMember.

notMember :: Ord k => k -> IntervalMap k a -> Bool Source #

Is the key not a member of the map? See also member.

lookup :: Ord k => k -> IntervalMap k a -> Maybe a Source #

Lookup the value at a key in the map.

The function will return the corresponding value as (Just value), or Nothing if the key isn't in the map.

findWithDefault :: Ord k => a -> k -> IntervalMap k a -> a Source #

The expression (findWithDefault def k map) returns the value at key k or returns default value def when the key is not in the map.

span :: Ord k => IntervalMap k a -> Interval k Source #

convex hull of key intervals.

Construction

whole :: Ord k => a -> IntervalMap k a Source #

The map that maps whole range of k to a.

empty :: Ord k => IntervalMap k a Source #

The empty map.

singleton :: Ord k => Interval k -> a -> IntervalMap k a Source #

A map with a single interval.

Insertion

insert :: Ord k => Interval k -> a -> IntervalMap k a -> IntervalMap k a Source #

insert a new key and value in the map. If the key is already present in the map, the associated value is replaced with the supplied value.

insertWith :: Ord k => (a -> a -> a) -> Interval k -> a -> IntervalMap k a -> IntervalMap k a Source #

Insert with a function, combining new value and old value. insertWith f key value mp will insert the pair (interval, value) into mp. If the interval overlaps with existing entries, the value for the entry is replace with (f new_value old_value).

Delete/Update

delete :: Ord k => Interval k -> IntervalMap k a -> IntervalMap k a Source #

Delete an interval and its value from the map. When the interval does not overlap with the map, the original map is returned.

adjust :: Ord k => (a -> a) -> Interval k -> IntervalMap k a -> IntervalMap k a Source #

Update a value at a specific interval with the result of the provided function. When the interval does not overlatp with the map, the original map is returned.

update :: Ord k => (a -> Maybe a) -> Interval k -> IntervalMap k a -> IntervalMap k a Source #

The expression (update f i map) updates the value x at i (if it is in the map). If (f x) is Nothing, the element is deleted. If it is (Just y), the key i is bound to the new value y.

alter :: Ord k => (Maybe a -> Maybe a) -> Interval k -> IntervalMap k a -> IntervalMap k a Source #

The expression (alter f i map) alters the value x at i, or absence thereof. alter can be used to insert, delete, or update a value in a IntervalMap.

Combine

union :: Ord k => IntervalMap k a -> IntervalMap k a -> IntervalMap k a Source #

The expression (union t1 t2) takes the left-biased union of t1 and t2. It prefers t1 when overlapping keys are encountered,

unionWith :: Ord k => (a -> a -> a) -> IntervalMap k a -> IntervalMap k a -> IntervalMap k a Source #

Union with a combining function.

unions :: Ord k => [IntervalMap k a] -> IntervalMap k a Source #

The union of a list of maps: (unions == foldl union empty).

unionsWith :: Ord k => (a -> a -> a) -> [IntervalMap k a] -> IntervalMap k a Source #

The union of a list of maps, with a combining operation: (unionsWith f == foldl (unionWith f) empty).

intersection :: Ord k => IntervalMap k a -> IntervalMap k a -> IntervalMap k a Source #

Intersection of two maps. Return data in the first map for the keys existing in both maps.

intersectionWith :: Ord k => (a -> b -> c) -> IntervalMap k a -> IntervalMap k b -> IntervalMap k c Source #

Intersection with a combining function.

difference :: Ord k => IntervalMap k a -> IntervalMap k b -> IntervalMap k a Source #

Return elements of the first map not existing in the second map.

Traversal

map :: (a -> b) -> IntervalMap k a -> IntervalMap k b Source #

Map a function over all values in the map.

mapKeysMonotonic :: forall k1 k2 a. (Ord k1, Ord k2) => (k1 -> k2) -> IntervalMap k1 a -> IntervalMap k2 a Source #

mapKeysMonotonic f s is the map obtained by applying f to each key of s. f must be strictly monotonic. That is, for any values x and y, if x < y then f x < f y.

Conversion

elems :: IntervalMap k a -> [a] Source #

Return all elements of the map in the ascending order of their keys.

keys :: IntervalMap k a -> [Interval k] Source #

Return all keys of the map in ascending order. Subject to list

assocs :: IntervalMap k a -> [(Interval k, a)] Source #

An alias for toAscList. Return all key/value pairs in the map in ascending key order.

keysSet :: Ord k => IntervalMap k a -> IntervalSet k Source #

The set of all keys of the map.

List

fromList :: Ord k => [(Interval k, a)] -> IntervalMap k a Source #

Build a map from a list of key/value pairs. If the list contains more than one value for the same key, the last value for the key is retained.

fromListWith :: Ord k => (a -> a -> a) -> [(Interval k, a)] -> IntervalMap k a Source #

Build a map from a list of key/value pairs with a combining function.

toList :: IntervalMap k a -> [(Interval k, a)] Source #

Convert the map to a list of key/value pairs.

Ordered List

toAscList :: IntervalMap k a -> [(Interval k, a)] Source #

Convert the map to a list of key/value pairs where the keys are in ascending order.

toDescList :: IntervalMap k a -> [(Interval k, a)] Source #

Convert the map to a list of key/value pairs where the keys are in descending order.

Filter

filter :: Ord k => (a -> Bool) -> IntervalMap k a -> IntervalMap k a Source #

Filter all values that satisfy some predicate.

split :: Ord k => Interval k -> IntervalMap k a -> (IntervalMap k a, IntervalMap k a, IntervalMap k a) Source #

The expression (split i map) is a triple (map1,map2,map3) where the keys in map1 are smaller than i, the keys in map2 are included in i, and the keys in map3 are larger than i.

Submap

isSubmapOf :: (Ord k, Eq a) => IntervalMap k a -> IntervalMap k a -> Bool Source #

This function is defined as (isSubmapOf = isSubmapOfBy (==)).

isSubmapOfBy :: Ord k => (a -> b -> Bool) -> IntervalMap k a -> IntervalMap k b -> Bool Source #

The expression (isSubmapOfBy f t1 t2) returns True if all keys in t1 are in tree t2, and when f returns True when applied to their respective values.

isProperSubmapOf :: (Ord k, Eq a) => IntervalMap k a -> IntervalMap k a -> Bool Source #

Is this a proper submap? (ie. a submap but not equal). Defined as (isProperSubmapOf = isProperSubmapOfBy (==)).

isProperSubmapOfBy :: Ord k => (a -> b -> Bool) -> IntervalMap k a -> IntervalMap k b -> Bool Source #

Is this a proper submap? (ie. a submap but not equal). The expression (isProperSubmapOfBy f m1 m2) returns True when m1 and m2 are not equal, all keys in m1 are in m2, and when f returns True when applied to their respective values.