interval-1.20160821: Intervals with adherences.

Safe HaskellSafe
LanguageHaskell98

Data.Interval

Contents

Synopsis

Type Limit

data Limit x Source #

Constructors

Limit 

Fields

Instances

Functor Limit Source # 

Methods

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

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

Bounded (Limit (Unlimitable x)) Source # 
Eq x => Eq (Limit x) Source # 

Methods

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

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

Data x => Data (Limit x) Source # 

Methods

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

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

toConstr :: Limit x -> Constr #

dataTypeOf :: Limit x -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord x => Ord (HH (Limit x)) Source # 

Methods

compare :: HH (Limit x) -> HH (Limit x) -> Ordering #

(<) :: HH (Limit x) -> HH (Limit x) -> Bool #

(<=) :: HH (Limit x) -> HH (Limit x) -> Bool #

(>) :: HH (Limit x) -> HH (Limit x) -> Bool #

(>=) :: HH (Limit x) -> HH (Limit x) -> Bool #

max :: HH (Limit x) -> HH (Limit x) -> HH (Limit x) #

min :: HH (Limit x) -> HH (Limit x) -> HH (Limit x) #

Ord x => Ord (LL (Limit x)) Source # 

Methods

compare :: LL (Limit x) -> LL (Limit x) -> Ordering #

(<) :: LL (Limit x) -> LL (Limit x) -> Bool #

(<=) :: LL (Limit x) -> LL (Limit x) -> Bool #

(>) :: LL (Limit x) -> LL (Limit x) -> Bool #

(>=) :: LL (Limit x) -> LL (Limit x) -> Bool #

max :: LL (Limit x) -> LL (Limit x) -> LL (Limit x) #

min :: LL (Limit x) -> LL (Limit x) -> LL (Limit x) #

Show x => Show (Limit x) Source # 

Methods

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

show :: Limit x -> String #

showList :: [Limit x] -> ShowS #

NFData x => NFData (Limit x) Source # 

Methods

rnf :: Limit x -> () #

data Adherence Source #

Constructors

Out 
In 

Instances

Eq Adherence Source # 
Data Adherence Source # 

Methods

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

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

toConstr :: Adherence -> Constr #

dataTypeOf :: Adherence -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Adherence Source # 

flip_limit :: Limit x -> Limit x Source #

Return given Limit with its adherence set to the opposite one.

Comparing Limits

newtype LL x Source #

Compare two low Limits.

Constructors

LL 

Fields

Instances

Eq x => Eq (LL x) Source # 

Methods

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

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

Ord x => Ord (LL (Limit x)) Source # 

Methods

compare :: LL (Limit x) -> LL (Limit x) -> Ordering #

(<) :: LL (Limit x) -> LL (Limit x) -> Bool #

(<=) :: LL (Limit x) -> LL (Limit x) -> Bool #

(>) :: LL (Limit x) -> LL (Limit x) -> Bool #

(>=) :: LL (Limit x) -> LL (Limit x) -> Bool #

max :: LL (Limit x) -> LL (Limit x) -> LL (Limit x) #

min :: LL (Limit x) -> LL (Limit x) -> LL (Limit x) #

newtype HH x Source #

Compare two high Limits.

Constructors

HH 

Fields

Instances

Eq x => Eq (HH x) Source # 

Methods

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

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

Ord x => Ord (HH (Limit x)) Source # 

Methods

compare :: HH (Limit x) -> HH (Limit x) -> Ordering #

(<) :: HH (Limit x) -> HH (Limit x) -> Bool #

(<=) :: HH (Limit x) -> HH (Limit x) -> Bool #

(>) :: HH (Limit x) -> HH (Limit x) -> Bool #

(>=) :: HH (Limit x) -> HH (Limit x) -> Bool #

max :: HH (Limit x) -> HH (Limit x) -> HH (Limit x) #

min :: HH (Limit x) -> HH (Limit x) -> HH (Limit x) #

Type Interval

newtype Ord x => Interval x Source #

Constructors

Interval (Limit x, Limit x) 

Instances

Eq x => Eq (Interval x) Source # 

Methods

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

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

(Data x, Ord x) => Data (Interval x) Source # 

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 :: (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 => Ord (Interval x) Source #

Lexicographical order, handling Adherence correctly.

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 #

(Ord x, Show x) => Show (Pretty (Interval x)) Source # 
(Ord x, Show x) => Show (Interval x) Source # 

Methods

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

show :: Interval x -> String #

showList :: [Interval x] -> ShowS #

(NFData x, Ord x) => NFData (Interval x) Source # 

Methods

rnf :: Interval x -> () #

low :: Ord x => Interval x -> Limit x Source #

high :: Ord x => Interval x -> Limit x Source #

interval :: Ord x => Limit x -> Limit x -> Maybe (Interval x) Source #

Return Interval with given low then high Limits, if they form a valid Interval.

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

Like fmap, but may return Nothing, if mapped Interval is not valid.

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

Like fmap, but only safe if given map preserves Ordering.

limits :: Ord x => Interval x -> (Limit x, Limit x) Source #

Return limits of given Interval as a tuple.

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

Return an Interval spanning over a single limit.

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

Return given Interval with flip_limit applied to its limits.

compare_without_adherence :: Ord x => Limit x -> Limit x -> Ordering Source #

Return Ordering comparing given Intervals according to their limits.

locate :: Ord x => x -> Interval x -> Ordering Source #

Return:

  • LT: if given value is lower than all values in given Interval.
  • EQ: if given value is into the given Interval.
  • GT: if given value is higher than all values in given Interval.

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

Return True iif. given value is into the given Interval.

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

Return True iif. every value of the first Interval is into the second Interval.

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

Return True iif. every value of the second Interval is into the first Interval.

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

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

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

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

Type Position

data Position Source #

Constructors

Away

-_| (LT) or |_- (GT)

Adjacent

-| (LT) or |- (GT)

Overlap

-+| (LT) or |+- (GT)

Prefix

+| (LT) or +- (GT)

Suffixed

-+ (LT) or |+ (GT)

Include

-+- (LT) or |+| (GT)

Equal

+ (EQ)

(..<<..) :: Ord x => Interval x -> Interval x -> Bool infix 4 Source #

Return True iif. Position of given Intervals is (Away, LT).

(..>>..) :: Ord x => Interval x -> Interval x -> Bool infix 4 Source #

Return True iif. Position of given Intervals is (Away, GT).

(..<..) :: Ord x => Interval x -> Interval x -> Bool infix 4 Source #

Return True iif. Position of given Intervals is (Away, LT) or (Adjacent, LT).

(..>..) :: Ord x => Interval x -> Interval x -> Bool infix 4 Source #

Return True iif. Position of given Intervals is (Away, GT) or (Adjacent, GT).

(..<=..) :: Ord x => Interval x -> Interval x -> Bool infix 4 Source #

Return True iif. Position of given Intervals is (Away, LT), (Adjacent, LT), (Overlap, LT), (Prefix, LT), (Suffixed, LT), (Include, GT), or (Equal, _).

(..>=..) :: Ord x => Interval x -> Interval x -> Bool infix 4 Source #

Return True iif. Position of given Intervals is (Away, GT), (Adjacent, GT), (Overlap, GT), (Prefix, GT), (Suffixed, GT), (Include, LT), or (Equal, _).

Merge

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

Type Unlimitable

Type Pretty

newtype Pretty x Source #

Constructors

Pretty x 

Instances

Eq x => Eq (Pretty x) Source # 

Methods

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

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

Ord x => Ord (Pretty x) Source # 

Methods

compare :: Pretty x -> Pretty x -> Ordering #

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

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

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

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

max :: Pretty x -> Pretty x -> Pretty x #

min :: Pretty x -> Pretty x -> Pretty x #

(Ord x, Show x) => Show (Pretty (Unlimitable x)) Source # 
(Ord x, Show x) => Show (Pretty (Interval x)) Source # 
(Ord x, Show x) => Show (Pretty (Sieve x)) # 

Methods

showsPrec :: Int -> Pretty (Sieve x) -> ShowS #

show :: Pretty (Sieve x) -> String #

showList :: [Pretty (Sieve x)] -> ShowS #