interval-algebra-1.1.3: An implementation of Allen's interval algebra for temporal logic
Copyright(c) NoviSci Inc 2020
LicenseBSD3
Maintainerbsaul@novisci.com
Stabilityexperimental
Safe HaskellSafe
LanguageHaskell2010

IntervalAlgebra.IntervalUtilities

Description

In the examples below, iv is a synonym for beginerval used to save space.

Synopsis

Fold over sequential intervals

combineIntervals :: (Applicative f, Ord a, Intervallic i a, Monoid (f (Interval a)), Foldable f) => f (i 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 combineIntervalsL for a version that works only on lists.

>>> combineIntervals [iv 10 0, iv 5 2, iv 2 10, iv 2 13]
[(0, 12),(13, 15)]

combineIntervalsL :: Intervallic i a => [i 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*.

>>> combineIntervalsL [iv 10 0, iv 5 2, iv 2 10, iv 2 13]
[(0, 12),(13, 15)]

gaps :: (IntervalCombinable i a, Traversable f, Monoid (f (Maybe (Interval a))), Applicative f) => f (i a) -> Maybe (f (Interval a)) Source #

Returns a Maybe container of intervals consisting of the gaps between intervals in the input. *To work properly, the input should be sorted*. See gapsL for a version that always returns a list.

>>> gaps [iv 4 1, iv 4 8, iv 3 11]

gapsL :: (IntervalCombinable i a, Applicative f, Monoid (f (Maybe (Interval a))), Traversable f) => f (i 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.

gapsWithin Source #

Arguments

:: (Applicative f, Witherable f, Monoid (f (Interval a)), Monoid (f (Maybe (Interval a))), IntervalSizeable a b, Intervallic i0 a, IntervalCombinable i1 a) 
=> i0 a

i

-> f (i1 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 clipped to i, so that all the intervals are within i. If all of the input intervals are disjoint from the focal interval or if the input is empty, then Nothing is returned. When there are no gaps among the concurring intervals, then `Just mempty` (e.g. `Just []`) is returned.

>>> gapsWithin (iv 9 1) [iv 5 0, iv 2 7, iv 3 12]
Just [(5, 7),(9, 10)]

Operations on Meeting sequences of paired intervals

foldMeetingSafe Source #

Arguments

:: (Eq b, Ord a, Show a) 
=> [PairedInterval b a]

Be sure this only contains intervals that sequentially meets.

-> [PairedInterval b a] 

Folds over a list of Paired Intervals and in the case that the getPairData is equal between two sequential meeting intervals, these two intervals are combined into one. This function is "safe" in the sense that if the input is invalid and contains any sequential pairs of intervals with an IntervalRelation, other than Meets, then the function returns an empty list.

formMeetingSequence :: (Eq b, Show a, Monoid b, IntervalSizeable a c) => [PairedInterval b a] -> [PairedInterval b a] Source #

Convert an ordered sequence of PairedInterval b a. that may have any interval relation (before, starts, etc) into a sequence of sequentially meeting PairedInterval b a. That is, a sequence where one the end of one interval meets the beginning of the subsequent event. The getPairData of the input PairedIntervals are combined using the Monoid <> function, hence the pair data must be a Monoid instance.

Withering functions

Clear containers based on predicate

nothingIf Source #

Arguments

:: (Monoid (f (i a)), Filterable f) 
=> ((i a -> Bool) -> f (i a) -> Bool)

e.g. any or all

-> (i a -> Bool)

predicate to apply to each element of input list

-> f (i a) 
-> Maybe (f (i 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.

nothingIfNone Source #

Arguments

:: (Monoid (f (i a)), Foldable f, Filterable f) 
=> (i a -> Bool)

predicate to apply to each element of input list

-> f (i a) 
-> Maybe (f (i a)) 

Returns the Nothing if *none* of the element of input satisfy the predicate condition.

For example, the following returns Nothing because none of the intervals in the input list starts (3, 5).

>>> nothingIfNone (starts (iv 2 3)) [iv 1 3, iv 1 5]
Nothing

In the following, (3, 5) starts (3, 6), so Just the input is returned.

>>> nothingIfNone (starts (iv 2 3)) [iv 3 3, iv 1 5]
Just [(3, 6),(5, 6)]

nothingIfAny Source #

Arguments

:: (Monoid (f (i a)), Foldable f, Filterable f) 
=> (i a -> Bool)

predicate to apply to each element of input list

-> f (i a) 
-> Maybe (f (i a)) 

Returns Nothing if *any* of the element of input satisfy the predicate condition.

>>> nothingIfAny (starts (iv 2 3)) [iv 3 3, iv 1 5]
Just [(3, 6),(5, 6)]
>>> nothingIfAny (starts (iv 2 3)) [iv 3 3, iv 1 5]
Nothing

nothingIfAll Source #

Arguments

:: (Monoid (f (i a)), Foldable f, Filterable f) 
=> (i a -> Bool)

predicate to apply to each element of input list

-> f (i a) 
-> Maybe (f (i a)) 

Returns Nothing if *all* of the element of input satisfy the predicate condition. >>> nothingIfAll (starts (iv 2 3)) [iv 3 3, iv 4 3] Nothing

Filter containers based on predicate

filterBefore :: (Filterable f, Intervallic i0 a, Intervallic i1 a) => i0 a -> f (i1 a) -> f (i1 a) Source #

Filter Filterable containers of one Intervallic type based by comparing to a (potentially different) Intervallic type using the corresponding interval predicate function.

filterMeets :: (Filterable f, Intervallic i0 a, Intervallic i1 a) => i0 a -> f (i1 a) -> f (i1 a) Source #

Filter Filterable containers of one Intervallic type based by comparing to a (potentially different) Intervallic type using the corresponding interval predicate function.

filterOverlaps :: (Filterable f, Intervallic i0 a, Intervallic i1 a) => i0 a -> f (i1 a) -> f (i1 a) Source #

Filter Filterable containers of one Intervallic type based by comparing to a (potentially different) Intervallic type using the corresponding interval predicate function.

filterFinishedBy :: (Filterable f, Intervallic i0 a, Intervallic i1 a) => i0 a -> f (i1 a) -> f (i1 a) Source #

Filter Filterable containers of one Intervallic type based by comparing to a (potentially different) Intervallic type using the corresponding interval predicate function.

filterContains :: (Filterable f, Intervallic i0 a, Intervallic i1 a) => i0 a -> f (i1 a) -> f (i1 a) Source #

Filter Filterable containers of one Intervallic type based by comparing to a (potentially different) Intervallic type using the corresponding interval predicate function.

filterStarts :: (Filterable f, Intervallic i0 a, Intervallic i1 a) => i0 a -> f (i1 a) -> f (i1 a) Source #

Filter Filterable containers of one Intervallic type based by comparing to a (potentially different) Intervallic type using the corresponding interval predicate function.

filterEquals :: (Filterable f, Intervallic i0 a, Intervallic i1 a) => i0 a -> f (i1 a) -> f (i1 a) Source #

Filter Filterable containers of one Intervallic type based by comparing to a (potentially different) Intervallic type using the corresponding interval predicate function.

filterStartedBy :: (Filterable f, Intervallic i0 a, Intervallic i1 a) => i0 a -> f (i1 a) -> f (i1 a) Source #

Filter Filterable containers of one Intervallic type based by comparing to a (potentially different) Intervallic type using the corresponding interval predicate function.

filterDuring :: (Filterable f, Intervallic i0 a, Intervallic i1 a) => i0 a -> f (i1 a) -> f (i1 a) Source #

Filter Filterable containers of one Intervallic type based by comparing to a (potentially different) Intervallic type using the corresponding interval predicate function.

filterFinishes :: (Filterable f, Intervallic i0 a, Intervallic i1 a) => i0 a -> f (i1 a) -> f (i1 a) Source #

Filter Filterable containers of one Intervallic type based by comparing to a (potentially different) Intervallic type using the corresponding interval predicate function.

filterOverlappedBy :: (Filterable f, Intervallic i0 a, Intervallic i1 a) => i0 a -> f (i1 a) -> f (i1 a) Source #

Filter Filterable containers of one Intervallic type based by comparing to a (potentially different) Intervallic type using the corresponding interval predicate function.

filterMetBy :: (Filterable f, Intervallic i0 a, Intervallic i1 a) => i0 a -> f (i1 a) -> f (i1 a) Source #

Filter Filterable containers of one Intervallic type based by comparing to a (potentially different) Intervallic type using the corresponding interval predicate function.

filterAfter :: (Filterable f, Intervallic i0 a, Intervallic i1 a) => i0 a -> f (i1 a) -> f (i1 a) Source #

Filter Filterable containers of one Intervallic type based by comparing to a (potentially different) Intervallic type using the corresponding interval predicate function.

filterDisjoint :: (Filterable f, Intervallic i0 a, Intervallic i1 a) => i0 a -> f (i1 a) -> f (i1 a) Source #

Filter Filterable containers of one Intervallic type based by comparing to a (potentially different) Intervallic type using the corresponding interval predicate function.

filterNotDisjoint :: (Filterable f, Intervallic i0 a, Intervallic i1 a) => i0 a -> f (i1 a) -> f (i1 a) Source #

Filter Filterable containers of one Intervallic type based by comparing to a (potentially different) Intervallic type using the corresponding interval predicate function.

filterConcur :: (Filterable f, Intervallic i0 a, Intervallic i1 a) => i0 a -> f (i1 a) -> f (i1 a) Source #

Filter Filterable containers of one Intervallic type based by comparing to a (potentially different) Intervallic type using the corresponding interval predicate function.

filterWithin :: (Filterable f, Intervallic i0 a, Intervallic i1 a) => i0 a -> f (i1 a) -> f (i1 a) Source #

Filter Filterable containers of one Intervallic type based by comparing to a (potentially different) Intervallic type using the corresponding interval predicate function.

filterEnclose :: (Filterable f, Intervallic i0 a, Intervallic i1 a) => i0 a -> f (i1 a) -> f (i1 a) Source #

Filter Filterable containers of one Intervallic type based by comparing to a (potentially different) Intervallic type using the corresponding interval predicate function.

filterEnclosedBy :: (Filterable f, Intervallic i0 a, Intervallic i1 a) => i0 a -> f (i1 a) -> f (i1 a) Source #

Filter Filterable containers of one Intervallic type based by comparing to a (potentially different) Intervallic type using the corresponding interval predicate function.

Misc utilities

relations :: (Foldable f, Applicative m, Intervallic i a, Monoid (m IntervalRelation)) => f (i a) -> m IntervalRelation Source #

A generic form of relations which can output any Applicative and Monoid structure. >>> (relations [iv 1 0, iv 1 1]) :: [IntervalRelation (Interval Int)] [Meets]

relationsL :: (Foldable f, Intervallic i a) => f (i a) -> [IntervalRelation] Source #

Returns a list of the IntervalRelation between each consecutive pair of intervals. This is just a specialized relations which returns a list.

>>> relationsL [iv 1 0, iv 1 1]
[Meets]

intersect :: (Intervallic i a, IntervalSizeable a b) => i a -> i a -> Maybe (Interval a) Source #

Forms a Just new interval from the intersection of two intervals, provided the intervals are not disjoint.

>>> intersect (iv 5 0) (iv 2 3)
Just (3, 5)

clip :: (Intervallic i0 a, Intervallic i1 a, IntervalSizeable a b) => i0 a -> i1 a -> Maybe (Interval a) Source #

In the case that x y are not disjoint, clips y to the extent of x.

>>> clip (iv 5 0) (iv 3 3)
Just (3, 5)
>>> clip (iv 3 0) (iv 2 4)
Nothing

durations :: (Functor f, Intervallic i a, IntervalSizeable a b) => f (i a) -> f b Source #

Returns the duration of each 'Intervallic i a' in the Functor f.

>>> durations [iv 9 1, iv 10 2, iv 1 5]
[9,10,1]