interval-algebra-2.2.0: An implementation of Allen's interval algebra for temporal logic
Copyright(c) NoviSci Inc 2020-2022
TargetRWE 2023
LicenseBSD3
Maintainerbsaul@novisci.com 2020-2022, bbrown@targetrwe.com 2023
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

IntervalAlgebra.IntervalUtilities

Description

 
Synopsis

Fold over sequential intervals

combineIntervals :: (SizedIv (Interval a), 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 = combineIntervals ivs
>>> xComb
[(0, 12),(13, 15)]
>>> :{
pretty $
  standardExampleDiagram
    (zip ivs ["x1", "x2", "x3", "x4"])
    [(xComb, "xComb")]
:}
----------      <- [x1]
  -----         <- [x2]
          --    <- [x3]
             -- <- [x4]
------------ -- <- [xComb]
===============

combineIntervalsFromSorted :: forall a i. (Ord a, Intervallic i, SizedIv (Interval a)) => [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.

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

rangeInterval :: (Foldable t, Ord a, SizedIv (Interval a)) => 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 :: Maybe (Interval Int))
Nothing
>>> rangeInterval (Just (bi 1 0))
Just (0, 1)

Combining intervals

(><) :: (Iv (Interval a), Ord (Moment (Interval a)), SizedIv (Interval a), Intervallic i) => i a -> i a -> Maybe (Interval a) Source #

If x is before y, then form a new Just Interval a from the interval in the "gap" between x and y from the end of x to the begin of y. Otherwise, Nothing.

(.+.) :: (Iv (Interval a), Ord (Moment (Interval a)), SizedIv (Interval a), Intervallic i) => i a -> i a -> Maybe (Interval a) Source #

Maybe form a new Interval a by the union of two Interval as that meets.

Functions for manipulating intervals

lookback Source #

Arguments

:: (Intervallic i, SizedIv (Interval a), Ord (Moment (Interval a))) 
=> Moment (Interval a)

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, SizedIv (Interval a), Ord (Moment (Interval a))) 
=> Moment (Interval a)

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

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

Returns a list of intervals consisting of the gaps between consecutive intervals in the input, after they have been sorted by interval ordering.

>>> 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
[(5, 8)]
>>> 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
[(5, 7),(10, 13)]
>>> :{
  pretty $
    standardExampleDiagram (zip ivs ["x1", "x2", "x3"]) [(gapIvs, "gapIvs")]
:}
 ----           <- [x1]
       ---      <- [x2]
             -- <- [x3]
     --   ---   <- [gapIvs]
===============

pairGaps :: (Intervallic i, SizedIv (Interval a), Ord a, Ord (Moment (Interval a))) => [i a] -> [Maybe (Moment (Interval a))] Source #

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

Misc utilities

relations :: (Intervallic i, Iv (Interval a)) => [i a] -> [IntervalRelation] Source #

Returns a list of the IntervalRelation between each consecutive pair of i a.

>>> relations [beginerval 1 0, beginerval 1 1]
[Meets]
>>> relations [beginerval 1 0, beginerval 1 1, beginerval 2 1]
[Meets,Starts]
>>> relations [beginerval 1 0]
[]

intersect :: (Intervallic i, SizedIv (Interval a), Ord a, Ord (Moment (Interval a))) => i a -> i a -> Maybe (Interval a) Source #

Forms Just a 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, SizedIv (Interval a), Ord a, Ord (Moment (Interval a))) => 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, SizedIv (Interval a)) => f (i a) -> f (Moment (Interval a)) 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]