Copyright | (c) NoviSci Inc 2020 |
---|---|
License | BSD3 |
Maintainer | bsaul@novisci.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- combineIntervals :: IntervalCombinable a => [Interval a] -> [Interval a]
- gaps :: IntervalCombinable a => [Interval a] -> [Interval a]
- durations :: (Functor f, IntervalSizeable a b) => f (Interval a) -> f b
- clip :: (IntervalAlgebraic a, IntervalSizeable a b) => Interval a -> Interval a -> Maybe (Interval a)
- relations :: IntervalAlgebraic a => [Interval a] -> [IntervalRelation a]
- gapsWithin :: (IntervalSizeable a b, IntervalCombinable a, IntervalFilterable [] a) => Interval a -> [Interval a] -> [Interval a]
- emptyIf :: (Monoid (f (Interval a)), Foldable f, IntervalFilterable f a) => ((Interval a -> Bool) -> f (Interval a) -> Bool) -> (Interval a -> Bool) -> f (Interval a) -> f (Interval a)
- emptyIfNone :: (Monoid (f (Interval a)), Foldable f, IntervalFilterable f a) => (Interval a -> Bool) -> f (Interval a) -> f (Interval a)
- emptyIfAny :: (Monoid (f (Interval a)), Foldable f, IntervalFilterable f a) => (Interval a -> Bool) -> f (Interval a) -> f (Interval a)
- emptyIfAll :: (Monoid (f (Interval a)), Foldable f, IntervalFilterable f a) => (Interval a -> Bool) -> f (Interval a) -> f (Interval a)
Documentation
combineIntervals :: IntervalCombinable a => [Interval a] -> [Interval a] Source #
Returns a list of intervals where any intervals that meet or share support are combined into one interval. *To work properly, the input list should be sorted*.
>>>
combineIntervals [intInt 0 10, intInt 2 7, intInt 10 12, intInt 13 15]
[(0, 12),(13, 15)]
gaps :: IntervalCombinable a => [Interval a] -> [Interval a] Source #
Returns a (possibly empty) list of intervals consisting of the gaps between intervals in the input list. *To work properly, the input list should be sorted*.
clip :: (IntervalAlgebraic a, IntervalSizeable a b) => Interval a -> Interval a -> Maybe (Interval a) Source #
In the case that x y are not disjoint, clips y to the extent of x.
>>>
clip (intInt 0 5) (intInt 3 6)
Just (3, 5)
>>>
clip (intInt 0 3) (intInt 4 6)
Nothing
relations :: IntervalAlgebraic a => [Interval a] -> [IntervalRelation a] Source #
Finds the IntervalRelation
between each consecutive pair of intervals.
>>>
relations [intInt 0 1, intInt 1 2]
[Meets]
:: (IntervalSizeable a b, IntervalCombinable a, IntervalFilterable [] a) | |
=> Interval a | i |
-> [Interval a] | x |
-> [Interval a] |
Applies gaps
to all the non-disjoint intervals in x
that are *not* disjoint
from i
. Intervals that overlaps
or are overlappedBy
i
are clip
ped to i
.
>>>
gapsWithin (intInt 1 10) [intInt 0 5, intInt 7 9, intInt 12 15]
[(5, 7),(9, 10)]
:: (Monoid (f (Interval a)), Foldable f, IntervalFilterable f a) | |
=> ((Interval a -> Bool) -> f (Interval a) -> Bool) | |
-> (Interval a -> Bool) | predicate to apply to each element of input list |
-> f (Interval a) | |
-> f (Interval a) |
Given a predicate combinator, a predicate, and list of intervals, returns
the input unchanged if the predicate combinator is True
. Otherwise, returns
an empty list. See emptyIfAny
and emptyIfNone
for examples.
:: (Monoid (f (Interval a)), Foldable f, IntervalFilterable f a) | |
=> (Interval a -> Bool) | predicate to apply to each element of input list |
-> f (Interval a) | |
-> f (Interval a) |
Returns the empty monoid structure if *none* of the element of input satisfy the predicate condition.
For example, the following returns the empty list because none of the intervals
in the input list starts
(3, 5).
>>>
emptyIfNone (starts (intInt 3 5)) [intInt 3 4, intInt 5 6]
[]
In the following, (3, 5) starts
(3, 6), so the input is returned.
>>>
emptyIfNone (starts (intInt 3 5)) [intInt 3 6, intInt 5 6]
[(3, 6),(5, 6)]