trifecta-1.5: A modern parser combinator library with convenient diagnostics

Portabilitynon-portable (MPTCs, type families, functional dependencies)
Stabilityexperimental
Maintainerekmett@gmail.com
Safe HaskellNone

Text.Trifecta.Util.IntervalMap

Contents

Description

Interval maps implemented using the FingerTree type, following section 4.8 of

An amortized running time is given for each operation, with n referring to the size of the priority queue. These bounds hold even in a persistent (shared) setting.

Note: Many of these operations have the same names as similar operations on lists in the Prelude. The ambiguity may be resolved using either qualification or the hiding clause.

Unlike Data.IntervalMap.FingerTree, this version sorts things so that the largest interval from a given point comes first. This way if you have nested intervals, you get the outermost interval before the contained intervals.

Synopsis

Intervals

data Interval v Source

A closed interval. The lower bound should be less than or equal to the higher bound.

Constructors

Interval 

Fields

low :: v
 
high :: v
 

Interval maps

newtype IntervalMap v a Source

Map of closed intervals, possibly with duplicates. The Foldable and Traversable instances process the intervals in lexicographical order.

Constructors

IntervalMap 

Fields

runIntervalMap :: FingerTree (IntInterval v) (Node v a)
 

Instances

Functor (IntervalMap v) 
Foldable (IntervalMap v) 
Traversable (IntervalMap v) 
FunctorWithIndex (Interval v) (IntervalMap v) 
FoldableWithIndex (Interval v) (IntervalMap v) 
TraversableWithIndex (Interval v) (IntervalMap v) 
Ord v => Measured (IntInterval v) (IntervalMap v a) 
Ord v => Monoid (IntervalMap v a) 
Ord v => HasUnion (IntervalMap v a)

O(m log (n/m)). Merge two interval maps. The map may contain duplicate intervals; entries with equal intervals are kept in the original order.

Ord v => HasUnion0 (IntervalMap v a) 

singleton :: Ord v => Interval v -> a -> IntervalMap v aSource

O(1). Interval map with a single entry.

insert :: Ord v => v -> v -> a -> IntervalMap v a -> IntervalMap v aSource

O(log n). Insert an interval into a map. The map may contain duplicate intervals; the new entry will be inserted before any existing entries for the same interval.

Searching

search :: Ord v => v -> IntervalMap v a -> [(Interval v, a)]Source

O(k log (n/k)). All intervals that contain the given point, in lexicographical order.

intersections :: Ord v => v -> v -> IntervalMap v a -> [(Interval v, a)]Source

O(k log (n/k)). All intervals that intersect with the given interval, in lexicographical order.

dominators :: Ord v => v -> v -> IntervalMap v a -> [(Interval v, a)]Source

O(k log (n/k)). All intervals that contain the given interval, in lexicographical order.

Prepending an offset onto every interval in the map

offset :: (Ord v, Monoid v) => v -> IntervalMap v a -> IntervalMap v aSource

O(n). Add a delta to each interval in the map

The result monoid

data IntInterval v Source

Constructors

NoInterval 
IntInterval (Interval v) v 

Instances

fromList :: Ord v => [(v, v, a)] -> IntervalMap v aSource