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 Intervallic i where
- getInterval :: i a -> Interval a
- setInterval :: i a -> Interval b -> i b
- newtype ParseErrorInterval = ParseErrorInterval String
- begin :: Intervallic i => i a -> a
- end :: Intervallic i => i a -> a
- 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 b. IntervalSizeable a b => b -> a -> Interval a
- bi :: IntervalSizeable a b => b -> a -> Interval a
- enderval :: forall a b. IntervalSizeable a b => b -> a -> Interval a
- ei :: IntervalSizeable a b => b -> a -> Interval a
- safeInterval :: IntervalSizeable a b => (a, a) -> Interval a
- si :: IntervalSizeable a b => (a, a) -> Interval a
- expand :: forall i a b. (IntervalSizeable a b, Intervallic i) => b -> b -> i a -> i a
- expandl :: (IntervalSizeable a b, Intervallic i) => b -> i a -> i a
- expandr :: (IntervalSizeable a b, Intervallic i) => b -> i a -> i a
- data IntervalRelation
- meets :: (Eq a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- metBy :: (Eq a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- before :: (Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- after :: (Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- overlaps :: (Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- overlappedBy :: (Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- finishedBy :: (Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- finishes :: (Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- contains :: (Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- during :: (Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- starts :: (Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- startedBy :: (Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- equals :: (Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- precedes :: (Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- precededBy :: (Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- disjoint :: (Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- notDisjoint :: (Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- concur :: (Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- within :: (Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- encloses :: (Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a)
- enclosedBy :: (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 :: (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 :: (IntervalSizeable a b, Intervallic i) => b -> i a -> Interval a
- endervalFromBegin :: (IntervalSizeable a b, Intervallic i) => b -> i a -> Interval a
- beginervalMoment :: forall a b. IntervalSizeable a b => a -> Interval a
- endervalMoment :: forall a b. IntervalSizeable a b => a -> Interval a
- shiftFromBegin :: (IntervalSizeable a b, Intervallic i1, Intervallic i0) => i0 a -> i1 a -> i1 b
- shiftFromEnd :: (IntervalSizeable a b, Intervallic i1, Intervallic i0) => i0 a -> i1 a -> i1 b
- momentize :: forall i a b. (IntervalSizeable a b, 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 :: (Ord 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
- class (Ord a, Intervallic i) => IntervalCombinable i a where
- extenterval :: (Ord a, Intervallic i) => i a -> i a -> Interval a
- class (Ord a, Num b, Ord b) => IntervalSizeable a b | a -> b where
- moment :: forall a. b
- duration :: Intervallic i => 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
Intervallic Interval Source # | |
Defined in IntervalAlgebra.Core | |
Ord a => IntervalCombinable Interval a Source # | |
(Ord a, Arbitrary a) => Arbitrary (Interval a) Source # | |
Generic (Interval a) Source # | |
(Show a, Ord a) => Show (Interval a) Source # | |
Binary a => Binary (Interval a) Source # | |
NFData a => NFData (Interval a) Source # | |
Defined in IntervalAlgebra.Core | |
Eq a => Eq (Interval a) Source # | |
Ord a => Ord (Interval a) Source # | Imposes a total ordering on |
type Rep (Interval a) 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. 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 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 # |
newtype ParseErrorInterval Source #
A type identifying interval parsing errors.
Instances
Show ParseErrorInterval Source # | |
Defined in IntervalAlgebra.Core showsPrec :: Int -> ParseErrorInterval -> ShowS # show :: ParseErrorInterval -> String # showList :: [ParseErrorInterval] -> ShowS # | |
Eq ParseErrorInterval Source # | |
Defined in IntervalAlgebra.Core (==) :: ParseErrorInterval -> ParseErrorInterval -> Bool # (/=) :: ParseErrorInterval -> ParseErrorInterval -> Bool # |
begin :: Intervallic i => i a -> a Source #
Access the endpoints of an i a
.
end :: Intervallic i => i a -> a Source #
Access the endpoints of an i a
.
Create new intervals
parseInterval :: (Show a, Ord a) => a -> a -> Either ParseErrorInterval (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 (ParseErrorInterval "0<=1")
prsi :: (Show a, Ord a) => a -> a -> Either ParseErrorInterval (Interval a) Source #
A synonym for parseInterval
:: forall a b. IntervalSizeable a b | |
=> b |
|
-> a | |
-> Interval a |
:: IntervalSizeable a b | |
=> b |
|
-> a | |
-> Interval a |
A synonym for beginerval
:: forall a b. IntervalSizeable a b | |
=> b |
|
-> a | |
-> Interval a |
:: IntervalSizeable a b | |
=> b |
|
-> a | |
-> Interval a |
A synonym for enderval
safeInterval :: IntervalSizeable a b => (a, a) -> Interval a Source #
Safely creates an
from a pair of endpoints.
IMPORTANT: This function uses Interval
beginerval
,
thus if the second element of the pair is <=
the first element,
the duration will be an Interval
of moment
duration.
>>>
safeInterval (4, 5 ::Int)
(4, 5)>>>
safeInterval (4, 3 :: Int)
(4, 5)
si :: IntervalSizeable a b => (a, a) -> Interval a Source #
A synonym for safeInterval
Modify intervals
:: forall i a b. (IntervalSizeable a b, Intervallic i) | |
=> 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.
>>>
iv2to4 = safeInterval (2::Int, 4::Int)
>>>
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 :: (IntervalSizeable a b, Intervallic i) => b -> 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 :: (IntervalSizeable a b, Intervallic i) => b -> 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] ======
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 :: (Eq a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #
metBy :: (Eq a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #
before :: (Ord 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 :: (Ord 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 :: (Ord 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 :: (Ord 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 :: (Ord 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 :: (Ord 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 :: (Ord 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 :: (Ord 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 :: (Ord 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 :: (Ord 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 :: (Ord 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 :: (Ord 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 :: (Ord 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 :: (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 :: (Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #
Does x concur
with y? Is x notDisjoint
with 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 :: (Ord a, Intervallic i0, Intervallic i1) => ComparativePredicateOf2 (i0 a) (i1 a) Source #
Does x concur
with y? Is x notDisjoint
with 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 :: (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 :: (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 :: (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
predicate :: (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.
:: (IntervalSizeable a b, Intervallic i) | |
=> b |
|
-> i a | the |
-> Interval a |
Creates a new Interval from the end
of an i a
.
:: (IntervalSizeable a b, Intervallic i) | |
=> b |
|
-> i a | the |
-> Interval a |
Creates a new Interval from the begin
of an i a
.
beginervalMoment :: forall a b. IntervalSizeable a b => a -> Interval a Source #
endervalMoment :: forall a b. IntervalSizeable a b => a -> Interval a Source #
shiftFromBegin :: (IntervalSizeable a b, Intervallic i1, Intervallic i0) => i0 a -> i1 a -> i1 b 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 :: (IntervalSizeable a b, Intervallic i1, Intervallic i0) => i0 a -> i1 a -> i1 b 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 b. (IntervalSizeable a b, Intervallic i) => i a -> i a Source #
Changes the duration of an Intervallic
value to a moment starting at the
begin
of the interval.
>>>
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 :: (Ord 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
Combine two intervals
class (Ord a, Intervallic i) => 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 #
Deprecated: A specialized function without clear use-cases.
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 :: (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)
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'.
moment :: forall a. b Source #
The smallest duration for an 'Interval a'.
duration :: Intervallic i => 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
.
Instances
IntervalSizeable Day Integer Source # | |
IntervalSizeable UTCTime NominalDiffTime Source # | Note that the |
Defined in IntervalAlgebra.Core moment :: forall a. NominalDiffTime Source # duration :: Intervallic i => i UTCTime -> NominalDiffTime Source # | |
IntervalSizeable Integer Integer Source # | |
IntervalSizeable Int Int Source # | |