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
Safe HaskellSafe-Inferred
LanguageHaskell2010

IntervalAlgebra.Core

Description

The IntervalAlgebra module provides data types and related classes for the interval-based temporal logic described in Allen (1983) and axiomatized in Allen and Hayes (1987). A good primer on Allen's algebra can be found here.

Design

The module provides an Interval type wrapping a canonical interval to be used with the relation algebra defined in the papers cited above. Interval a wraps (a, a), giving the interval's begin and end points.

However, the module provides typeclasses to generalize an Interval and the interval algebra for temporal logic, such that it could be used in settings where there is no need for continguity between the begin and end points, or where the "intervals" are qualitative and do not have a begin or end. See Iv for an example.

Synopsis

Canonical intervals

data Interval a Source #

An Interval a is a pair \( (x, y) \text{ such that } x < y\). To create intervals use the parseInterval, beginerval, or enderval functions.

Instances

Instances details
Intervallic Interval Source # 
Instance details

Defined in IntervalAlgebra.Core

Eq a => Eq (Interval a) Source # 
Instance details

Defined in IntervalAlgebra.Core

Methods

(==) :: Interval a -> Interval a -> Bool #

(/=) :: Interval a -> Interval a -> Bool #

Ord a => Ord (Interval a) Source #

Imposes a total ordering on Interval a based on first ordering the begins then the ends.

Instance details

Defined in IntervalAlgebra.Core

Methods

compare :: Interval a -> Interval a -> Ordering #

(<) :: Interval a -> Interval a -> Bool #

(<=) :: Interval a -> Interval a -> Bool #

(>) :: Interval a -> Interval a -> Bool #

(>=) :: Interval a -> Interval a -> Bool #

max :: Interval a -> Interval a -> Interval a #

min :: Interval a -> Interval a -> Interval a #

(Show a, Ord a) => Show (Interval a) Source # 
Instance details

Defined in IntervalAlgebra.Core

Methods

showsPrec :: Int -> Interval a -> ShowS #

show :: Interval a -> String #

showList :: [Interval a] -> ShowS #

Generic (Interval a) Source # 
Instance details

Defined in IntervalAlgebra.Core

Associated Types

type Rep (Interval a) :: Type -> Type #

Methods

from :: Interval a -> Rep (Interval a) x #

to :: Rep (Interval a) x -> Interval a #

Arbitrary (Interval Double) Source # 
Instance details

Defined in IntervalAlgebra.Arbitrary

Arbitrary (Interval Int) Source # 
Instance details

Defined in IntervalAlgebra.Arbitrary

Arbitrary (Interval Integer) Source # 
Instance details

Defined in IntervalAlgebra.Arbitrary

Arbitrary (Interval UTCTime) Source # 
Instance details

Defined in IntervalAlgebra.Arbitrary

Arbitrary (Interval Day) Source # 
Instance details

Defined in IntervalAlgebra.Arbitrary

Binary a => Binary (Interval a) Source # 
Instance details

Defined in IntervalAlgebra.Core

Methods

put :: Interval a -> Put #

get :: Get (Interval a) #

putList :: [Interval a] -> Put #

NFData a => NFData (Interval a) Source # 
Instance details

Defined in IntervalAlgebra.Core

Methods

rnf :: Interval a -> () #

SizedIv (Interval Double) Source # 
Instance details

Defined in IntervalAlgebra.Core

Associated Types

type Moment (Interval Double) Source #

SizedIv (Interval Int) Source # 
Instance details

Defined in IntervalAlgebra.Core

Associated Types

type Moment (Interval Int) Source #

SizedIv (Interval Integer) Source # 
Instance details

Defined in IntervalAlgebra.Core

Associated Types

type Moment (Interval Integer) Source #

SizedIv (Interval UTCTime) Source #

Note this instance changes the moment to 1 Pico second, not 1 second as would be the case if the default were used.

Instance details

Defined in IntervalAlgebra.Core

Associated Types

type Moment (Interval UTCTime) Source #

SizedIv (Interval Day) Source # 
Instance details

Defined in IntervalAlgebra.Core

Associated Types

type Moment (Interval Day) Source #

PointedIv (Interval a) Source # 
Instance details

Defined in IntervalAlgebra.Core

Associated Types

type Point (Interval a) Source #

Ord a => Iv (Interval a) Source #

Implements the interval algebra for intervals represented as left and right endpoints, with points in a totally ordered set, as prescribed in Allen 1983.

Instance details

Defined in IntervalAlgebra.Core

type Rep (Interval a) Source # 
Instance details

Defined in IntervalAlgebra.Core

type Rep (Interval a) = D1 ('MetaData "Interval" "IntervalAlgebra.Core" "interval-algebra-2.2.0-inplace" 'True) (C1 ('MetaCons "Interval" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a, a))))
type Moment (Interval Double) Source # 
Instance details

Defined in IntervalAlgebra.Core

type Moment (Interval Int) Source # 
Instance details

Defined in IntervalAlgebra.Core

type Moment (Interval Integer) Source # 
Instance details

Defined in IntervalAlgebra.Core

type Moment (Interval UTCTime) Source # 
Instance details

Defined in IntervalAlgebra.Core

type Moment (Interval Day) Source # 
Instance details

Defined in IntervalAlgebra.Core

type Point (Interval a) Source # 
Instance details

Defined in IntervalAlgebra.Core

type Point (Interval a) = a

class PointedIv iv where Source #

Class representing intervals that can be cast to and from the canonical representation Interval a.

When iv is also an instance of PointedIv, with Ord (Point iv), it should adhere to Allen's construction of the interval algebra for intervals represented by left and right endpoints. See sections 3 and 4 of Allen 1983.

Specifically, the requirements for interval relations imply

ivBegin i < ivEnd i

This module provides default implementations for methods of Iv in that case.

Note iv should not be an instance of Intervallic unless iv ~ Interval a, since Intervallic is a class for getting and setting intervals as Interval a in particular.

A Vector whose elements are provided in strict ascending order is an example of a type that could implement PointedIv without being equivalent to Interval, with ivBegin = head and ivEnd = last.

Associated Types

type Point iv Source #

Methods

ivBegin :: iv -> Point iv Source #

Access the left ("begin") and right ("end") endpoints of an interval.

ivEnd :: iv -> Point iv Source #

Access the left ("begin") and right ("end") endpoints of an interval.

Instances

Instances details
PointedIv (Interval a) Source # 
Instance details

Defined in IntervalAlgebra.Core

Associated Types

type Point (Interval a) Source #

class PointedIv iv => SizedIv iv where Source #

The SizedIv typeclass is a generic interface for constructing and manipulating intervals. The class imposes strong requirements on its methods, in large part to ensure the constructors ivExpandr and ivExpandl return "valid" intervals, particularly in the typical case where iv also implements the interval algebra.

In all cases, ivExpandr and ivExpandl should preserve the value of the point *not* shifted. That is,

ivBegin (ivExpandr d i) == ivBegin i
ivEnd (ivExpandl d i) == ivEnd i

In addition, using Interval as example, the following must hold:

When iv is Ord, for all i == Interval (b, e),

ivExpandr d i >= i
ivExpandl d i <= i

When Moment iv is Ord,

duration (ivExpandr d i) >= max moment (duration i)
duration (ivExpandl d i) >= max moment (duration i)

In particular, if the duration d by which to expand is less than moment, and duration i >= moment then these constructors should return the input.

ivExpandr d i == i
ivExpandl d i == i

When Moment iv also is Num, the default moment value is 1 and in all cases should be positive.

moment @iv > 0

When in addition Point iv ~ Moment iv, the class provides a default duration as duration i = ivEnd i - ivBegin i.

This module enforces Point (Interval a) = a. However, it need not be that a ~ Moment iv. For example Moment (Interval UTCTime) ~ NominalDiffTime.

SizedIv and the interval algebra

When iv is an instance of Iv, the methods of this class should ensure the validity of the resulting interval with respect to the interval algebra. For example, when Point iv is Ord, they must always produce a valid interval i such that ivBegin i < ivEnd i.

In addition, the requirements of SizedIv implementations in the common case where Moment iv is Num and Ord require the constructors to produce intervals with duration of at least moment.

In order to preserve the properties above, ivExpandr, ivExpandl will not want to assume validity of the input interval. In other words, ivExpandr d i need not be the identity when d < moment since it will need to ensure the result is a valid interval even if i is not.

These two methods can therefore be used as constructors for valid intervals.

Minimal complete definition

ivExpandr, ivExpandl

Associated Types

type Moment iv Source #

Type of moment.

Methods

moment :: Moment iv Source #

The smallest duration for an iv. When 'Moment iv' is an instance of Num, the default is 1. If Moment iv is Ord and Num, moment > 0 is required.

default moment :: Num (Moment iv) => Moment iv Source #

duration :: iv -> Moment iv Source #

The duration of an iv. When Moment iv ~ Point iv and Point iv is Num this defaults to ivEnd i - ivBegin i.

default duration :: (Point iv ~ Moment iv, Num (Point iv)) => iv -> Moment iv Source #

ivExpandr :: Moment iv -> iv -> iv Source #

Resize iv by expanding to the "left" or to the "right" by some duration. If iv implements the interval algebra via Iv, these methods must produce valid intervals regardless of the validity of the input and thus serve as constructors for intervals. See also beginerval, endverval, safeInterval and related.

See the class documentation for details requirements.

>>> ivExpandr 1 (safeInterval (0, 1) :: Interval Int) == safeInterval (0, 2)
True
>>> ivExpandr 0 (safeInterval (0, 1) :: Interval Int) == safeInterval (0, 1)
True
>>> ivExpandl 1 (safeInterval (0, 1) :: Interval Int) == safeInterval (-1, 1)
True
>>> ivExpandl 0 (safeInterval (0, 1) :: Interval Int) == safeInterval (0, 1)
True

ivExpandl :: Moment iv -> iv -> iv Source #

Resize iv by expanding to the "left" or to the "right" by some duration. If iv implements the interval algebra via Iv, these methods must produce valid intervals regardless of the validity of the input and thus serve as constructors for intervals. See also beginerval, endverval, safeInterval and related.

See the class documentation for details requirements.

>>> ivExpandr 1 (safeInterval (0, 1) :: Interval Int) == safeInterval (0, 2)
True
>>> ivExpandr 0 (safeInterval (0, 1) :: Interval Int) == safeInterval (0, 1)
True
>>> ivExpandl 1 (safeInterval (0, 1) :: Interval Int) == safeInterval (-1, 1)
True
>>> ivExpandl 0 (safeInterval (0, 1) :: Interval Int) == safeInterval (0, 1)
True

Instances

Instances details
SizedIv (Interval Double) Source # 
Instance details

Defined in IntervalAlgebra.Core

Associated Types

type Moment (Interval Double) Source #

SizedIv (Interval Int) Source # 
Instance details

Defined in IntervalAlgebra.Core

Associated Types

type Moment (Interval Int) Source #

SizedIv (Interval Integer) Source # 
Instance details

Defined in IntervalAlgebra.Core

Associated Types

type Moment (Interval Integer) Source #

SizedIv (Interval UTCTime) Source #

Note this instance changes the moment to 1 Pico second, not 1 second as would be the case if the default were used.

Instance details

Defined in IntervalAlgebra.Core

Associated Types

type Moment (Interval UTCTime) Source #

SizedIv (Interval Day) Source # 
Instance details

Defined in IntervalAlgebra.Core

Associated Types

type Moment (Interval Day) Source #

class Intervallic i where Source #

The Intervallic typeclass defines how to get and set the Interval content of a data structure. Intervallic types can be compared via IntervalRelation s on their underlying Interval, and functions of this module define versions of the methods from Iv, PointedIv and SizedIv for instances of Intervallic by applying them to the contained interval.

Only the canonical representation Interval should define an instance of all four classes.

PairedInterval is the prototypical example of an Intervallic.

>>> getInterval (Interval (0, 10))
(0, 10)
>>> begin (Interval (0, 10))
0
>>> end (Interval (0, 10))
10

Methods

getInterval :: i a -> Interval a Source #

Get the interval from an i a.

setInterval :: i a -> Interval b -> i b Source #

Set the interval in an i a.

begin :: forall i a. (SizedIv (Interval a), Intervallic i) => i a -> a Source #

Access the endpoints of an i a .

end :: forall i a. (SizedIv (Interval a), Intervallic i) => i a -> a Source #

Access the endpoints of an i a .

Create new intervals

newtype ParseErrorInterval Source #

A type identifying interval parsing errors.

parseInterval :: (Show a, Ord a) => a -> a -> Either ParseErrorInterval (Interval a) Source #

Parse a pair of as to create an Interval a. Note this checks only that begin < end and has no relation to checking the conditions of SizedIv.

>>> parseInterval 0 1
Right (0, 1)
>>> parseInterval 1 0
Left (ParseErrorInterval "0<=1")

prsi :: (Show a, Ord a) => a -> a -> Either ParseErrorInterval (Interval a) Source #

A synonym for parseInterval

beginerval Source #

Arguments

:: forall a. SizedIv (Interval a) 
=> Moment (Interval a)

duration to add to the begin

-> a

the begin point of the Interval

-> Interval a 

Safely creates an 'Interval a' using x as the begin and adding max moment dur to x as the end. For the SizedIv instances this module exports, beginerval is the same as interval. However, it is defined separately since beginerval will always have this behavior whereas interval behavior might differ by implementation.

>>> beginerval (0::Int) (0::Int)
(0, 1)
>>> beginerval (1::Int) (0::Int)
(0, 1)
>>> beginerval (2::Int) (0::Int)
(0, 2)

bi Source #

Arguments

:: forall a. SizedIv (Interval a) 
=> Moment (Interval a)

duration to add to the begin

-> a

the begin point of the Interval

-> Interval a 

A synonym for beginerval

enderval Source #

Arguments

:: forall a. SizedIv (Interval a) 
=> Moment (Interval a)

duration to subtract from the end

-> a

the end point of the Interval

-> Interval a 

Safely creates an 'Interval a' using x as the end and adding negate max moment dur to x as the begin.

>>> enderval (0::Int) (0::Int)
(-1, 0)
>>> enderval (1::Int) (0::Int)
(-1, 0)
>>> enderval (2::Int) (0::Int)
(-2, 0)

ei Source #

Arguments

:: forall a. SizedIv (Interval a) 
=> Moment (Interval a)

duration to subtract from the end

-> a

the end point of the Interval

-> Interval a 

A synonym for enderval

safeInterval :: forall a. (SizedIv (Interval a), Ord (Moment (Interval a))) => (a, a) -> Interval a Source #

Safely creates an Interval from a pair of endpoints, expanding from the left endpoint if necessary to create a valid interval according to the rules of SizedIv. This function simply wraps ivExpandr.

>>> safeInterval (4, 5 ::Int)
(4, 5)
>>> safeInterval (4, 3 :: Int)
(4, 5)

si :: (SizedIv (Interval a), Ord (Moment (Interval a))) => (a, a) -> Interval a Source #

A synonym for safeInterval

Modify intervals within an Intervallic

expand Source #

Arguments

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

duration to subtract from the begin

-> Moment (Interval a)

duration to add to the end

-> i a 
-> i a 

Resize an i a to by expanding to "left" by l and to the "right" by r. In the case that l or r are less than a moment the respective endpoints are unchanged.

>>> iv2to4 = safeInterval (2::Int, 4)
>>> iv2to4' = expand 0 0 iv2to4
>>> iv1to5 = expand 1 1 iv2to4
>>> iv2to4
(2, 4)
>>> iv2to4'
(2, 4)
>>> iv1to5
(1, 5)
>>> pretty $ standardExampleDiagram [(iv2to4, "iv2to4"), (iv1to5, "iv1to5")] []
  --  <- [iv2to4]
 ---- <- [iv1to5]
=====

expandl :: (SizedIv (Interval a), Intervallic i) => Moment (Interval a) -> i a -> i a Source #

Expands an i a to the "left".

>>> iv2to4 = (safeInterval (2::Int, 4::Int))
>>> iv0to4 = expandl 2 iv2to4
>>> iv2to4
(2, 4)
>>> iv0to4
(0, 4)
>>> pretty $ standardExampleDiagram [(iv2to4, "iv2to4"), (iv0to4, "iv0to4")] []
  -- <- [iv2to4]
---- <- [iv0to4]
====

expandr :: (SizedIv (Interval a), Intervallic i) => Moment (Interval a) -> i a -> i a Source #

Expands an i a to the "right".

>>> iv2to4 = (safeInterval (2::Int, 4::Int))
>>> iv2to6 = expandr 2 iv2to4
>>> iv2to4
(2, 4)
>>> iv2to6
(2, 6)
>>> pretty $ standardExampleDiagram [(iv2to4, "iv2to4"), (iv2to6, "iv2to6")] []
  --   <- [iv2to4]
  ---- <- [iv2to6]
======

Combine two intervals

extenterval :: (SizedIv (Interval a), Ord a, Intervallic i) => i a -> i a -> Interval a Source #

Creates a new Interval spanning the extent x and y.

>>> extenterval (Interval (0, 1)) (Interval (9, 10))
(0, 10)

Interval Algebra

class Iv iv where Source #

Generic interface for defining relations between abstract representations of intervals, for the purpose of Allen's interval algebra.

In general, these "intervals" need not be representable as temporal intervals with a fixed beginning and ending. Specifically, the relations can be defined to provide temporal reasoning in a qualitative setting, examples of which are in Allen 1983.

For intervals that can be cast in canonical form as Interval s with begin and end points, see PointedIv and SizedIv.

Instances of Iv must ensure any pair of intervals satisfies exactly one of the thirteen possible IntervalRelation s.

When iv is also an instance of PointedIv, with Ord (Point iv), the requirement implies

ivBegin i < ivEnd i

Allen 1983 defines the IntervalRelation s for such cases, which is provided in this module for the canonical representation Interval a.

Examples

Expand

The following example is modified from Allen 1983 to demonstrate the algebra used for temporal reasoning in a qualitative setting, for a case where iv does not have points.

It represents the temporal logic of the statement

We found the letter during dinner, after we made the decision.
>>> :{
data GoingsOn = Dinner | FoundLetter | MadeDecision
 deriving (Show, Eq)
instance Iv GoingsOn where
 ivRelate MadeDecision Dinner = Before
 ivRelate MadeDecision FoundLetter = Before
 ivRelate FoundLetter Dinner = During
 ivRelate x y
   | x == y = Equals
   | otherwise = converseRelation (ivRelate y x)
:}

Methods

ivRelate :: iv -> iv -> IntervalRelation Source #

The IntervalRelation between two intervals.

ivBefore Source #

Arguments

:: iv

x

-> iv

y

-> Bool 

ivAfter Source #

Arguments

:: iv

x

-> iv

y

-> Bool 

ivMeets Source #

Arguments

:: iv

x

-> iv

y

-> Bool 

Is ivRelate x y == Meets? ivMetBy = flip ivMeets.

ivMetBy Source #

Arguments

:: iv

x

-> iv

y

-> Bool 

Is ivRelate x y == Meets? ivMetBy = flip ivMeets.

ivOverlaps Source #

Arguments

:: iv

x

-> iv

y

-> Bool 

Is ivRelate x y == Overlaps? ivOverlappedBy = flip ivOverlaps.

ivOverlappedBy Source #

Arguments

:: iv

x

-> iv

y

-> Bool 

Is ivRelate x y == Overlaps? ivOverlappedBy = flip ivOverlaps.

ivStarts Source #

Arguments

:: iv

x

-> iv

y

-> Bool 

Is ivRelate x y == Starts? ivStartedBy = flip ivStarts.

ivStartedBy Source #

Arguments

:: iv

x

-> iv

y

-> Bool 

Is ivRelate x y == Starts? ivStartedBy = flip ivStarts.

ivFinishes Source #

Arguments

:: iv

x

-> iv

y

-> Bool 

Is ivRelate x y == Finishes? ivFinishedBy = flip ivFinishes.

ivFinishedBy Source #

Arguments

:: iv

x

-> iv

y

-> Bool 

Is ivRelate x y == Finishes? ivFinishedBy = flip ivFinishes.

ivDuring Source #

Arguments

:: iv

x

-> iv

y

-> Bool 

Is ivRelate x y == During? ivContains = flip ivDuring.

ivContains Source #

Arguments

:: iv

x

-> iv

y

-> Bool 

Is ivRelate x y == During? ivContains = flip ivDuring.

ivEquals Source #

Arguments

:: iv

x

-> iv

y

-> Bool 

Is ivRelate x y == Equals?

Instances

Instances details
Ord a => Iv (Interval a) Source #

Implements the interval algebra for intervals represented as left and right endpoints, with points in a totally ordered set, as prescribed in Allen 1983.

Instance details

Defined in IntervalAlgebra.Core

Interval Relations and Predicates

data IntervalRelation Source #

The IntervalRelation type and the associated predicate functions enumerate the thirteen possible ways that two SizedIv objects may relate according to Allen's interval algebra. Constructors are shown with their corresponding predicate function.

Instances

Instances details
Bounded IntervalRelation Source # 
Instance details

Defined in IntervalAlgebra.Core

Enum IntervalRelation Source # 
Instance details

Defined in IntervalAlgebra.Core

Eq IntervalRelation Source # 
Instance details

Defined in IntervalAlgebra.Core

Ord IntervalRelation Source # 
Instance details

Defined in IntervalAlgebra.Core

Show IntervalRelation Source # 
Instance details

Defined in IntervalAlgebra.Core

meets :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

Does x meets y? Is x metBy y?

Example data with corresponding diagram:

>>> x = bi 5 0
>>> y = bi 5 5
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
-----      <- [x]
     ----- <- [y]
==========

Examples:

>>> x `meets` y
True
>>> x `metBy` y
False
>>> y `meets` x
False
>>> y `metBy` x
True

metBy :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

Does x meets y? Is x metBy y?

Example data with corresponding diagram:

>>> x = bi 5 0
>>> y = bi 5 5
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
-----      <- [x]
     ----- <- [y]
==========

Examples:

>>> x `meets` y
True
>>> x `metBy` y
False
>>> y `meets` x
False
>>> y `metBy` x
True

before :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

Is x before y? Does x precedes y? Is x after y? Is x precededBy y?

Example data with corresponding diagram:

>>> x = bi 3 0
>>> y = bi 4 6
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
---        <- [x]
      ---- <- [y]
==========

Examples:

>>> x `before` y
True
>>> x `precedes` y
True
>>> x `after`y
False
>>> x `precededBy` y
False
>>> y `before` x
False
>>> y `precedes` x
False
>>> y `after` x
True
>>> y `precededBy` x
True

after :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

Is x before y? Does x precedes y? Is x after y? Is x precededBy y?

Example data with corresponding diagram:

>>> x = bi 3 0
>>> y = bi 4 6
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
---        <- [x]
      ---- <- [y]
==========

Examples:

>>> x `before` y
True
>>> x `precedes` y
True
>>> x `after`y
False
>>> x `precededBy` y
False
>>> y `before` x
False
>>> y `precedes` x
False
>>> y `after` x
True
>>> y `precededBy` x
True

overlaps :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

Does x overlaps y? Is x overlappedBy y?

Example data with corresponding diagram:

>>> x = bi 6 0
>>> y = bi 6 4
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
------     <- [x]
    ------ <- [y]
==========

Examples:

>>> x `overlaps` y
True
>>> x `overlappedBy` y
False
>>> y `overlaps` x
False
>>> y `overlappedBy` x
True

overlappedBy :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

Does x overlaps y? Is x overlappedBy y?

Example data with corresponding diagram:

>>> x = bi 6 0
>>> y = bi 6 4
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
------     <- [x]
    ------ <- [y]
==========

Examples:

>>> x `overlaps` y
True
>>> x `overlappedBy` y
False
>>> y `overlaps` x
False
>>> y `overlappedBy` x
True

finishedBy :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

Does x finishes y? Is x finishedBy y?

Example data with corresponding diagram:

>>> x = bi 3 7
>>> y = bi 6 4
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
       --- <- [x]
    ------ <- [y]
==========

Examples:

>>> x `finishes` y
True
>>> x `finishedBy` y
False
>>> y `finishes` x
False
>>> y `finishedBy` x
True

finishes :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

Does x finishes y? Is x finishedBy y?

Example data with corresponding diagram:

>>> x = bi 3 7
>>> y = bi 6 4
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
       --- <- [x]
    ------ <- [y]
==========

Examples:

>>> x `finishes` y
True
>>> x `finishedBy` y
False
>>> y `finishes` x
False
>>> y `finishedBy` x
True

contains :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

Is x during y? Does x contains y?

Example data with corresponding diagram:

>>> x = bi 3 5
>>> y = bi 6 4
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
     ---   <- [x]
    ------ <- [y]
==========

Examples:

>>> x `during` y
True
>>> x `contains` y
False
>>> y `during` x
False
>>> y `contains` x
True

during :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

Is x during y? Does x contains y?

Example data with corresponding diagram:

>>> x = bi 3 5
>>> y = bi 6 4
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
     ---   <- [x]
    ------ <- [y]
==========

Examples:

>>> x `during` y
True
>>> x `contains` y
False
>>> y `during` x
False
>>> y `contains` x
True

starts :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

Does x starts y? Is x startedBy y?

Example data with corresponding diagram:

>>> x = bi 3 4
>>> y = bi 6 4
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
    ---    <- [x]
    ------ <- [y]
==========

Examples:

>>> x `starts` y
True
>>> x `startedBy` y
False
>>> y `starts` x
False
>>> y `startedBy` x
True

startedBy :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

Does x starts y? Is x startedBy y?

Example data with corresponding diagram:

>>> x = bi 3 4
>>> y = bi 6 4
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
    ---    <- [x]
    ------ <- [y]
==========

Examples:

>>> x `starts` y
True
>>> x `startedBy` y
False
>>> y `starts` x
False
>>> y `startedBy` x
True

equals :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

Does x equals y?

Example data with corresponding diagram:

>>> x = bi 6 4
>>> y = bi 6 4
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
    ------ <- [x]
    ------ <- [y]
==========

Examples:

>>> x `equals` y
True
>>> y `equals` x
True

Additional predicates and utilities

precedes :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

Is x before y? Does x precedes y? Is x after y? Is x precededBy y?

Example data with corresponding diagram:

>>> x = bi 3 0
>>> y = bi 4 6
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
---        <- [x]
      ---- <- [y]
==========

Examples:

>>> x `before` y
True
>>> x `precedes` y
True
>>> x `after`y
False
>>> x `precededBy` y
False
>>> y `before` x
False
>>> y `precedes` x
False
>>> y `after` x
True
>>> y `precededBy` x
True

precededBy :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

Is x before y? Does x precedes y? Is x after y? Is x precededBy y?

Example data with corresponding diagram:

>>> x = bi 3 0
>>> y = bi 4 6
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
---        <- [x]
      ---- <- [y]
==========

Examples:

>>> x `before` y
True
>>> x `precedes` y
True
>>> x `after`y
False
>>> x `precededBy` y
False
>>> y `before` x
False
>>> y `precedes` x
False
>>> y `after` x
True
>>> y `precededBy` x
True

disjoint :: (SizedIv (Interval a), Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

Are x and y disjoint (before, after, meets, or metBy)?

Example data with corresponding diagram:

>>> x = bi 3 0
>>> y = bi 3 5
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
---      <- [x]
     --- <- [y]
========

Examples:

>>> x `disjoint` y
True
>>> y `disjoint` x
True

Example data with corresponding diagram:

>>> x = bi 3 0
>>> y = bi 3 3
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
---    <- [x]
   --- <- [y]
======

Examples:

>>> x `disjoint` y
True
>>> y `disjoint` x
True

Example data with corresponding diagram:

>>> x = bi 6 0
>>> y = bi 3 3
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
------ <- [x]
   --- <- [y]
======

Examples:

>>> x `disjoint` y
False
>>> y `disjoint` x
False

notDisjoint :: (SizedIv (Interval a), Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

Does x concur y, meaning x and y share some support? Is x notDisjoint y? This is the complement of disjoint.

Example data with corresponding diagram:

>>> x = bi 3 0
>>> y = bi 3 4
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
---     <- [x]
    --- <- [y]
=======

Examples:

>>> x `notDisjoint` y
False
>>> y `concur` x
False

Example data with corresponding diagram:

>>> x = bi 3 0
>>> y = bi 3 3
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
---    <- [x]
   --- <- [y]
======

Examples:

>>> x `notDisjoint` y
False
>>> y `concur` x
False

Example data with corresponding diagram:

>>> x = bi 6 0
>>> y = bi 3 3
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
------ <- [x]
   --- <- [y]
======

Examples:

>>> x `notDisjoint` y
True
>>> y `concur` x
True

concur :: (SizedIv (Interval a), Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

Does x concur y, meaning x and y share some support? Is x notDisjoint y? This is the complement of disjoint.

Example data with corresponding diagram:

>>> x = bi 3 0
>>> y = bi 3 4
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
---     <- [x]
    --- <- [y]
=======

Examples:

>>> x `notDisjoint` y
False
>>> y `concur` x
False

Example data with corresponding diagram:

>>> x = bi 3 0
>>> y = bi 3 3
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
---    <- [x]
   --- <- [y]
======

Examples:

>>> x `notDisjoint` y
False
>>> y `concur` x
False

Example data with corresponding diagram:

>>> x = bi 6 0
>>> y = bi 3 3
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
------ <- [x]
   --- <- [y]
======

Examples:

>>> x `notDisjoint` y
True
>>> y `concur` x
True

within :: (SizedIv (Interval a), Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

Is x within (enclosedBy) y? That is, during, starts, finishes, or equals?

Example data with corresponding diagram:

>>> x = bi 6 4
>>> y = bi 6 4
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
    ------ <- [x]
    ------ <- [y]
==========

Examples:

>>> x `within` y
True
>>> y `enclosedBy` x
True

Example data with corresponding diagram:

>>> x = bi 6 4
>>> y = bi 5 4
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
    ------ <- [x]
    -----  <- [y]
==========

Examples:

>>> x `within` y
False
>>> y `enclosedBy` x
True

Example data with corresponding diagram:

>>> x = bi 6 4
>>> y = bi 4 5
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
    ------ <- [x]
     ----  <- [y]
==========

Examples:

>>> x `within` y
False
>>> y `enclosedBy` x
True

Example data with corresponding diagram:

>>> x = bi 2 7
>>> y = bi 1 5
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
       -- <- [x]
     -    <- [y]
=========

Examples:

>>> x `within` y
False
>>> y `enclosedBy` x
False

encloses :: (SizedIv (Interval a), Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

Does x encloses y? That is, is y within x?

Example data with corresponding diagram:

>>> x = bi 6 4
>>> y = bi 6 4
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
    ------ <- [x]
    ------ <- [y]
==========

Examples:

>>> x `encloses` y
True
>>> y `encloses` x
True

Example data with corresponding diagram:

>>> x = bi 6 4
>>> y = bi 5 4
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
    ------ <- [x]
    -----  <- [y]
==========

Examples:

>>> x `encloses` y
True
>>> y `encloses` x
False

Example data with corresponding diagram:

>>> x = bi 6 4
>>> y = bi 4 5
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
    ------ <- [x]
     ----  <- [y]
==========

Examples:

>>> x `encloses` y
True
>>> y `encloses` x
False

Example data with corresponding diagram:

>>> x = bi 2 7
>>> y = bi 1 5
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
       -- <- [x]
     -    <- [y]
=========

Examples:

>>> x `encloses` y
False
>>> y `encloses` x
False

enclosedBy :: (SizedIv (Interval a), Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

Is x within (enclosedBy) y? That is, during, starts, finishes, or equals?

Example data with corresponding diagram:

>>> x = bi 6 4
>>> y = bi 6 4
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
    ------ <- [x]
    ------ <- [y]
==========

Examples:

>>> x `within` y
True
>>> y `enclosedBy` x
True

Example data with corresponding diagram:

>>> x = bi 6 4
>>> y = bi 5 4
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
    ------ <- [x]
    -----  <- [y]
==========

Examples:

>>> x `within` y
False
>>> y `enclosedBy` x
True

Example data with corresponding diagram:

>>> x = bi 6 4
>>> y = bi 4 5
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
    ------ <- [x]
     ----  <- [y]
==========

Examples:

>>> x `within` y
False
>>> y `enclosedBy` x
True

Example data with corresponding diagram:

>>> x = bi 2 7
>>> y = bi 1 5
>>> pretty $ standardExampleDiagram [(x, "x"), (y, "y")] []
       -- <- [x]
     -    <- [y]
=========

Examples:

>>> x `within` y
False
>>> y `enclosedBy` x
False

(<|>) :: (Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) -> ComparativePredicateOf2 (i0 a) (i1 a) -> ComparativePredicateOf2 (i0 a) (i1 a) Source #

Operator for composing the union of two predicates on Intervallic s.

predicate :: (SizedIv (Interval a), Ord a, Intervallic i0, Intervallic i1) => Set IntervalRelation -> ComparativePredicateOf2 (i0 a) (i1 a) Source #

Forms a predicate function from the union of a set of IntervalRelations.

unionPredicates :: [ComparativePredicateOf2 a b] -> ComparativePredicateOf2 a b Source #

Compose a list of interval relations with _or_ to create a new ComparativePredicateOf1 i a. For example, unionPredicates [before, meets] creates a predicate function determining if one interval is either before or meets another interval.

disjointRelations :: Set IntervalRelation Source #

The set of IntervalRelation meaning two intervals are disjoint.

withinRelations :: Set IntervalRelation Source #

The set of IntervalRelation meaning one interval is within the other.

strictWithinRelations :: Set IntervalRelation Source #

The set of IntervalRelation meaning one interval is *strictly* within the other.

type ComparativePredicateOf1 a = a -> a -> Bool Source #

Defines a predicate of two objects of type a.

type ComparativePredicateOf2 a b = a -> b -> Bool Source #

Defines a predicate of two object of different types.

beginervalFromEnd Source #

Arguments

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

duration to add to the end

-> i a

the i a from which to get the end

-> Interval a 

Creates a new Interval from the end of another.

endervalFromBegin Source #

Arguments

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

duration to subtract from the begin

-> i a

the i a from which to get the begin

-> Interval a 

Creates a new Interval from the begin of another.

beginervalMoment :: forall a. SizedIv (Interval a) => a -> Interval a Source #

Safely creates a new Interval with moment length with begin at x

>>> beginervalMoment (10 :: Int)
(10, 11)

endervalMoment :: forall a. SizedIv (Interval a) => a -> Interval a Source #

Safely creates a new Interval with moment length with end at x

>>> endervalMoment (10 :: Int)
(9, 10)

shiftFromBegin :: (Num a, SizedIv (Interval a), Intervallic i1, Intervallic i0) => i0 a -> i1 a -> i1 a Source #

Modifies the endpoints of second argument's interval by taking the difference from the first's input's begin.

Example data with corresponding diagram:

>>> a = bi 3 2 :: Interval Int
>>> a
(2, 5)
>>> x = bi 3 7 :: Interval Int
>>> x
(7, 10)
>>> y = bi 4 9 :: Interval Int
>>> y
(9, 13)
>>> pretty $ standardExampleDiagram [(a, "a"), (x, "x"), (y, "y")] []
  ---         <- [a]
       ---    <- [x]
         ---- <- [y]
=============

Examples:

>>> x' = shiftFromBegin a x
>>> x'
(5, 8)
>>> y' = shiftFromBegin a y
>>> y'
(7, 11)
>>> pretty $ standardExampleDiagram [(x', "x'"), (y', "y'")] []
     ---    <- [x']
       ---- <- [y']
===========

shiftFromEnd :: (Num a, SizedIv (Interval a), Intervallic i1, Intervallic i0) => i0 a -> i1 a -> i1 a Source #

Modifies the endpoints of second argument's interval by taking the difference from the first's input's end.

Example data with corresponding diagram:

>>> a = bi 3 2 :: Interval Int
>>> a
(2, 5)
>>> x = bi 3 7 :: Interval Int
>>> x
(7, 10)
>>> y = bi 4 9 :: Interval Int
>>> y
(9, 13)
>>> pretty $ standardExampleDiagram [(a, "a"), (x, "x"), (y, "y")] []
  ---         <- [a]
       ---    <- [x]
         ---- <- [y]
=============

Examples:

>>> x' = shiftFromEnd a x
>>> x'
(2, 5)
>>> y' = shiftFromEnd a y
>>> y'
(4, 8)
>>> pretty $ standardExampleDiagram [(x', "x'"), (y', "y'")] []
  ---    <- [x']
    ---- <- [y']
========

momentize :: forall i a. (SizedIv (Interval a), Intervallic i) => i a -> i a Source #

Changes the duration of an Intervallic value to a moment starting at the begin of the interval. Uses beginervalMoment.

>>> momentize (Interval (6, 10))
(6, 7)

toEnumInterval :: (Enum a, Intervallic i) => i Int -> i a Source #

Converts an i Int to an i a via toEnum. This assumes the provided toEnum method is strictly monotone increasing: For a types that are Ord, then for Int values x, y it holds that x < y implies toEnum x < toEnum y.

fromEnumInterval :: (Enum a, Intervallic i) => i a -> i Int Source #

Converts an i a to an i Int via fromEnum. This assumes the provided fromEnum method is strictly monotone increasing: For a types that are Ord with values x, y, then x < y implies fromEnum x < fromEnum y, so long as the latter is well-defined.

Algebraic operations

relate :: (Iv (Interval a), Intervallic i0, Intervallic i1) => i0 a -> i1 a -> IntervalRelation Source #

Compare two i a to determine their IntervalRelation.

>>> relate (Interval (0::Int, 1)) (Interval (1, 2))
Meets
>>> relate (Interval (1::Int, 2)) (Interval (0, 1))
MetBy

compose :: IntervalRelation -> IntervalRelation -> Set IntervalRelation Source #

Compose two interval relations according to the rules of the algebra. The rules are enumerated according to this table.