Copyright | (c) NoviSci Inc 2020 |
---|---|
License | BSD3 |
Maintainer | bsaul@novisci.com |
Safe Haskell | Safe |
Language | Haskell2010 |
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
s: Interval
provides an interface to the data structures which contain anIntervallic
.Interval
provides an interface to methods of combining twoIntervalCombinable
.Interval
s
provides methods for measuring and modifying the size of an interval.IntervalSizeable
Synopsis
- data Interval a
- class Ord a => Intervallic i a where
- getInterval :: i a -> Interval a
- setInterval :: i a -> Interval a -> i a
- begin, end :: i a -> a
- parseInterval :: (Show a, Ord a) => a -> a -> Either String (Interval a)
- beginerval :: IntervalSizeable a b => b -> a -> Interval a
- enderval :: IntervalSizeable a b => b -> a -> Interval a
- expand :: (IntervalSizeable a b, Intervallic i a) => b -> b -> i a -> i a
- expandl :: (IntervalSizeable a b, Intervallic i a) => b -> i a -> i a
- expandr :: (IntervalSizeable a b, Intervallic i a) => b -> i a -> i a
- data IntervalRelation
- meets :: (Intervallic i0 a, Intervallic i1 a) => ComparativePredicateOf2 (i0 a) (i1 a)
- metBy :: (Intervallic i0 a, Intervallic i1 a) => ComparativePredicateOf2 (i0 a) (i1 a)
- before :: (Intervallic i0 a, Intervallic i1 a) => ComparativePredicateOf2 (i0 a) (i1 a)
- after :: (Intervallic i0 a, Intervallic i1 a) => ComparativePredicateOf2 (i0 a) (i1 a)
- overlaps :: (Intervallic i0 a, Intervallic i1 a) => ComparativePredicateOf2 (i0 a) (i1 a)
- overlappedBy :: (Intervallic i0 a, Intervallic i1 a) => ComparativePredicateOf2 (i0 a) (i1 a)
- finishedBy :: (Intervallic i0 a, Intervallic i1 a) => ComparativePredicateOf2 (i0 a) (i1 a)
- finishes :: (Intervallic i0 a, Intervallic i1 a) => ComparativePredicateOf2 (i0 a) (i1 a)
- contains :: (Intervallic i0 a, Intervallic i1 a) => ComparativePredicateOf2 (i0 a) (i1 a)
- during :: (Intervallic i0 a, Intervallic i1 a) => ComparativePredicateOf2 (i0 a) (i1 a)
- starts :: (Intervallic i0 a, Intervallic i1 a) => ComparativePredicateOf2 (i0 a) (i1 a)
- startedBy :: (Intervallic i0 a, Intervallic i1 a) => ComparativePredicateOf2 (i0 a) (i1 a)
- equals :: (Intervallic i0 a, Intervallic i1 a) => ComparativePredicateOf2 (i0 a) (i1 a)
- disjoint :: (Intervallic i0 a, Intervallic i1 a) => ComparativePredicateOf2 (i0 a) (i1 a)
- notDisjoint :: (Intervallic i0 a, Intervallic i1 a) => ComparativePredicateOf2 (i0 a) (i1 a)
- concur :: (Intervallic i0 a, Intervallic i1 a) => ComparativePredicateOf2 (i0 a) (i1 a)
- within :: (Intervallic i0 a, Intervallic i1 a) => ComparativePredicateOf2 (i0 a) (i1 a)
- enclose :: (Intervallic i0 a, Intervallic i1 a) => ComparativePredicateOf2 (i0 a) (i1 a)
- enclosedBy :: (Intervallic i0 a, Intervallic i1 a) => ComparativePredicateOf2 (i0 a) (i1 a)
- (<|>) :: (Intervallic i0 a, Intervallic i1 a) => ComparativePredicateOf2 (i0 a) (i1 a) -> ComparativePredicateOf2 (i0 a) (i1 a) -> ComparativePredicateOf2 (i0 a) (i1 a)
- unionPredicates :: [ComparativePredicateOf2 a b] -> ComparativePredicateOf2 a b
- type ComparativePredicateOf1 a = a -> a -> Bool
- type ComparativePredicateOf2 a b = a -> b -> Bool
- intervalRelations :: Set IntervalRelation
- relate :: (Intervallic i0 a, Intervallic i1 a) => i0 a -> i1 a -> IntervalRelation
- compose :: IntervalRelation -> IntervalRelation -> Set IntervalRelation
- complement :: Set IntervalRelation -> Set IntervalRelation
- union :: Set IntervalRelation -> Set IntervalRelation -> Set IntervalRelation
- intersection :: Set IntervalRelation -> Set IntervalRelation -> Set IntervalRelation
- converse :: Set IntervalRelation -> Set IntervalRelation
- class Intervallic i a => IntervalCombinable i a where
- extenterval :: Intervallic i a => i a -> i a -> Interval a
- class (Ord a, Num b, Ord b) => IntervalSizeable a b | a -> b where
- moment :: b
- moment' :: Intervallic i a => i a -> b
- duration :: Intervallic i a => i a -> b
- add :: b -> a -> a
- diff :: a -> a -> b
Intervals
An
is a pair \( (x, y) \text{ such that } x < y\). To create
intervals use the Interval
a
, parseInterval
, or beginerval
functions.enderval
Instances
Functor Interval Source # | |
Ord a => IntervalCombinable Interval a Source # | |
Ord a => Intervallic Interval a Source # | |
Eq a => Eq (Interval a) Source # | |
Ord a => Ord (Interval a) Source # | Imposes a total ordering on |
(Show a, Ord a) => Show (Interval a) Source # | |
Arbitrary (Interval Int) Source # | |
Arbitrary (Interval Day) Source # | |
class Ord a => Intervallic i a where Source #
The
typeclass defines how to get and set the Intervallic
Interval
content
of a data structure. It also includes functions for getting the endpoints of the
Interval
via
and begin
. end
>>>
getInterval (Interval (0, 10))
(0, 10)
>>>
begin (Interval (0, 10))
0
>>>
end (Interval (0, 10))
10
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
.
Access the endpoints of an i a
.
Access the endpoints of an i a
.
Instances
Ord a => Intervallic Interval a Source # | |
Ord a => Intervallic (PairedInterval b) a Source # | |
Defined in IntervalAlgebra.PairedInterval getInterval :: PairedInterval b a -> Interval a Source # setInterval :: PairedInterval b a -> Interval a -> PairedInterval b a Source # begin :: PairedInterval b a -> a Source # end :: PairedInterval b a -> a Source # |
Create new intervals
parseInterval :: (Show a, Ord a) => a -> a -> Either String (Interval a) Source #
Safely parse a pair of a
s to create an
.Interval
a
>>>
parseInterval 0 1
Right (0, 1)
>>>
parseInterval 1 0
Left "0<1"
:: IntervalSizeable a b | |
=> b |
|
-> a | |
-> Interval a |
:: IntervalSizeable a b | |
=> b |
|
-> a | |
-> Interval a |
Modify intervals
:: (IntervalSizeable a b, Intervallic i a) | |
=> b | duration to subtract from the |
-> b | duration to add to the |
-> 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
objects may Interval
relate
according
to Allen's interval algebra. Constructors are shown with their corresponding
predicate function.
Instances
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 #
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 #
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 #
(<|>) :: (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
. For example,
ComparativePredicateOf1
i aunionPredicates [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
intervalRelations :: Set IntervalRelation Source #
The Set
of all IntervalRelation
s.
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.
complement :: Set IntervalRelation -> Set IntervalRelation Source #
Finds the complement of a
.Set
IntervalRelation
union :: Set IntervalRelation -> Set IntervalRelation -> Set IntervalRelation Source #
Find the union of two Set
s of IntervalRelation
s.
intersection :: Set IntervalRelation -> Set IntervalRelation -> Set IntervalRelation Source #
Find the intersection of two Set
s of IntervalRelation
s.
converse :: Set IntervalRelation -> Set IntervalRelation Source #
Find the converse of a
. Set
IntervalRelation
Combine two intervals
class Intervallic i a => IntervalCombinable i a where Source #
The
typeclass provides methods for (possibly) combining
two IntervalCombinable
i a
s to form a
, or in case of Maybe
i a><
, a possibly different
Intervallic
type.
(.+.) :: i a -> i a -> Maybe (i a) Source #
Maybe form a new i a
by the union of two i a
s 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 Interval
s and combining
intervals when x
is *not* before
y
.
Instances
Ord a => IntervalCombinable Interval a Source # | |
(Ord a, Eq b, Monoid b) => IntervalCombinable (PairedInterval b) a Source # | |
Defined in IntervalAlgebra.PairedInterval (.+.) :: PairedInterval b a -> PairedInterval b a -> Maybe (PairedInterval b a) Source # (><) :: PairedInterval b a -> PairedInterval b a -> Maybe (PairedInterval b a) Source # (<+>) :: (Semigroup (f (PairedInterval b a)), Applicative f) => PairedInterval b a -> PairedInterval b a -> f (PairedInterval b a) Source # |
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 (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'.
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'
.
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
.
Takes the difference between two a
to return a b
.