data-interval-2.1.2: Interval datatype, interval arithmetic and interval-based containers
Copyright(c) Masahiro Sakai 2016
LicenseBSD-style
Maintainermasahiro.sakai@gmail.com
Stabilityprovisional
Portabilitynon-portable (CPP, DeriveDataTypeable, DeriveGeneric)
Safe HaskellSafe
LanguageHaskell2010

Data.IntervalRelation

Description

Interval relations and their algebra.

Synopsis

Documentation

data Relation Source #

Describes how two intervals x and y can be related. See Allen's interval algebra and Intervals and their relations.

Constructors

Before

Any element of x is smaller than any element of y, and intervals are not connected. In other words, there exists an element that is bigger than any element of x and smaller than any element of y.

JustBefore

Any element of x is smaller than any element of y, but intervals are connected and non-empty. This implies that intersection of intervals is empty, and union is a single interval.

Overlaps

Intersection of x and y is non-empty, x start and finishes earlier than y. This implies that union is a single interval, and x finishes no earlier than y starts.

Starts

x is a proper subset of y, and they share lower bounds.

During

x is a proper subset of y, but they share neither lower nor upper bounds.

Finishes

x is a proper subset of y, and they share upper bounds.

Equal

Intervals are equal.

FinishedBy

Inverse of Finishes.

Contains

Inverse of During.

StartedBy

Inverse of Starts.

OverlappedBy

Inverse of Overlaps.

JustAfter

Inverse of JustBefore.

After

Inverse of Before.

Instances

Instances details
Data Relation Source # 
Instance details

Defined in Data.IntervalRelation

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Relation -> c Relation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Relation #

toConstr :: Relation -> Constr #

dataTypeOf :: Relation -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Relation) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Relation) #

gmapT :: (forall b. Data b => b -> b) -> Relation -> Relation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Relation -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Relation -> r #

gmapQ :: (forall d. Data d => d -> u) -> Relation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Relation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Relation -> m Relation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Relation -> m Relation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Relation -> m Relation #

Bounded Relation Source # 
Instance details

Defined in Data.IntervalRelation

Enum Relation Source # 
Instance details

Defined in Data.IntervalRelation

Generic Relation Source # 
Instance details

Defined in Data.IntervalRelation

Associated Types

type Rep Relation :: Type -> Type #

Methods

from :: Relation -> Rep Relation x #

to :: Rep Relation x -> Relation #

Read Relation Source # 
Instance details

Defined in Data.IntervalRelation

Show Relation Source # 
Instance details

Defined in Data.IntervalRelation

Eq Relation Source # 
Instance details

Defined in Data.IntervalRelation

Ord Relation Source # 
Instance details

Defined in Data.IntervalRelation

type Rep Relation Source # 
Instance details

Defined in Data.IntervalRelation

type Rep Relation = D1 ('MetaData "Relation" "Data.IntervalRelation" "data-interval-2.1.2-MIRiQQEkd820wHV9oduNz" 'False) (((C1 ('MetaCons "Before" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "JustBefore" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Overlaps" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Starts" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "During" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Finishes" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Equal" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FinishedBy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Contains" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "StartedBy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverlappedBy" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "JustAfter" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "After" 'PrefixI 'False) (U1 :: Type -> Type)))))

invert :: Relation -> Relation Source #

Inverts a relation, such that invert (relate x y) = relate y x