interval-algebra-2.1.2: 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

 
Synopsis

Fold over sequential intervals

combineIntervals :: (Applicative f, Ord a, Intervallic i, 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. This functions sorts the input intervals first. See combineIntervalsL for a version that works only on lists. If you know the input intervals are sorted, use combineIntervalsFromSorted instead.

>>> x1 = bi 10 0
>>> x2 = bi 5 2
>>> x3 = bi 2 10
>>> x4 = bi 2 13
>>> ivs = [x1, x2, x3, x4]
>>> ivs
[(0, 10),(2, 7),(10, 12),(13, 15)]
>>> xComb = combineIntervals ivs
>>> xComb
[(0, 12),(13, 15)]
>>> :{
pretty $
  standardExampleDiagram
    (zip ivs ["x1", "x2", "x3", "x4"])
    [(xComb, "xComb")]
:}
----------      <- [x1]
  -----         <- [x2]
          --    <- [x3]
             -- <- [x4]
------------ -- <- [xComb]
===============

combineIntervalsL :: (Intervallic i, Ord a) => [i a] -> [Interval a] Source #

Returns a list of intervals where any intervals that meet or share support are combined into one interval. This function sorts the input. If you know the input intervals are sorted, use combineIntervalsLFromSorted.

>>> x1 = bi 10 0
>>> x2 = bi 5 2
>>> x3 = bi 2 10
>>> x4 = bi 2 13
>>> ivs = [x1, x2, x3, x4]
>>> ivs
[(0, 10),(2, 7),(10, 12),(13, 15)]
>>> xComb = combineIntervalsL ivs
>>> xComb
[(0, 12),(13, 15)]
>>> :{
pretty $
  standardExampleDiagram
    (zip ivs ["x1", "x2", "x3", "x4"])
    [(xComb, "xComb")]
:}
----------      <- [x1]
  -----         <- [x2]
          --    <- [x3]
             -- <- [x4]
------------ -- <- [xComb]
===============

combineIntervalsFromSorted :: (Applicative f, Ord a, Intervallic i, 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. The condition is applied cumulatively, from left to right, so to work properly, the input list should be sorted in increasing order. See combineIntervalsLFromSorted for a version that works only on lists.

>>> combineIntervalsFromSorted [bi 10 0, bi 5 2, bi 2 10, bi 2 13]
[(0, 12),(13, 15)]

combineIntervalsFromSortedL :: forall a i. (Ord a, Intervallic i) => [i a] -> [Interval a] Source #

Returns a list of intervals where any intervals that meet or share support are combined into one interval. The operation is applied cumulatively, from left to right, so to work properly, the input list should be sorted in increasing order.

>>> combineIntervalsFromSortedL [bi 10 0, bi 5 2, bi 2 10, bi 2 13]
[(0, 12),(13, 15)]
>>> combineIntervalsFromSortedL [bi 10 0, bi 5 2, bi 0 8]
[(0, 10)]

rangeInterval :: (Ord a, Foldable t) => t (Interval a) -> Maybe (Interval a) Source #

Maybe form an Interval a from Control.Foldl t => t (Interval a) spanning the range of all intervals in the list, i.e. whose begin is the minimum of begin across intervals in the list and whose end is the maximum of end.

>>> rangeInterval ([] :: [Interval Int])
Nothing
>>> x1 = bi 2 2
>>> x2 = bi 3 6
>>> x3 = bi 4 7
>>> ivs = [x1, x2, x3] :: [Interval Int]
>>> ivs
[(2, 4),(6, 9),(7, 11)]
>>> spanIv = rangeInterval ivs
>>> spanIv
Just (2, 11)
>>> :{
case spanIv of
  Nothing -> pretty ""
  (Just x) -> pretty $ standardExampleDiagram
    (zip (ivs ++ [x]) ["x1", "x2", "x3", "spanIv"])
    []
:}
  --        <- [x1]
      ---   <- [x2]
       ---- <- [x3]
  --------- <- [spanIv]
===========
>>> rangeInterval Nothing
Nothing
>>> rangeInterval (Just (bi 1 0))
Just (0, 1)

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.

>>> x1 = bi 4 1
>>> x2 = bi 4 8
>>> x3 = bi 3 11
>>> ivs = [x1, x2, x3]
>>> ivs
[(1, 5),(8, 12),(11, 14)]
>>> gaps ivs
Nothing
>>> pretty $ standardExampleDiagram (zip ivs ["x1", "x2", "x3"]) []
 ----          <- [x1]
        ----   <- [x2]
           --- <- [x3]
==============
>>> x1 = bi 4 1
>>> x2 = bi 3 7
>>> x3 = bi 2 13
>>> ivs = [x1, x2, x3]
>>> ivs
[(1, 5),(7, 10),(13, 15)]
>>> gapIvs = gaps ivs
>>> gapIvs
Just [(5, 7),(10, 13)]
>>> :{
case gapIvs of
  Nothing -> pretty ""
  (Just x) -> pretty $
    standardExampleDiagram (zip ivs ["x1", "x2", "x3"]) [(x, "gapIvs")]
:}
 ----           <- [x1]
       ---      <- [x2]
             -- <- [x3]
     --   ---   <- [gapIvs]
===============

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.

>>> x1 = bi 4 1
>>> x2 = bi 4 8
>>> x3 = bi 3 11
>>> ivs = [x1, x2, x3]
>>> ivs
[(1, 5),(8, 12),(11, 14)]
>>> gapIvs = gapsL ivs
>>> gapIvs
[]
>>> :{
pretty $ standardExampleDiagram (zip ivs ["x1", "x2", "x3"]) []
:}
 ----          <- [x1]
        ----   <- [x2]
           --- <- [x3]
==============
>>> x1 = bi 4 1
>>> x2 = bi 3 7
>>> x3 = bi 2 13
>>> ivs = [x1, x2, x3]
>>> ivs
[(1, 5),(7, 10),(13, 15)]
>>> gapIvs = gapsL ivs
>>> gapIvs
[(5, 7),(10, 13)]
>>> :{
pretty $
  standardExampleDiagram (zip ivs ["x1", "x2", "x3"]) [(gapIvs, "gapIvs")]
:}
 ----           <- [x1]
       ---      <- [x2]
             -- <- [x3]
     --   ---   <- [gapIvs]
===============

gapsWithin Source #

Arguments

:: (Applicative f, Witherable f, Monoid (f (Interval a)), Monoid (f (Maybe (Interval a))), IntervalSizeable a b, Intervallic i0, 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 (bi 9 1) [bi 5 0, bi 2 7, bi 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 (bi 2 3)) [bi 1 3, bi 1 5]
Nothing

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

>>> nothingIfNone (starts (bi 2 3)) [bi 3 3, bi 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 (startedBy (bi 2 3)) [bi 3 3, bi 1 5]
Just [(3, 6),(5, 6)]
>>> nothingIfAny (starts (bi 2 3)) [bi 3 3, bi 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 (bi 2 3)) [bi 3 3, bi 4 3]
Nothing

Filter containers based on predicate

filterBefore :: (Filterable f, Ord a, Intervallic i0, Intervallic i1) => 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, Ord a, Intervallic i0, Intervallic i1) => 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, Ord a, Intervallic i0, Intervallic i1) => 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, Ord a, Intervallic i0, Intervallic i1) => 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, Ord a, Intervallic i0, Intervallic i1) => 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, Ord a, Intervallic i0, Intervallic i1) => 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, Ord a, Intervallic i0, Intervallic i1) => 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, Ord a, Intervallic i0, Intervallic i1) => 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, Ord a, Intervallic i0, Intervallic i1) => 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, Ord a, Intervallic i0, Intervallic i1) => 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, Ord a, Intervallic i0, Intervallic i1) => 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, Ord a, Intervallic i0, Intervallic i1) => 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, Ord a, Intervallic i0, Intervallic i1) => 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, Ord a, Intervallic i0, Intervallic i1) => 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, Ord a, Intervallic i0, Intervallic i1) => 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, Ord a, Intervallic i0, Intervallic i1) => 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, Ord a, Intervallic i0, Intervallic i1) => 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.

filterEncloses :: (Filterable f, Ord a, Intervallic i0, Intervallic i1) => 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, Ord a, Intervallic i0, Intervallic i1) => 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.

Functions for manipulating intervals

lookback Source #

Arguments

:: (Intervallic i, IntervalSizeable a b) 
=> b

lookback duration

-> i a 
-> Interval a 

Creates a new Interval of a provided lookback duration ending at the begin of the input interval.

>>> lookback 4 (beginerval 10 (1 :: Int))
(-3, 1)

lookahead Source #

Arguments

:: (Intervallic i, IntervalSizeable a b) 
=> b

lookahead duration

-> i a 
-> Interval a 

Creates a new Interval of a provided lookahead duration beginning at the end of the input interval.

>>> lookahead 4 (beginerval 1 (1 :: Int))
(2, 6)

Gaps

makeGapsWithinPredicate :: (Monoid (t (Interval a)), Monoid (t (Maybe (Interval a))), Applicative t, Witherable t, IntervalSizeable a b, Intervallic i0, IntervalCombinable i1 a) => ((b -> Bool) -> t b -> Bool) -> (b -> b -> Bool) -> b -> i0 a -> t (i1 a) -> Bool Source #

Create a predicate function that checks whether within a provided spanning interval, are there (e.g. any, all) gaps of (e.g. <=,=, >) a specified duration among the input intervals?

pairGaps :: (Intervallic i, IntervalSizeable a b, IntervalCombinable i a) => [i a] -> [Maybe b] Source #

Gets the durations of gaps (via 'IntervalAlgebra.(><)') between all pairs of the input.

anyGapsWithinAtLeastDuration Source #

Arguments

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

duration of gap

-> i0 a

within this interval

-> t (i1 a) 
-> Bool 

Within a provided spanning interval, are there any gaps of at least the specified duration among the input intervals?

allGapsWithinLessThanDuration Source #

Arguments

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

duration of gap

-> i0 a

within this interval

-> t (i1 a) 
-> Bool 

Within a provided spanning interval, are all gaps less than the specified duration among the input intervals?

>>> allGapsWithinLessThanDuration 30 (beginerval 100 (0::Int)) [beginerval 5 (-1), beginerval 99 10]
True

Misc utilities

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

A generic form of relations which can output any Applicative and Monoid structure.

>>> (relations [bi 1 0,bi 1 1]) :: [IntervalRelation]
[Meets]

relationsL :: (Foldable f, Ord a, Intervallic i) => 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 [bi 1 0, bi 1 1]
[Meets]

intersect :: (Intervallic i, 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 (bi 5 0) (bi 2 3)
Just (3, 5)

clip :: (Intervallic i0, Intervallic i1, 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 (bi 5 0) ((bi 3 3) :: Interval Int)
Just (3, 5)
>>> clip (bi 3 0) ((bi 2 4) :: Interval Int)
Nothing

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

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

>>> durations [bi 9 1, bi 10 2, bi 1 5 :: Interval Int]
[9,10,1]