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

IntervalAlgebra.IntervalUtilities

Description

 
Synopsis

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.

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

Returns the duration of each Interval in the Functor f.

>>> durations [intInt 1 10, intInt 2 12, intInt 5 6]
[9,10,1]

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]

gapsWithin Source #

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 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)]

nothingIf Source #

Arguments

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

e.g. any or all

-> (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 emptyIfAny and emptyIfNone for examples.

nothingIfNone Source #

Arguments

:: (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]

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

>>> nothingIfNone (starts (intInt 3 5)) [intInt 3 6, intInt 5 6]

nothingIfAny Source #

Arguments

:: (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

nothingIfAll Source #

Arguments

:: (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 as 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 as 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.