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

IntervalAlgebra

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 is built around three typeclasses designed to separate concerns of constructing, relating, and combining types that contain Intervals:

  1. Intervallic provides an interface to the data structures which contain an Interval.
  2. IntervalCombinable provides an interface to methods of combining two Intervals.
  3. IntervalSizeable provides methods for measuring and modifying the size of an interval.
Synopsis

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
Functor Interval Source # 
Instance details

Defined in IntervalAlgebra

Methods

fmap :: (a -> b) -> Interval a -> Interval b #

(<$) :: a -> Interval b -> Interval a #

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

Defined in IntervalAlgebra

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

Defined in IntervalAlgebra

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

Defined in IntervalAlgebra

Methods

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

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

(Eq (Interval a), Intervallic Interval 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

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 #

Intervallic Interval a => Show (Interval a) Source # 
Instance details

Defined in IntervalAlgebra

Methods

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

show :: Interval a -> String #

showList :: [Interval a] -> ShowS #

Arbitrary (Interval Int) Source # 
Instance details

Defined in IntervalAlgebra.Arbitrary

Arbitrary (Interval Day) Source # 
Instance details

Defined in IntervalAlgebra.Arbitrary

class (Ord a, Show a) => Intervallic i a where Source #

The Intervallic typeclass defines how to get and set the Interval content of a data structure. It also includes functions for getting the endpoints of the Interval via begin and end.

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

Minimal complete definition

getInterval, setInterval

Methods

getInterval :: i a -> Interval a Source #

Get the interval from an i a.

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

Set the interval in an i a.

begin :: i a -> a Source #

Access the endpoints of an i a .

end :: i a -> a Source #

Access the endpoints of an i a .

Instances

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

Defined in IntervalAlgebra

(Ord a, Show a) => Intervallic (PairedInterval b) a Source # 
Instance details

Defined in IntervalAlgebra.PairedInterval

Create new intervals

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

Safely parse a pair of as to create an Interval a.

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

beginerval Source #

Arguments

:: IntervalSizeable a b 
=> b

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.

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

enderval Source #

Arguments

:: IntervalSizeable a b 
=> b

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)

Modify intervals

expand Source #

Arguments

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

duration to subtract from the begin

-> b

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.

>>> expand 0 0 (Interval (0::Int, 2::Int))
(0, 2)
>>> expand 1 1 (Interval (0::Int, 2::Int))
(-1, 3)

expandl :: (IntervalSizeable a b, Intervallic i a) => b -> i a -> i a Source #

Expands an i a to "left".

>>> expandl 2 (Interval (0::Int, 2::Int))
(-2, 2)

expandr :: (IntervalSizeable a b, Intervallic i a) => b -> i a -> i a Source #

Expands an i a to "right".

>>> expandr 2 (Interval (0::Int, 2::Int))
(0, 4)

Interval Algebra

Interval Relations and Predicates

data IntervalRelation Source #

The IntervalRelation type and the associated predicate functions enumerate the thirteen possible ways that two Interval 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

Enum IntervalRelation Source # 
Instance details

Defined in IntervalAlgebra

Eq IntervalRelation Source # 
Instance details

Defined in IntervalAlgebra

Ord IntervalRelation Source # 
Instance details

Defined in IntervalAlgebra

Read IntervalRelation Source # 
Instance details

Defined in IntervalAlgebra

Show IntervalRelation Source # 
Instance details

Defined in IntervalAlgebra

Meets, Metby

x `meets` y
y `metBy` x
   x: |-----|
   y:       |-----| 
   

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

Does x meets y? Is x metBy y?

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

Does x meets y? Is x metBy y?

Before, After

x `before` y
y `after` x
   x: |-----|  
   y:          |-----|
   

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

Is x before y? Is x after y?

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

Is x before y? Is x after y?

Overlaps, OverlappedBy

x `overlaps` y
y `overlappedBy` x
   x: |-----|
   y:     |-----|
   

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

Does x overlap y? Is x overlapped by y?

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

Does x overlap y? Is x overlapped by y?

Finishes, FinishedBy

x `finishes` y
y `finishedBy` x
   x:   |---| 
   y: |-----|
   

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

Does x finish y? Is x finished by y?

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

Does x finish y? Is x finished by y?

During, Contains

x `during` y
y `contains` x
   x:   |-| 
   y: |-----|
   

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

Is x during y? Does x contain y?

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

Is x during y? Does x contain y?

Starts, StartedBy

x `starts` y
y `startedBy` x
   x: |---| 
   y: |-----|
   

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

Does x start y? Is x started by y?

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

Does x start y? Is x started by y?

Equal

x `equal` y
y `equal` x
   x: |-----| 
   y: |-----|
   

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

Does x equal y?

Additional predicates and utilities

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

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

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

Are x and y not disjoint (concur); i.e. do they share any support? This is the complement of disjoint.

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

Are x and y not disjoint (concur); i.e. do they share any support? This is the complement of disjoint.

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

Is x entirely *within* (enclosed by) the endpoints of y? That is, during, starts, finishes, or equals?

enclose :: (Intervallic i0 a, Intervallic i1 a) => ComparativePredicateOf2 (i0 a) (i1 a) Source #

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

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

Is x entirely *within* (enclosed by) the endpoints of y? That is, during, starts, finishes, or equals?

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

Operator for composing the union of two predicates

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.

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.

Algebraic operations

relate :: (Intervallic i0 a, Intervallic i1 a) => 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.

Combine two intervals

class Intervallic i a => IntervalCombinable i a where Source #

The IntervalCombinable typeclass provides methods for (possibly) combining two i as to form an Interval.

Minimal complete definition

(><), (<+>)

Methods

(.+.) :: i a -> i a -> Maybe (i a) Source #

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

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

(<+>) :: (Semigroup (f (i a)), Applicative f) => i a -> i a -> f (i a) Source #

If x is before y, return f x appended to f y. Otherwise, return extenterval of x and y (wrapped in f). This is useful for (left) folding over an *ordered* container of Intervals and combining intervals when x is *not* before y.

Instances

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

Defined in IntervalAlgebra

(Ord a, Show a, Eq b, Monoid b) => IntervalCombinable (PairedInterval b) a Source # 
Instance details

Defined in IntervalAlgebra.PairedInterval

extenterval :: Intervallic i a => 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)

Measure an interval

class (Show a, Ord a, Num b, Ord b) => IntervalSizeable a b | a -> b where Source #

The IntervalSizeable typeclass provides functions to determine the size of an Intervallic type and to resize an 'Interval a'.

Minimal complete definition

add, diff

Methods

moment :: b Source #

The smallest duration for an 'Interval a'.

moment' :: Intervallic i a => i a -> b Source #

Gives back a moment based on the input's type.

duration :: Intervallic i a => i a -> b Source #

Determine the duration of an 'i a'.

add :: b -> a -> a Source #

Shifts an a. Most often, the b will be the same type as a. But for example, if a is Day then b could be Int.

diff :: a -> a -> b Source #

Takes the difference between two a to return a b.