Copyright | (c) NoviSci Inc 2020-2022 TargetRWE 2023 |
---|---|
License | BSD3 |
Maintainer | bsaul@novisci.com 2020-2022, bbrown@targetrwe.com 2023 |
Safe Haskell | Safe-Inferred |
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 provides an Interval
type wrapping a canonical interval to be used with the
relation algebra defined in the papers cited above.
wraps Interval
a(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
- data Interval a
- class PointedIv iv where
- class PointedIv iv => SizedIv iv where
- class Intervallic i where
- getInterval :: i a -> Interval a
- setInterval :: i a -> Interval b -> i b
- begin :: forall i a. (SizedIv (Interval a), Intervallic i) => i a -> a
- end :: forall i a. (SizedIv (Interval a), Intervallic i) => i a -> a
- newtype ParseErrorInterval = ParseErrorInterval String
- parseInterval :: (Show a, Ord a) => a -> a -> Either ParseErrorInterval (Interval a)
- prsi :: (Show a, Ord a) => a -> a -> Either ParseErrorInterval (Interval a)
- beginerval :: forall a. SizedIv (Interval a) => Moment (Interval a) -> a -> Interval a
- bi :: forall a. SizedIv (Interval a) => Moment (Interval a) -> a -> Interval a
- enderval :: forall a. SizedIv (Interval a) => Moment (Interval a) -> a -> Interval a
- ei :: forall a. SizedIv (Interval a) => Moment (Interval a) -> a -> Interval a
- safeInterval :: forall a. (SizedIv (Interval a), Ord (Moment (Interval a))) => (a, a) -> Interval a
- si :: (SizedIv (Interval a), Ord (Moment (Interval a))) => (a, a) -> Interval a
- expand :: (SizedIv (Interval a), Intervallic i) => Moment (Interval a) -> Moment (Interval a) -> i a -> i a
- expandl :: (SizedIv (Interval a), Intervallic i) => Moment (Interval a) -> i a -> i a
- expandr :: (SizedIv (Interval a), Intervallic i) => Moment (Interval a) -> i a -> i a
- extenterval :: (SizedIv (Interval a), Ord a, Intervallic i) => i a -> i a -> Interval a
- class Iv iv where
- ivRelate :: iv -> iv -> IntervalRelation
- ivBefore, ivAfter :: iv -> iv -> Bool
- ivMeets, ivMetBy :: iv -> iv -> Bool
- ivOverlaps, ivOverlappedBy :: iv -> iv -> Bool
- ivStarts, ivStartedBy :: iv -> iv -> Bool
- ivFinishes, ivFinishedBy :: iv -> iv -> Bool
- ivDuring, ivContains :: iv -> iv -> Bool
- ivEquals :: iv -> iv -> Bool
- data IntervalRelation
- meets :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- metBy :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- before :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- after :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- overlaps :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- overlappedBy :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- finishedBy :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- finishes :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- contains :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- during :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- starts :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- startedBy :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- equals :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- precedes :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- precededBy :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- disjoint :: (SizedIv (Interval a), Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- notDisjoint :: (SizedIv (Interval a), Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- concur :: (SizedIv (Interval a), Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- within :: (SizedIv (Interval a), Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- encloses :: (SizedIv (Interval a), Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- enclosedBy :: (SizedIv (Interval a), Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- (<|>) :: (Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) -> ComparativePredicateOf2 (i0 a) (i1 a) -> ComparativePredicateOf2 (i0 a) (i1 a)
- predicate :: (SizedIv (Interval a), Ord a, Intervallic i0, Intervallic i1) => Set IntervalRelation -> ComparativePredicateOf2 (i0 a) (i1 a)
- unionPredicates :: [ComparativePredicateOf2 a b] -> ComparativePredicateOf2 a b
- disjointRelations :: Set IntervalRelation
- withinRelations :: Set IntervalRelation
- strictWithinRelations :: Set IntervalRelation
- type ComparativePredicateOf1 a = a -> a -> Bool
- type ComparativePredicateOf2 a b = a -> b -> Bool
- beginervalFromEnd :: (SizedIv (Interval a), Intervallic i) => Moment (Interval a) -> i a -> Interval a
- endervalFromBegin :: (SizedIv (Interval a), Intervallic i) => Moment (Interval a) -> i a -> Interval a
- beginervalMoment :: forall a. SizedIv (Interval a) => a -> Interval a
- endervalMoment :: forall a. SizedIv (Interval a) => a -> Interval a
- shiftFromBegin :: (Num a, SizedIv (Interval a), Intervallic i1, Intervallic i0) => i0 a -> i1 a -> i1 a
- shiftFromEnd :: (Num a, SizedIv (Interval a), Intervallic i1, Intervallic i0) => i0 a -> i1 a -> i1 a
- momentize :: forall i a. (SizedIv (Interval a), Intervallic i) => i a -> i a
- toEnumInterval :: (Enum a, Intervallic i) => i Int -> i a
- fromEnumInterval :: (Enum a, Intervallic i) => i a -> i Int
- intervalRelations :: Set IntervalRelation
- relate :: (Iv (Interval a), Intervallic i0, Intervallic i1) => 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
- converseRelation :: IntervalRelation -> IntervalRelation
Canonical 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
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
.
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
then these constructors should return the input.duration
i >= moment
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
. However, it need not be
that Point
(Interval a) = aa ~ 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
is Point
ivOrd
, 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
is Moment
ivNum
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,
need not be the
identity when ivExpandr
d id <
since it will need to ensure the result is a valid interval
even if moment
i
is not.
These two methods can therefore be used as constructors for valid intervals.
The smallest duration for an iv
. When 'Moment iv' is an instance of
Num
, the default is 1. If
is Moment
ivOrd
and Num
,
is required.moment
> 0
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
.
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
SizedIv (Interval Double) Source # | |
Defined in IntervalAlgebra.Core | |
SizedIv (Interval Int) Source # | |
Defined in IntervalAlgebra.Core | |
SizedIv (Interval Integer) Source # | |
Defined in IntervalAlgebra.Core | |
SizedIv (Interval UTCTime) Source # | Note this instance changes the |
Defined in IntervalAlgebra.Core | |
SizedIv (Interval Day) Source # | |
Defined in IntervalAlgebra.Core |
class Intervallic i where Source #
The
typeclass defines how to get and set the Intervallic
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
should define an instance of all four
classes.Interval
PairedInterval
is the prototypical example of an Intervallic
.
>>>
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 b -> i b Source #
Set the interval in an i a
.
Instances
Intervallic Interval Source # | |
Defined in IntervalAlgebra.Core | |
Intervallic IntervalText Source # | |
Defined in IntervalAlgebra.IntervalDiagram getInterval :: IntervalText a -> Interval a Source # setInterval :: IntervalText a -> Interval b -> IntervalText b Source # | |
Intervallic (PairedInterval b) Source # | |
Defined in IntervalAlgebra.PairedInterval getInterval :: PairedInterval b a -> Interval a Source # setInterval :: PairedInterval b a -> Interval b0 -> PairedInterval b b0 Source # |
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.
Instances
Eq ParseErrorInterval Source # | |
Defined in IntervalAlgebra.Core (==) :: ParseErrorInterval -> ParseErrorInterval -> Bool # (/=) :: ParseErrorInterval -> ParseErrorInterval -> Bool # | |
Show ParseErrorInterval Source # | |
Defined in IntervalAlgebra.Core showsPrec :: Int -> ParseErrorInterval -> ShowS # show :: ParseErrorInterval -> String # showList :: [ParseErrorInterval] -> ShowS # |
parseInterval :: (Show a, Ord a) => a -> a -> Either ParseErrorInterval (Interval a) Source #
prsi :: (Show a, Ord a) => a -> a -> Either ParseErrorInterval (Interval a) Source #
A synonym for parseInterval
:: forall a. SizedIv (Interval a) | |
=> Moment (Interval a) |
|
-> a | |
-> Interval a |
Safely creates an 'Interval a' using x
as the begin
and adding max
to moment
durx
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)
:: forall a. SizedIv (Interval a) | |
=> Moment (Interval a) |
|
-> a | |
-> Interval a |
A synonym for beginerval
:: forall a. SizedIv (Interval a) | |
=> Moment (Interval a) |
|
-> a | |
-> Interval a |
A synonym for enderval
safeInterval :: forall a. (SizedIv (Interval a), Ord (Moment (Interval a))) => (a, a) -> Interval a Source #
si :: (SizedIv (Interval a), Ord (Moment (Interval a))) => (a, a) -> Interval a Source #
A synonym for safeInterval
Modify intervals within an Intervallic
:: (SizedIv (Interval a), Intervallic i) | |
=> Moment (Interval a) | duration to subtract from the |
-> Moment (Interval a) | 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.
>>>
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
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
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) :}
ivRelate :: iv -> iv -> IntervalRelation Source #
The IntervalRelation
between two intervals.
:: iv |
|
-> iv |
|
-> Bool |
:: iv |
|
-> iv |
|
-> Bool |
:: iv |
|
-> iv |
|
-> Bool |
:: iv |
|
-> iv |
|
-> Bool |
:: iv |
|
-> iv |
|
-> Bool |
Is
? ivRelate
x y == Overlaps
.ivOverlappedBy
= flip ivOverlaps
:: iv |
|
-> iv |
|
-> Bool |
Is
? ivRelate
x y == Overlaps
.ivOverlappedBy
= flip ivOverlaps
:: iv |
|
-> iv |
|
-> Bool |
Is
? ivRelate
x y == Starts
.ivStartedBy
= flip ivStarts
:: iv |
|
-> iv |
|
-> Bool |
Is
? ivRelate
x y == Starts
.ivStartedBy
= flip ivStarts
:: iv |
|
-> iv |
|
-> Bool |
Is
? ivRelate
x y == Finishes
.ivFinishedBy
= flip ivFinishes
:: iv |
|
-> iv |
|
-> Bool |
Is
? ivRelate
x y == Finishes
.ivFinishedBy
= flip ivFinishes
:: iv |
|
-> iv |
|
-> Bool |
Is
? ivRelate
x y == During
.ivContains
= flip ivDuring
:: iv |
|
-> iv |
|
-> Bool |
Is
? ivRelate
x y == During
.ivContains
= flip ivDuring
:: iv |
|
-> iv |
|
-> Bool |
Is
?ivRelate
x y == Equals
Instances
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. |
Defined in IntervalAlgebra.Core ivRelate :: Interval a -> Interval a -> IntervalRelation Source # ivBefore :: Interval a -> Interval a -> Bool Source # ivAfter :: Interval a -> Interval a -> Bool Source # ivMeets :: Interval a -> Interval a -> Bool Source # ivMetBy :: Interval a -> Interval a -> Bool Source # ivOverlaps :: Interval a -> Interval a -> Bool Source # ivOverlappedBy :: Interval a -> Interval a -> Bool Source # ivStarts :: Interval a -> Interval a -> Bool Source # ivStartedBy :: Interval a -> Interval a -> Bool Source # ivFinishes :: Interval a -> Interval a -> Bool Source # ivFinishedBy :: Interval a -> Interval a -> Bool Source # ivDuring :: Interval a -> Interval a -> Bool Source # |
Interval Relations and Predicates
data IntervalRelation Source #
The IntervalRelation
type and the associated predicate functions enumerate
the thirteen possible ways that two
objects may SizedIv
relate
according to Allen's interval algebra. Constructors are shown with their
corresponding predicate function.
Instances
meets :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #
metBy :: (Iv (Interval a), Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #
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
, meaning concur
yx
and y
share some support? Is x
? This is
the notDisjoint
ycomplement
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
, meaning concur
yx
and y
share some support? Is x
? This is
the notDisjoint
ycomplement
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 IntervalRelation
s.
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.
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.
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
intervalRelations :: Set IntervalRelation Source #
The Set
of all IntervalRelation
s.
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.
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
converseRelation :: IntervalRelation -> IntervalRelation Source #
Find the converse of a single IntervalRelation