Copyright | (c) NoviSci Inc 2020 |
---|---|
License | BSD3 |
Maintainer | bsaul@novisci.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- combineIntervals :: (IntervalCombinable a, Applicative f, Monoid (f (Interval a)), Foldable f) => f (Interval a) -> f (Interval a)
- combineIntervals' :: IntervalCombinable a => [Interval a] -> [Interval a]
- gaps :: (IntervalCombinable a, Applicative f, Monoid (f (Interval a)), Foldable f) => f (Interval a) -> f (Interval a)
- gaps' :: (IntervalCombinable a, Applicative f, Monoid (f (Interval a)), Foldable f) => f (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, Foldable f) => f (Interval a) -> [IntervalRelation a]
- relations' :: (IntervalAlgebraic a, Foldable f, Applicative m, Monoid (m (IntervalRelation a))) => f (Interval a) -> m (IntervalRelation a)
- gapsWithin :: (Applicative f, Foldable f, Monoid (f (Interval a)), IntervalSizeable a b, IntervalCombinable a, Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> Maybe (f (Interval a))
- nothingIf :: (Monoid (f (Interval a)), Filterable f, IntervalAlgebraic a) => ((Interval a -> Bool) -> f (Interval a) -> Bool) -> (Interval a -> Bool) -> f (Interval a) -> Maybe (f (Interval a))
- nothingIfNone :: (Monoid (f (Interval a)), Foldable f, Filterable f, IntervalAlgebraic a) => (Interval a -> Bool) -> f (Interval a) -> Maybe (f (Interval a))
- nothingIfAny :: (Monoid (f (Interval a)), Foldable f, Filterable f, IntervalAlgebraic a) => (Interval a -> Bool) -> f (Interval a) -> Maybe (f (Interval a))
- nothingIfAll :: (Monoid (f (Interval a)), Foldable f, Filterable f, IntervalAlgebraic a) => (Interval a -> Bool) -> f (Interval a) -> Maybe (f (Interval a))
- filterBefore :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a)
- filterMeets :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a)
- filterOverlaps :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a)
- filterFinishedBy :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a)
- filterContains :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a)
- filterStarts :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a)
- filterEquals :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a)
- filterStartedBy :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a)
- filterDuring :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a)
- filterFinishes :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a)
- filterOverlappedBy :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a)
- filterMetBy :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a)
- filterAfter :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a)
- filterDisjoint :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a)
- filterNotDisjoint :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a)
- filterWithin :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a)
Documentation
combineIntervals :: (IntervalCombinable a, Applicative f, Monoid (f (Interval a)), Foldable f) => f (Interval a) -> f (Interval a) Source #
Returns a container of intervals where any intervals that meet or share support
are combined into one interval. *To work properly, the input should
be sorted*. See combineIntervals'
for a version that works only on lists.
>>>
combineIntervals [intInt 0 10, intInt 2 7, intInt 10 12, intInt 13 15]
[(0, 12),(13, 15)]
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, Applicative f, Monoid (f (Interval a)), Foldable f) => f (Interval a) -> f (Interval a) Source #
Returns a (possibly empty) container of intervals consisting of the gaps
between intervals in the input. *To work properly, the input should be
sorted*. See gaps'
for a version that returns a list.
>>>
gaps [intInt 1 5, intInt 8 12, intInt 11 14]
[(5, 8)]
gaps' :: (IntervalCombinable a, Applicative f, Monoid (f (Interval a)), Foldable f) => f (Interval a) -> [Interval a] Source #
Returns a (possibly empty) list of intervals consisting of the gaps between
intervals in the input container. *To work properly, the input should be
sorted*. This version outputs a list. See gaps
for a version that lifts
the result to same input structure f
.
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, Foldable f) => f (Interval a) -> [IntervalRelation a] Source #
Returns a list of the IntervalRelation
between each consecutive pair
of intervals. This the specialized form of relations'
which can return
any Applicative
, Monoid
structure.
>>>
relations [intInt 0 1, intInt 1 2]
[Meets]
relations' :: (IntervalAlgebraic a, Foldable f, Applicative m, Monoid (m (IntervalRelation a))) => f (Interval a) -> m (IntervalRelation a) Source #
A generic form of relations
which can output any Applicative
and
Monoid
structure.
>>> (relations' [intInt 0 1, intInt 1 2]) :: [IntervalRelation Int]
[Meets]
:: (Applicative f, Foldable f, Monoid (f (Interval a)), IntervalSizeable a b, IntervalCombinable a, Filterable f, IntervalAlgebraic a) | |
=> Interval a | i |
-> f (Interval a) | x |
-> Maybe (f (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
, so that all the intervals are within
i
. If there are no gaps, then
Nothing
is returned.
>>>
gapsWithin (intInt 1 10) [intInt 0 5, intInt 7 9, intInt 12 15]
Just [(5, 7),(9, 10)]
:: (Monoid (f (Interval a)), Filterable f, IntervalAlgebraic a) | |
=> ((Interval a -> Bool) -> f (Interval a) -> Bool) | |
-> (Interval a -> Bool) | predicate to apply to each element of input list |
-> f (Interval a) | |
-> Maybe (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 nothingIfAny
and nothingIfNone
for examples.
:: (Monoid (f (Interval a)), Foldable f, Filterable f, IntervalAlgebraic a) | |
=> (Interval a -> Bool) | predicate to apply to each element of input list |
-> f (Interval a) | |
-> Maybe (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).
>>>
nothingIfNone (starts (intInt 3 5)) [intInt 3 4, intInt 5 6]
Nothing
In the following, (3, 5) starts
(3, 6), so the input is returned.
>>>
nothingIfNone (starts (intInt 3 5)) [intInt 3 6, intInt 5 6]
Just [(3, 6),(5, 6)]
:: (Monoid (f (Interval a)), Foldable f, Filterable f, IntervalAlgebraic a) | |
=> (Interval a -> Bool) | predicate to apply to each element of input list |
-> f (Interval a) | |
-> Maybe (f (Interval a)) |
Returns the empty monoid structure if *any* of the element of input satisfy the predicate condition
:: (Monoid (f (Interval a)), Foldable f, Filterable f, IntervalAlgebraic a) | |
=> (Interval a -> Bool) | predicate to apply to each element of input list |
-> f (Interval a) | |
-> Maybe (f (Interval a)) |
Returns the empty monoid structure if *all* of the element of input satisfy the predicate condition
Filtering functions
filterBefore :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a) Source #
Filter a Filterable
of Interval as to those before
the Interval a
in the first argument.
filterMeets :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a) Source #
Filter a Filterable
of Interval as to those that meets
the Interval a
in the first argument.
filterOverlaps :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a) Source #
Filter a Filterable
of Interval a
s to those that overlaps
the Interval a
in the first argument.
filterFinishedBy :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a) Source #
Filter a Filterable
of Interval as to those finishedBy
the Interval a
in the first argument.
filterContains :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a) Source #
Filter a Filterable
of Interval as to those that contains
the Interval a
in the first argument.
filterStarts :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a) Source #
Filter a Filterable
of Interval as to those starts
the Interval a
in the first argument.
filterEquals :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a) Source #
Filter a Filterable
of Interval as to those that equals
the Interval a
in the first argument.
filterStartedBy :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a) Source #
Filter a Filterable
of Interval as to those startedBy
the Interval a
in the first argument.
filterDuring :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a) Source #
Filter a Filterable
of Interval as to those during
the Interval a
in the first argument.
filterFinishes :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a) Source #
Filter a Filterable
of Interval as to those finishes
the Interval a
in the first argument.
filterOverlappedBy :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a) Source #
Filter a Filterable
of Interval a
s to those overlappedBy
the Interval a
in the first argument.
filterMetBy :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a) Source #
Filter a Filterable
of Interval as to those metBy
the Interval a
in the first argument.
filterAfter :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a) Source #
Filter a Filterable
of Interval as to those after
the Interval a
in the first argument.
filterDisjoint :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a) Source #
Filter a Filterable
of Interval as to those that are disjoint
from the Interval a
in the first argument.
filterNotDisjoint :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a) Source #
Filter a Filterable
of Interval as to those that are notDisjoint
from the Interval a
in the first argument.
filterWithin :: (Filterable f, IntervalAlgebraic a) => Interval a -> f (Interval a) -> f (Interval a) Source #
Filter a Filterable
of Interval as to those that are within
the Interval a
in the first argument.