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

Contents

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 four typeclasses designed to separate concerns of constructing, relating, and combining Intervals:

  1. Intervallic provides an interface to the data structure of an Interval, defining how an Interval a is constructed.
  2. IntervalAlgebraic provides an interface to the IntervalRelations, the workhorse of Allen's temporal logic.
  3. IntervalCombinable provides an interface to methods of combining two Intervals.
  4. IntervalSizeable and the related Moment provides methods for measuring and modifying the size of an interval. collections of intervals.

An advantage of nested typeclass design is that developers can define an Interval of type a with just the amount of structure that they need.

Total Ordering of Intervals

The modules makes the (opinionated) choice of a total ordering for Intervallic Intervals. Namely, the ordering is based on first ordering the begins then the ends.

Development

This module is under development and the API may change in the future.

Synopsis

Classes

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

The Intervallic typeclass specifies how an Interval as is constructed. It also includes functions for getting the begin and end of an Interval a.

Minimal complete definition

Nothing

Methods

parseInterval :: a -> a -> Either String (Interval a) Source #

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

unsafeInterval :: a -> a -> Interval a Source #

Create a new Interval a. This function is not safe as it does not enforce that \(x < y\). Use with caution. It is meant to be helper function in early prototyping of this package. This function may be deprecated in future releases.

begin :: Interval a -> a Source #

Access the ends of an Interval a .

end :: Interval a -> a Source #

Access the ends of an Interval a .

class (Eq a, Intervallic a) => IntervalAlgebraic a where Source #

The IntervalAlgebraic typeclass specifies the functions and relational operators for interval-based temporal logic. The typeclass defines the relational operators for intervals, plus other useful utilities such as disjoint, within, and unionPredicates.

Minimal complete definition

Nothing

Methods

relate :: Interval a -> Interval a -> IntervalRelation a Source #

Compare two intervals to determine their IntervalRelation.

predicate' :: IntervalRelation a -> ComparativePredicateOf (Interval a) Source #

Maps an IntervalRelation to its corresponding predicate function.

predicates :: Set (IntervalRelation a) -> [ComparativePredicateOf (Interval a)] Source #

Given a set of IntervalRelations return a list of predicate functions corresponding to each relation.

predicate :: Set (IntervalRelation a) -> ComparativePredicateOf (Interval a) Source #

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

toSet :: [IntervalRelation a] -> Set (IntervalRelation a) Source #

Shortcut to creating a 'Set IntervalRelation' from a list.

compose :: IntervalRelation a -> IntervalRelation a -> Set (IntervalRelation a) Source #

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

complement :: Set (IntervalRelation a) -> Set (IntervalRelation a) Source #

Finds the complement of a 'Set IntervalRelation'.

intersection :: Set (IntervalRelation a) -> Set (IntervalRelation a) -> Set (IntervalRelation a) Source #

Find the intersection of two Sets of IntervalRelation

union :: Set (IntervalRelation a) -> Set (IntervalRelation a) -> Set (IntervalRelation a) Source #

Find the union of two Sets of IntervalRelation

converse :: Set (IntervalRelation a) -> Set (IntervalRelation a) Source #

Find the converse of a 'Set IntervalRelation'.

equals :: ComparativePredicateOf (Interval a) Source #

Does x equal y?

meets :: ComparativePredicateOf (Interval a) Source #

Does x meet y? Is y metBy x?

metBy :: ComparativePredicateOf (Interval a) Source #

Does x meet y? Is y metBy x?

before :: ComparativePredicateOf (Interval a) Source #

Is x before y? Is x after y?

after :: ComparativePredicateOf (Interval a) Source #

Is x before y? Is x after y?

overlaps :: ComparativePredicateOf (Interval a) Source #

Does x overlap y? Is x overlapped by y?

overlappedBy :: ComparativePredicateOf (Interval a) Source #

Does x overlap y? Is x overlapped by y?

starts :: ComparativePredicateOf (Interval a) Source #

Does x start y? Is x started by y?

startedBy :: ComparativePredicateOf (Interval a) Source #

Does x start y? Is x started by y?

precedes :: ComparativePredicateOf (Interval a) Source #

Synonyms for starts and startedBy

precededBy :: ComparativePredicateOf (Interval a) Source #

Synonyms for starts and startedBy

finishes :: ComparativePredicateOf (Interval a) Source #

Does x finish y? Is x finished by y?

finishedBy :: ComparativePredicateOf (Interval a) Source #

Does x finish y? Is x finished by y?

during :: ComparativePredicateOf (Interval a) Source #

Is x during y? Does x contain y?

contains :: ComparativePredicateOf (Interval a) Source #

Is x during y? Does x contain y?

unionPredicates :: [ComparativePredicateOf (Interval a)] -> ComparativePredicateOf (Interval a) Source #

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

(<|>) :: ComparativePredicateOf (Interval a) -> ComparativePredicateOf (Interval a) -> ComparativePredicateOf (Interval a) Source #

Operator for composing the union of two predicates

disjointRelations :: Set (IntervalRelation a) Source #

withinRelations :: Set (IntervalRelation a) Source #

disjoint :: ComparativePredicateOf (Interval a) Source #

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

notDisjoint :: ComparativePredicateOf (Interval a) Source #

Are x and y not disjoint; i.e. do they share any support?

concur :: ComparativePredicateOf (Interval a) Source #

A synonym for notDisjoint.

within :: ComparativePredicateOf (Interval a) Source #

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

enclose :: ComparativePredicateOf (Interval a) Source #

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

enclosedBy :: ComparativePredicateOf (Interval a) Source #

Synonym for within.

Instances

Instances details
IntervalAlgebraic Int Source # 
Instance details

Defined in IntervalAlgebra

Methods

relate :: Interval Int -> Interval Int -> IntervalRelation Int Source #

predicate' :: IntervalRelation Int -> ComparativePredicateOf (Interval Int) Source #

predicates :: Set (IntervalRelation Int) -> [ComparativePredicateOf (Interval Int)] Source #

predicate :: Set (IntervalRelation Int) -> ComparativePredicateOf (Interval Int) Source #

toSet :: [IntervalRelation Int] -> Set (IntervalRelation Int) Source #

compose :: IntervalRelation Int -> IntervalRelation Int -> Set (IntervalRelation Int) Source #

complement :: Set (IntervalRelation Int) -> Set (IntervalRelation Int) Source #

intersection :: Set (IntervalRelation Int) -> Set (IntervalRelation Int) -> Set (IntervalRelation Int) Source #

union :: Set (IntervalRelation Int) -> Set (IntervalRelation Int) -> Set (IntervalRelation Int) Source #

converse :: Set (IntervalRelation Int) -> Set (IntervalRelation Int) Source #

equals :: ComparativePredicateOf (Interval Int) Source #

meets :: ComparativePredicateOf (Interval Int) Source #

metBy :: ComparativePredicateOf (Interval Int) Source #

before :: ComparativePredicateOf (Interval Int) Source #

after :: ComparativePredicateOf (Interval Int) Source #

overlaps :: ComparativePredicateOf (Interval Int) Source #

overlappedBy :: ComparativePredicateOf (Interval Int) Source #

starts :: ComparativePredicateOf (Interval Int) Source #

startedBy :: ComparativePredicateOf (Interval Int) Source #

precedes :: ComparativePredicateOf (Interval Int) Source #

precededBy :: ComparativePredicateOf (Interval Int) Source #

finishes :: ComparativePredicateOf (Interval Int) Source #

finishedBy :: ComparativePredicateOf (Interval Int) Source #

during :: ComparativePredicateOf (Interval Int) Source #

contains :: ComparativePredicateOf (Interval Int) Source #

unionPredicates :: [ComparativePredicateOf (Interval Int)] -> ComparativePredicateOf (Interval Int) Source #

(<|>) :: ComparativePredicateOf (Interval Int) -> ComparativePredicateOf (Interval Int) -> ComparativePredicateOf (Interval Int) Source #

disjointRelations :: Set (IntervalRelation Int) Source #

withinRelations :: Set (IntervalRelation Int) Source #

disjoint :: ComparativePredicateOf (Interval Int) Source #

notDisjoint :: ComparativePredicateOf (Interval Int) Source #

concur :: ComparativePredicateOf (Interval Int) Source #

within :: ComparativePredicateOf (Interval Int) Source #

enclose :: ComparativePredicateOf (Interval Int) Source #

enclosedBy :: ComparativePredicateOf (Interval Int) Source #

IntervalAlgebraic Integer Source # 
Instance details

Defined in IntervalAlgebra

Methods

relate :: Interval Integer -> Interval Integer -> IntervalRelation Integer Source #

predicate' :: IntervalRelation Integer -> ComparativePredicateOf (Interval Integer) Source #

predicates :: Set (IntervalRelation Integer) -> [ComparativePredicateOf (Interval Integer)] Source #

predicate :: Set (IntervalRelation Integer) -> ComparativePredicateOf (Interval Integer) Source #

toSet :: [IntervalRelation Integer] -> Set (IntervalRelation Integer) Source #

compose :: IntervalRelation Integer -> IntervalRelation Integer -> Set (IntervalRelation Integer) Source #

complement :: Set (IntervalRelation Integer) -> Set (IntervalRelation Integer) Source #

intersection :: Set (IntervalRelation Integer) -> Set (IntervalRelation Integer) -> Set (IntervalRelation Integer) Source #

union :: Set (IntervalRelation Integer) -> Set (IntervalRelation Integer) -> Set (IntervalRelation Integer) Source #

converse :: Set (IntervalRelation Integer) -> Set (IntervalRelation Integer) Source #

equals :: ComparativePredicateOf (Interval Integer) Source #

meets :: ComparativePredicateOf (Interval Integer) Source #

metBy :: ComparativePredicateOf (Interval Integer) Source #

before :: ComparativePredicateOf (Interval Integer) Source #

after :: ComparativePredicateOf (Interval Integer) Source #

overlaps :: ComparativePredicateOf (Interval Integer) Source #

overlappedBy :: ComparativePredicateOf (Interval Integer) Source #

starts :: ComparativePredicateOf (Interval Integer) Source #

startedBy :: ComparativePredicateOf (Interval Integer) Source #

precedes :: ComparativePredicateOf (Interval Integer) Source #

precededBy :: ComparativePredicateOf (Interval Integer) Source #

finishes :: ComparativePredicateOf (Interval Integer) Source #

finishedBy :: ComparativePredicateOf (Interval Integer) Source #

during :: ComparativePredicateOf (Interval Integer) Source #

contains :: ComparativePredicateOf (Interval Integer) Source #

unionPredicates :: [ComparativePredicateOf (Interval Integer)] -> ComparativePredicateOf (Interval Integer) Source #

(<|>) :: ComparativePredicateOf (Interval Integer) -> ComparativePredicateOf (Interval Integer) -> ComparativePredicateOf (Interval Integer) Source #

disjointRelations :: Set (IntervalRelation Integer) Source #

withinRelations :: Set (IntervalRelation Integer) Source #

disjoint :: ComparativePredicateOf (Interval Integer) Source #

notDisjoint :: ComparativePredicateOf (Interval Integer) Source #

concur :: ComparativePredicateOf (Interval Integer) Source #

within :: ComparativePredicateOf (Interval Integer) Source #

enclose :: ComparativePredicateOf (Interval Integer) Source #

enclosedBy :: ComparativePredicateOf (Interval Integer) Source #

IntervalAlgebraic Day Source # 
Instance details

Defined in IntervalAlgebra

Methods

relate :: Interval Day -> Interval Day -> IntervalRelation Day Source #

predicate' :: IntervalRelation Day -> ComparativePredicateOf (Interval Day) Source #

predicates :: Set (IntervalRelation Day) -> [ComparativePredicateOf (Interval Day)] Source #

predicate :: Set (IntervalRelation Day) -> ComparativePredicateOf (Interval Day) Source #

toSet :: [IntervalRelation Day] -> Set (IntervalRelation Day) Source #

compose :: IntervalRelation Day -> IntervalRelation Day -> Set (IntervalRelation Day) Source #

complement :: Set (IntervalRelation Day) -> Set (IntervalRelation Day) Source #

intersection :: Set (IntervalRelation Day) -> Set (IntervalRelation Day) -> Set (IntervalRelation Day) Source #

union :: Set (IntervalRelation Day) -> Set (IntervalRelation Day) -> Set (IntervalRelation Day) Source #

converse :: Set (IntervalRelation Day) -> Set (IntervalRelation Day) Source #

equals :: ComparativePredicateOf (Interval Day) Source #

meets :: ComparativePredicateOf (Interval Day) Source #

metBy :: ComparativePredicateOf (Interval Day) Source #

before :: ComparativePredicateOf (Interval Day) Source #

after :: ComparativePredicateOf (Interval Day) Source #

overlaps :: ComparativePredicateOf (Interval Day) Source #

overlappedBy :: ComparativePredicateOf (Interval Day) Source #

starts :: ComparativePredicateOf (Interval Day) Source #

startedBy :: ComparativePredicateOf (Interval Day) Source #

precedes :: ComparativePredicateOf (Interval Day) Source #

precededBy :: ComparativePredicateOf (Interval Day) Source #

finishes :: ComparativePredicateOf (Interval Day) Source #

finishedBy :: ComparativePredicateOf (Interval Day) Source #

during :: ComparativePredicateOf (Interval Day) Source #

contains :: ComparativePredicateOf (Interval Day) Source #

unionPredicates :: [ComparativePredicateOf (Interval Day)] -> ComparativePredicateOf (Interval Day) Source #

(<|>) :: ComparativePredicateOf (Interval Day) -> ComparativePredicateOf (Interval Day) -> ComparativePredicateOf (Interval Day) Source #

disjointRelations :: Set (IntervalRelation Day) Source #

withinRelations :: Set (IntervalRelation Day) Source #

disjoint :: ComparativePredicateOf (Interval Day) Source #

notDisjoint :: ComparativePredicateOf (Interval Day) Source #

concur :: ComparativePredicateOf (Interval Day) Source #

within :: ComparativePredicateOf (Interval Day) Source #

enclose :: ComparativePredicateOf (Interval Day) Source #

enclosedBy :: ComparativePredicateOf (Interval Day) Source #

class IntervalAlgebraic a => IntervalCombinable a where Source #

The IntervalCombinable typeclass provides methods for (possibly) combining two Intervals.

Minimal complete definition

Nothing

Methods

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

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

extenterval :: Interval a -> Interval a -> Interval a Source #

Creates a new Interval spanning the extent x and y

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

(<+>) :: (Semigroup (f (Interval a)), Applicative f) => Interval a -> Interval a -> f (Interval 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.

intersect :: Interval a -> Interval a -> Maybe (Interval a) Source #

Forms a Just new interval from the intersection of two intervals, provided the intervals are not disjoint.

Instances

Instances details
IntervalCombinable Int Source # 
Instance details

Defined in IntervalAlgebra

IntervalCombinable Integer Source # 
Instance details

Defined in IntervalAlgebra

IntervalCombinable Day Source # 
Instance details

Defined in IntervalAlgebra

class (Intervallic a, Num b, Ord b) => Moment a b | a -> b where Source #

The Moment class fixes the smallest duration of an 'Intervallic a'.

Minimal complete definition

Nothing

Methods

moment :: b Source #

Instances

Instances details
Moment Int Int Source # 
Instance details

Defined in IntervalAlgebra

Methods

moment :: Int Source #

Moment Integer Integer Source # 
Instance details

Defined in IntervalAlgebra

Moment Day Integer Source # 
Instance details

Defined in IntervalAlgebra

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

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

Minimal complete definition

add, diff

Methods

duration :: Interval a -> b Source #

Determine the duration of an 'Interval 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.

expand :: b -> b -> Interval a -> Interval a Source #

Resize an 'Interval 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.

expandl :: b -> Interval a -> Interval a Source #

Expands an 'Interval a' to left by i.

expandr :: b -> Interval a -> Interval a Source #

Expands an 'Interval a' to right by i.

beginerval :: b -> a -> Interval a Source #

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

enderval :: b -> a -> Interval a Source #

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

Instances

Instances details
IntervalSizeable Int Int Source # 
Instance details

Defined in IntervalAlgebra

IntervalSizeable Integer Integer Source # 
Instance details

Defined in IntervalAlgebra

IntervalSizeable Day Integer Source # 
Instance details

Defined in IntervalAlgebra

Types

data Interval a Source #

An Interval a is a pair of as \( (x, y) \text{ where } x < y\). The Intervallic class provides a safe parseInterval function that returns a Left error if \(y < x\) and unsafeInterval as constructor for creating an interval that may not be valid.

Instances

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

Defined in IntervalAlgebra

Methods

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

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

Intervallic 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 a, Show 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

data IntervalRelation a Source #

The IntervalRelation type enumerates the thirteen possible ways that two Interval a objects can relate according to the interval algebra.

Meets, Metby

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

Before, After

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

Overlaps, OverlappedBy

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

Starts, StartedBy

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

Finishes, FinishedBy

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

During, Contains

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

Equal

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

Instances

Instances details
Bounded (IntervalRelation a) Source # 
Instance details

Defined in IntervalAlgebra

Enum (IntervalRelation a) Source # 
Instance details

Defined in IntervalAlgebra

Eq (IntervalRelation a) Source # 
Instance details

Defined in IntervalAlgebra

Ord (IntervalRelation a) Source # 
Instance details

Defined in IntervalAlgebra

Read (IntervalRelation a) Source # 
Instance details

Defined in IntervalAlgebra

Show (IntervalRelation a) Source # 
Instance details

Defined in IntervalAlgebra

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

Defines a predicate of two objects of type a.