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

IntervalAlgebra.PairedInterval

Description

 
Synopsis

Documentation

data PairedInterval b a Source #

An Interval a paired with some other data of type b.

Instances

Instances details
Bifunctor PairedInterval Source # 
Instance details

Defined in IntervalAlgebra.PairedInterval

Methods

bimap :: (a -> b) -> (c -> d) -> PairedInterval a c -> PairedInterval b d #

first :: (a -> b) -> PairedInterval a c -> PairedInterval b c #

second :: (b -> c) -> PairedInterval a b -> PairedInterval a c #

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

Defined in IntervalAlgebra.PairedInterval

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

Defined in IntervalAlgebra.PairedInterval

Methods

relate :: PairedInterval b a -> PairedInterval b a -> IntervalRelation (PairedInterval b a) Source #

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

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

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

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

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

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

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

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

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

equals :: ComparativePredicateOf (PairedInterval b a) Source #

meets :: ComparativePredicateOf (PairedInterval b a) Source #

metBy :: ComparativePredicateOf (PairedInterval b a) Source #

before :: ComparativePredicateOf (PairedInterval b a) Source #

after :: ComparativePredicateOf (PairedInterval b a) Source #

overlaps :: ComparativePredicateOf (PairedInterval b a) Source #

overlappedBy :: ComparativePredicateOf (PairedInterval b a) Source #

starts :: ComparativePredicateOf (PairedInterval b a) Source #

startedBy :: ComparativePredicateOf (PairedInterval b a) Source #

precedes :: ComparativePredicateOf (PairedInterval b a) Source #

precededBy :: ComparativePredicateOf (PairedInterval b a) Source #

finishes :: ComparativePredicateOf (PairedInterval b a) Source #

finishedBy :: ComparativePredicateOf (PairedInterval b a) Source #

during :: ComparativePredicateOf (PairedInterval b a) Source #

contains :: ComparativePredicateOf (PairedInterval b a) Source #

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

(<|>) :: ComparativePredicateOf (PairedInterval b a) -> ComparativePredicateOf (PairedInterval b a) -> ComparativePredicateOf (PairedInterval b a) Source #

disjointRelations :: Set (IntervalRelation (PairedInterval b a)) Source #

withinRelations :: Set (IntervalRelation (PairedInterval b a)) Source #

disjoint :: ComparativePredicateOf (PairedInterval b a) Source #

notDisjoint :: ComparativePredicateOf (PairedInterval b a) Source #

concur :: ComparativePredicateOf (PairedInterval b a) Source #

within :: ComparativePredicateOf (PairedInterval b a) Source #

enclose :: ComparativePredicateOf (PairedInterval b a) Source #

enclosedBy :: ComparativePredicateOf (PairedInterval b a) Source #

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

Defined in IntervalAlgebra.PairedInterval

(Eq a, Eq b) => Eq (PairedInterval b a) Source # 
Instance details

Defined in IntervalAlgebra.PairedInterval

(Eq a, Eq b, Ord a, Show a) => Ord (PairedInterval b a) Source #

Defines A total ordering on 'PairedInterval b a' based on the 'Interval a' part.

Instance details

Defined in IntervalAlgebra.PairedInterval

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

Defined in IntervalAlgebra.PairedInterval

data Empty Source #

Empty is used to trivially lift an Interval a into a PairedInterval.

Instances

Instances details
Eq Empty Source # 
Instance details

Defined in IntervalAlgebra.PairedInterval

Methods

(==) :: Empty -> Empty -> Bool #

(/=) :: Empty -> Empty -> Bool #

Ord Empty Source # 
Instance details

Defined in IntervalAlgebra.PairedInterval

Methods

compare :: Empty -> Empty -> Ordering #

(<) :: Empty -> Empty -> Bool #

(<=) :: Empty -> Empty -> Bool #

(>) :: Empty -> Empty -> Bool #

(>=) :: Empty -> Empty -> Bool #

max :: Empty -> Empty -> Empty #

min :: Empty -> Empty -> Empty #

Show Empty Source # 
Instance details

Defined in IntervalAlgebra.PairedInterval

Methods

showsPrec :: Int -> Empty -> ShowS #

show :: Empty -> String #

showList :: [Empty] -> ShowS #

Semigroup Empty Source # 
Instance details

Defined in IntervalAlgebra.PairedInterval

Methods

(<>) :: Empty -> Empty -> Empty #

sconcat :: NonEmpty Empty -> Empty #

stimes :: Integral b => b -> Empty -> Empty #

Monoid Empty Source # 
Instance details

Defined in IntervalAlgebra.PairedInterval

Methods

mempty :: Empty #

mappend :: Empty -> Empty -> Empty #

mconcat :: [Empty] -> Empty #

mkPairedInterval :: b -> Interval a -> PairedInterval b a Source #

Make a paired interval.

getPairData :: PairedInterval b a -> b Source #

Gets the data (i.e. non-interval) part of a PairedInterval.

intervals :: (Ord a, Show a) => [PairedInterval b a] -> [Interval a] Source #

Gets the intervals from a list of paired intervals.

equalPairData :: Eq b => ComparativePredicateOf (PairedInterval b a) Source #

Tests for equality of the data in a PairedInterval.

toTrivialPair :: Interval a -> PairedInterval Empty a Source #

Lifts an Interval a into a PairedInterval Empty a, where Empty is a trivial type that contains no data.

trivialize :: Functor f => f (Interval a) -> f (PairedInterval Empty a) Source #

Lifts a Functor containing Interval a(s) into a Functor containing PairedInterval Empty a(s).