interval-patterns-0.6.0.1: Intervals, and monoids thereof
Copyright(c) Melanie Brown 2022
License: BSD3 (see the file LICENSE)
Safe HaskellNone
LanguageHaskell2010

Data.Interval

Description

Intervals over types and their operations.

Synopsis

Documentation

data Extremum Source #

The kinds of extremum an interval can have.

Constructors

Minimum 
Infimum 
Supremum 
Maximum 

Instances

Instances details
Data Extremum Source # 
Instance details

Defined in Data.Interval

Methods

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

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

toConstr :: Extremum -> Constr #

dataTypeOf :: Extremum -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded Extremum Source # 
Instance details

Defined in Data.Interval

Enum Extremum Source # 
Instance details

Defined in Data.Interval

Generic Extremum Source # 
Instance details

Defined in Data.Interval

Associated Types

type Rep Extremum :: Type -> Type #

Methods

from :: Extremum -> Rep Extremum x #

to :: Rep Extremum x -> Extremum #

Read Extremum Source # 
Instance details

Defined in Data.Interval

Show Extremum Source # 
Instance details

Defined in Data.Interval

Eq Extremum Source # 
Instance details

Defined in Data.Interval

Ord Extremum Source # 
Instance details

Defined in Data.Interval

type Rep Extremum Source # 
Instance details

Defined in Data.Interval

type Rep Extremum = D1 ('MetaData "Extremum" "Data.Interval" "interval-patterns-0.6.0.1-AWVGvVImLF665RHNyYdFZ" 'False) ((C1 ('MetaCons "Minimum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Infimum" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Supremum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Maximum" 'PrefixI 'False) (U1 :: Type -> Type)))

opposite :: Extremum -> Extremum Source #

The opposite of an Extremum is its complementary analogue: how the same point would be viewed from the complement of the interval to which it belongs.

c.f. opposeBound.

data Bound ext x where Source #

A Bound is an endpoint of an Interval.

Constructors

Min :: !x -> Bound Minimum x 
Inf :: !x -> Bound Infimum x 
Sup :: !x -> Bound Supremum x 
Max :: !x -> Bound Maximum x 

Instances

Instances details
Foldable (Bound ext) Source # 
Instance details

Defined in Data.Interval

Methods

fold :: Monoid m => Bound ext m -> m #

foldMap :: Monoid m => (a -> m) -> Bound ext a -> m #

foldMap' :: Monoid m => (a -> m) -> Bound ext a -> m #

foldr :: (a -> b -> b) -> b -> Bound ext a -> b #

foldr' :: (a -> b -> b) -> b -> Bound ext a -> b #

foldl :: (b -> a -> b) -> b -> Bound ext a -> b #

foldl' :: (b -> a -> b) -> b -> Bound ext a -> b #

foldr1 :: (a -> a -> a) -> Bound ext a -> a #

foldl1 :: (a -> a -> a) -> Bound ext a -> a #

toList :: Bound ext a -> [a] #

null :: Bound ext a -> Bool #

length :: Bound ext a -> Int #

elem :: Eq a => a -> Bound ext a -> Bool #

maximum :: Ord a => Bound ext a -> a #

minimum :: Ord a => Bound ext a -> a #

sum :: Num a => Bound ext a -> a #

product :: Num a => Bound ext a -> a #

Traversable (Bound ext) Source # 
Instance details

Defined in Data.Interval

Methods

traverse :: Applicative f => (a -> f b) -> Bound ext a -> f (Bound ext b) #

sequenceA :: Applicative f => Bound ext (f a) -> f (Bound ext a) #

mapM :: Monad m => (a -> m b) -> Bound ext a -> m (Bound ext b) #

sequence :: Monad m => Bound ext (m a) -> m (Bound ext a) #

Functor (Bound ext) Source # 
Instance details

Defined in Data.Interval

Methods

fmap :: (a -> b) -> Bound ext a -> Bound ext b #

(<$) :: a -> Bound ext b -> Bound ext a #

Eq x => Eq (Bound ext x) Source # 
Instance details

Defined in Data.Interval

Methods

(==) :: Bound ext x -> Bound ext x -> Bool #

(/=) :: Bound ext x -> Bound ext x -> Bool #

Ord x => Ord (Bound ext (Levitated x)) Source # 
Instance details

Defined in Data.Interval

Methods

compare :: Bound ext (Levitated x) -> Bound ext (Levitated x) -> Ordering #

(<) :: Bound ext (Levitated x) -> Bound ext (Levitated x) -> Bool #

(<=) :: Bound ext (Levitated x) -> Bound ext (Levitated x) -> Bool #

(>) :: Bound ext (Levitated x) -> Bound ext (Levitated x) -> Bool #

(>=) :: Bound ext (Levitated x) -> Bound ext (Levitated x) -> Bool #

max :: Bound ext (Levitated x) -> Bound ext (Levitated x) -> Bound ext (Levitated x) #

min :: Bound ext (Levitated x) -> Bound ext (Levitated x) -> Bound ext (Levitated x) #

unBound :: Bound ext x -> x Source #

Extract the term from a Bound.

class Opposite (Opposite ext) ~ ext => Bounding ext where Source #

A type class for inverting Bounds.

Associated Types

type Opposite ext :: Extremum Source #

Methods

bound :: x -> Bound ext x Source #

opposeBound :: Bound ext x -> Bound (Opposite ext) x Source #

c.f. opposite.

Instances

Instances details
Bounding 'Infimum Source # 
Instance details

Defined in Data.Interval

Associated Types

type Opposite 'Infimum :: Extremum Source #

Bounding 'Maximum Source # 
Instance details

Defined in Data.Interval

Associated Types

type Opposite 'Maximum :: Extremum Source #

Bounding 'Minimum Source # 
Instance details

Defined in Data.Interval

Associated Types

type Opposite 'Minimum :: Extremum Source #

Bounding 'Supremum Source # 
Instance details

Defined in Data.Interval

Associated Types

type Opposite 'Supremum :: Extremum Source #

compareBounds :: Ord x => Bound ext1 x -> Bound ext2 x -> Ordering Source #

Bounds have special comparison rules for identical points.

>>> compareBounds (Min (Levitate 5)) (Max (Levitate 5))
EQ
>>> compareBounds (Inf (Levitate 5)) (Sup (Levitate 5))
GT
>>> compareBounds (Max (Levitate 5)) (Sup (Levitate 5))
GT
>>> compareBounds (Inf (Levitate 5)) (Min (Levitate 5))
GT
>>> compareBounds (Max (Levitate 5)) (Inf (Levitate 5))
LT

data SomeBound x Source #

Constructors

forall ext.(Bounding ext, Bounding (Opposite ext)) => SomeBound !(Bound ext x) 

Instances

Instances details
Eq x => Eq (SomeBound (Levitated x)) Source # 
Instance details

Defined in Data.Interval

Ord x => Ord (SomeBound (Levitated x)) Source # 
Instance details

Defined in Data.Interval

data Interval x where Source #

Constructors

(:<-->:) :: Ord x => !(Bound Infimum (Levitated x)) -> !(Bound Supremum (Levitated x)) -> Interval x infix 5 
(:<--|:) :: Ord x => !(Bound Infimum (Levitated x)) -> !(Bound Maximum (Levitated x)) -> Interval x infix 5 
(:|-->:) :: Ord x => !(Bound Minimum (Levitated x)) -> !(Bound Supremum (Levitated x)) -> Interval x infix 5 
(:|--|:) :: Ord x => !(Bound Minimum (Levitated x)) -> !(Bound Maximum (Levitated x)) -> Interval x infix 5 

Instances

Instances details
(Ord x, Data x) => Data (Interval x) Source # 
Instance details

Defined in Data.Interval

Methods

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

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

toConstr :: Interval x -> Constr #

dataTypeOf :: Interval x -> DataType #

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

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

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

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

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

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

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

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

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

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

(Ord x, Generic x) => Generic (Interval x) Source # 
Instance details

Defined in Data.Interval

Associated Types

type Rep (Interval x) :: Type -> Type #

Methods

from :: Interval x -> Rep (Interval x) x0 #

to :: Rep (Interval x) x0 -> Interval x #

(Ord x, Show x) => Show (Interval x) Source # 
Instance details

Defined in Data.Interval

Methods

showsPrec :: Int -> Interval x -> ShowS #

show :: Interval x -> String #

showList :: [Interval x] -> ShowS #

Ord x => Eq (Interval x) Source # 
Instance details

Defined in Data.Interval

Methods

(==) :: Interval x -> Interval x -> Bool #

(/=) :: Interval x -> Interval x -> Bool #

Ord x => Ord (Interval x) Source # 
Instance details

Defined in Data.Interval

Methods

compare :: Interval x -> Interval x -> Ordering #

(<) :: Interval x -> Interval x -> Bool #

(<=) :: Interval x -> Interval x -> Bool #

(>) :: Interval x -> Interval x -> Bool #

(>=) :: Interval x -> Interval x -> Bool #

max :: Interval x -> Interval x -> Interval x #

min :: Interval x -> Interval x -> Interval x #

type Rep (Interval x) Source # 
Instance details

Defined in Data.Interval

imap :: (Ord x, Ord y) => (x -> y) -> Interval x -> Interval y Source #

Since the Ord constraints on the constructors for Interval prevent it from being a Functor, this will have to suffice.

imapLev :: (Ord x, Ord y) => (Levitated x -> Levitated y) -> Interval x -> Interval y Source #

Same as imap but on the Levitated of the underlying type.

itraverse :: (Ord x, Ord y, Applicative f) => (x -> f y) -> Interval x -> f (Interval y) Source #

Since the Ord constraints on the constructors for Interval prevent it from being Traversable, this will have to suffice.

itraverseLev :: (Ord x, Ord y, Applicative f) => (Levitated x -> f (Levitated y)) -> Interval x -> f (Interval y) Source #

Same as itraverse but on the Levitated of the underlying type.

pattern (:<->:) :: Ord x => Levitated x -> Levitated x -> Interval x infix 5 Source #

A bidirectional pattern synonym matching open intervals.

pattern (:<-|:) :: Ord x => Levitated x -> Levitated x -> Interval x infix 5 Source #

A bidirectional pattern synonym matching open-closed intervals.

pattern (:|->:) :: Ord x => Levitated x -> Levitated x -> Interval x infix 5 Source #

A bidirectional pattern synonym matching closed-open intervals.

pattern (:|-|:) :: Ord x => Levitated x -> Levitated x -> Interval x infix 5 Source #

A bidirectional pattern synonym matching closed intervals.

pattern (:---:) :: forall x. Ord x => Levitated x -> Levitated x -> Interval x Source #

A unidirectional pattern synonym ignoring the particular Bounds.

pattern (:<>:) :: forall x. Ord x => x -> x -> Interval x infix 5 Source #

A bidirectional pattern synonym matching finite open intervals.

pattern (:<|:) :: forall x. Ord x => x -> x -> Interval x infix 5 Source #

A bidirectional pattern synonym matching finite open-closed intervals.

pattern (:|>:) :: forall x. Ord x => x -> x -> Interval x infix 5 Source #

A bidirectional pattern synonym matching finite closed-open intervals.

pattern (:||:) :: forall x. Ord x => x -> x -> Interval x infix 5 Source #

A bidirectional pattern synonym matching finite closed intervals.

pattern (:--:) :: forall x. Ord x => x -> x -> Interval x Source #

A unidirectional pattern synonym matching finite intervals, that ignores the particular Bounds.

pattern Whole :: Ord x => Interval x Source #

The whole interval.

(+/-) :: (Ord x, Num x) => x -> x -> Interval x Source #

m +/- r creates the closed interval centred at m with radius r.

For the open interval, simply write open (x +/- y).

(...) :: Ord x => (Levitated x, Extremum) -> (Levitated x, Extremum) -> Interval x Source #

Given limits and Extremums, try to make an interval.

bounds :: Interval x -> (SomeBound (Levitated x), SomeBound (Levitated x)) Source #

Get the (lower, upper) bounds of an Interval.

c.f. lower, upper.

lower :: Ord x => Interval x -> SomeBound (Levitated x) Source #

Get the lower bound of an interval.

lower = fst . bounds

lowerBound :: Ord x => Interval x -> (Levitated x, Extremum) Source #

Get the lower bound of an interval (with the bound expressed at the term level).

upper :: Ord x => Interval x -> SomeBound (Levitated x) Source #

Get the upper bound of an interval.

upper = snd . bounds

upperBound :: Ord x => Interval x -> (Levitated x, Extremum) Source #

Get the upper bound of an interval (with the bound expressed at the term level).

interval :: Ord x => SomeBound (Levitated x) -> SomeBound (Levitated x) -> Interval x Source #

Given SomeBounds, try to make an interval.

imin :: Ord x => Interval x -> Maybe (Levitated x) Source #

Get the minimum of an interval, if it exists.

iinf :: Ord x => Interval x -> Levitated x Source #

Get the infimum of an interval, weakening if necessary.

isup :: Ord x => Interval x -> Levitated x Source #

Get the supremum of an interval, weakening if necessary.

imax :: Ord x => Interval x -> Maybe (Levitated x) Source #

Get the maximum of an interval if it exists.

hull :: Ord x => Interval x -> Interval x -> Interval x Source #

Get the convex hull of two intervals.

>>> hull (7 :|>: 8) (3 :|>: 4)
(3 :|>: 8)
>>> hull (Bottom :<-|: Levitate 3) (4 :<>: 5)
(Bottom :<->: Levitate 5)

hulls :: Ord x => NonEmpty (Interval x) -> Interval x Source #

Get the convex hull of a non-empty list of intervals.

within :: Ord x => x -> Interval x -> Bool Source #

Test whether a point is contained in the interval.

point :: Ord x => x -> Interval x Source #

Create the closed-closed interval at a given point.

open :: Ord x => Interval x -> Interval x Source #

Open both bounds of the given interval.

close :: Ord x => Interval x -> Interval x Source #

Close both bounds of the given interval.

openclosed :: Ord x => Interval x -> Interval x Source #

Make the interval open-closed, leaving the endpoints unchanged.

closedopen :: Ord x => Interval x -> Interval x Source #

Make the interval closed-open, leaving the endpoints unchanged.

openLower :: Ord x => Interval x -> Interval x Source #

Make the lower bound open, leaving the endpoints unchanged.

closedLower :: Ord x => Interval x -> Interval x Source #

Make the lower bound closed, leaving the endpoints unchanged.

openUpper :: Ord x => Interval x -> Interval x Source #

Make the upper bound open, leaving the endpoints unchanged.

closedUpper :: Ord x => Interval x -> Interval x Source #

Make the upper bound closed, leaving the endpoints unchanged.

data Adjacency x Source #

According to Allen, two intervals can be "adjacent" in 13 different ways, into at most 3 distinct intervals. In this package, this quality is called the Adjacency of the intervals.

Instances

Instances details
(Data x, Ord x) => Data (Adjacency x) Source # 
Instance details

Defined in Data.Interval

Methods

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

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

toConstr :: Adjacency x -> Constr #

dataTypeOf :: Adjacency x -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (Adjacency x) Source # 
Instance details

Defined in Data.Interval

Associated Types

type Rep (Adjacency x) :: Type -> Type #

Methods

from :: Adjacency x -> Rep (Adjacency x) x0 #

to :: Rep (Adjacency x) x0 -> Adjacency x #

(Ord x, Show x) => Show (Adjacency x) Source # 
Instance details

Defined in Data.Interval

Ord x => Eq (Adjacency x) Source # 
Instance details

Defined in Data.Interval

Methods

(==) :: Adjacency x -> Adjacency x -> Bool #

(/=) :: Adjacency x -> Adjacency x -> Bool #

Ord x => Ord (Adjacency x) Source # 
Instance details

Defined in Data.Interval

type Rep (Adjacency x) Source # 
Instance details

Defined in Data.Interval

type Rep (Adjacency x) = D1 ('MetaData "Adjacency" "Data.Interval" "interval-patterns-0.6.0.1-AWVGvVImLF665RHNyYdFZ" 'False) (((C1 ('MetaCons "Before" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x))) :+: (C1 ('MetaCons "Meets" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)))) :+: C1 ('MetaCons "Overlaps" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)))))) :+: (C1 ('MetaCons "Starts" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x))) :+: (C1 ('MetaCons "During" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)))) :+: C1 ('MetaCons "Finishes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)))))) :+: ((C1 ('MetaCons "Identical" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x))) :+: (C1 ('MetaCons "FinishedBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x))) :+: C1 ('MetaCons "Contains" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)))))) :+: ((C1 ('MetaCons "StartedBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x))) :+: C1 ('MetaCons "OverlappedBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x))))) :+: (C1 ('MetaCons "MetBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)))) :+: C1 ('MetaCons "After" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Interval x)))))))

converseAdjacency :: Adjacency x -> Adjacency x Source #

The result of having compared the same two intervals in reverse order.

adjacency :: Ord x => Interval x -> Interval x -> Adjacency x Source #

Calculate the Adjacency between two intervals, according to Allen.

intersect :: forall x. Ord x => Interval x -> Interval x -> Maybe (Interval x) Source #

Calculate the intersection of two intervals, if it exists.

>>> intersect (2 :<>: 4) (3 :||: 5)
Just (3 :|>: 4)

>>> intersect (2 :<>: 4) (4 :||: 5)
Nothing

>>> intersect (1 :<>: 4) (2 :||: 3)
Just (2 :||: 3)

union :: forall x. Ord x => Interval x -> Interval x -> OneOrTwo (Interval x) Source #

Get the union of two intervals, as either OneOrTwo.

>>> union (2 :||: 5) (5 :<>: 7)
One (Levitate 2 :|->: Levitate 7)

>>> union (2 :||: 4) (5 :<>: 7)
Two (Levitate 2 :|-|: Levitate 4) (Levitate 5 :-: Levitate 7)

unions :: forall x. Ord x => [Interval x] -> [Interval x] Source #

O(n log n). Get the union of a list of intervals.

This function uses sort. See also unionsAsc.

unionsAsc :: forall x. Ord x => [Interval x] -> [Interval x] Source #

O(n). Get the union of a sorted list of intervals.

NOTE: The input condition is not checked. Use with care.

complement :: forall x. Ord x => Interval x -> Maybe (OneOrTwo (Interval x)) Source #

Take the complement of the interval, as possibly OneOrTwo.

>>> complement (3 :<>: 4)
Just (Two (Bottom :|-|: Levitate 3) (Levitate 4 :|-|: Top))

Note that infinitely-open intervals will return the points at infinity toward which they are infinite in their result:

>>> complement (Levitate 3 :-: Top)
Just (Two (Bottom :|-|: Levitate 3) (Top :|-|: Top))

difference :: forall x. Ord x => Interval x -> Interval x -> Maybe (OneOrTwo (Interval x)) Source #

Remove all points of the second interval from the first.

>>> difference Whole (3 :<>: 4)
Just (Two (Bottom :|-|: Levitate 3) (Levitate 4 :|-|: Top))

>>> difference (1 :<>: 4) (2 :||: 3)
Just (Two (1 :<>: 2) (3 :<>: 4))

>>> difference (1 :|>: 4) (0 :||: 1)
Just (One (1 :<>: 4))

>>> difference (1 :<>: 4) (0 :||: 1)
Just (One (1 :<>: 4))

(\\) :: forall x. Ord x => Interval x -> Interval x -> Maybe (OneOrTwo (Interval x)) Source #

Infix synonym for difference

symmetricDifference :: forall x. Ord x => Interval x -> Interval x -> Maybe (OneOrTwo (Interval x)) Source #

The difference of the union and intersection of two intervals.

>>> symmetricDifference Whole (3 :<>: 4)
Just (Two (Bottom :|-|: Levitate 3) (Levitate 4 :|-|: Top))

>>> symmetricDifference (1 :<>: 4) (2 :||: 3)
Just (Two (1 :<>: 2) (3 :<>: 4))

measure :: forall x. (Ord x, Num x) => Interval x -> Maybe x Source #

Get the measure of an interval.

>>> measure (-1 :<>: 1)
Just 2

>>> measure (Bottom :-: Levitate 1)
Nothing

measuring :: forall y x. (Ord x, Num y) => (x -> x -> y) -> Interval x -> Maybe y Source #

Apply a function to the lower, then upper, endpoint of an interval.

>>> measuring max (-1 :<>: 1)
Just 1

>>> measuring min (-1 :<>: 1)
Just (-1)

>>> measuring (*) (4 :<>: 6)
Just 24

hausdorff :: (Ord x, Num x) => Interval x -> Interval x -> Maybe x Source #

Get the distance between two intervals, or 0 if they adjacency.

>>> hausdorff (3 :<>: 5) (6 :<>: 7)
Just 1

>>> hausdorff (3 :<>: 5) Whole
Just 0

isSubsetOf :: Ord x => Interval x -> Interval x -> Bool Source #

Full containment.

data OneOrTwo x Source #

Either one of something, or two of it.

Use oneOrTwo to deconstruct.

Constructors

One !x 
Two !x !x 

Instances

Instances details
Foldable OneOrTwo Source # 
Instance details

Defined in Data.OneOrTwo

Methods

fold :: Monoid m => OneOrTwo m -> m #

foldMap :: Monoid m => (a -> m) -> OneOrTwo a -> m #

foldMap' :: Monoid m => (a -> m) -> OneOrTwo a -> m #

foldr :: (a -> b -> b) -> b -> OneOrTwo a -> b #

foldr' :: (a -> b -> b) -> b -> OneOrTwo a -> b #

foldl :: (b -> a -> b) -> b -> OneOrTwo a -> b #

foldl' :: (b -> a -> b) -> b -> OneOrTwo a -> b #

foldr1 :: (a -> a -> a) -> OneOrTwo a -> a #

foldl1 :: (a -> a -> a) -> OneOrTwo a -> a #

toList :: OneOrTwo a -> [a] #

null :: OneOrTwo a -> Bool #

length :: OneOrTwo a -> Int #

elem :: Eq a => a -> OneOrTwo a -> Bool #

maximum :: Ord a => OneOrTwo a -> a #

minimum :: Ord a => OneOrTwo a -> a #

sum :: Num a => OneOrTwo a -> a #

product :: Num a => OneOrTwo a -> a #

Traversable OneOrTwo Source # 
Instance details

Defined in Data.OneOrTwo

Methods

traverse :: Applicative f => (a -> f b) -> OneOrTwo a -> f (OneOrTwo b) #

sequenceA :: Applicative f => OneOrTwo (f a) -> f (OneOrTwo a) #

mapM :: Monad m => (a -> m b) -> OneOrTwo a -> m (OneOrTwo b) #

sequence :: Monad m => OneOrTwo (m a) -> m (OneOrTwo a) #

Functor OneOrTwo Source # 
Instance details

Defined in Data.OneOrTwo

Methods

fmap :: (a -> b) -> OneOrTwo a -> OneOrTwo b #

(<$) :: a -> OneOrTwo b -> OneOrTwo a #

Data x => Data (OneOrTwo x) Source # 
Instance details

Defined in Data.OneOrTwo

Methods

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

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

toConstr :: OneOrTwo x -> Constr #

dataTypeOf :: OneOrTwo x -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (OneOrTwo x) Source # 
Instance details

Defined in Data.OneOrTwo

Associated Types

type Rep (OneOrTwo x) :: Type -> Type #

Methods

from :: OneOrTwo x -> Rep (OneOrTwo x) x0 #

to :: Rep (OneOrTwo x) x0 -> OneOrTwo x #

Read x => Read (OneOrTwo x) Source # 
Instance details

Defined in Data.OneOrTwo

Show x => Show (OneOrTwo x) Source # 
Instance details

Defined in Data.OneOrTwo

Methods

showsPrec :: Int -> OneOrTwo x -> ShowS #

show :: OneOrTwo x -> String #

showList :: [OneOrTwo x] -> ShowS #

Eq x => Eq (OneOrTwo x) Source # 
Instance details

Defined in Data.OneOrTwo

Methods

(==) :: OneOrTwo x -> OneOrTwo x -> Bool #

(/=) :: OneOrTwo x -> OneOrTwo x -> Bool #

Ord x => Ord (OneOrTwo x) Source # 
Instance details

Defined in Data.OneOrTwo

Methods

compare :: OneOrTwo x -> OneOrTwo x -> Ordering #

(<) :: OneOrTwo x -> OneOrTwo x -> Bool #

(<=) :: OneOrTwo x -> OneOrTwo x -> Bool #

(>) :: OneOrTwo x -> OneOrTwo x -> Bool #

(>=) :: OneOrTwo x -> OneOrTwo x -> Bool #

max :: OneOrTwo x -> OneOrTwo x -> OneOrTwo x #

min :: OneOrTwo x -> OneOrTwo x -> OneOrTwo x #

type Rep (OneOrTwo x) Source # 
Instance details

Defined in Data.OneOrTwo

type Rep (OneOrTwo x) = D1 ('MetaData "OneOrTwo" "Data.OneOrTwo" "interval-patterns-0.6.0.1-AWVGvVImLF665RHNyYdFZ" 'False) (C1 ('MetaCons "One" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 x)) :+: C1 ('MetaCons "Two" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 x) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 x)))