numeric-domains-0.1.0.0: Numeric Domains

Copyright(c) Michael Szvetits 2019
LicenseBSD3 (see the file LICENSE)
Maintainertypedbyte@qualified.name
Stabilitystable
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Numeric.Interval

Contents

Description

This module exports the types and functions needed to construct, combine and process non-empty numeric intervals.

Package users might want to use the module Numeric.Domain instead, since it provides a convenient abstraction for empty and multiple intervals.

Synopsis

Core Types

data Interval a Source #

A numeric interval is a non-empty, possibly infinite range of values.

Note that rounding errors due to floating point arithmetic are not handled at the lower and upper bounds of intervals.

Instances
Eq a => Eq (Interval a) Source # 
Instance details

Defined in Numeric.Interval

Methods

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

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

Show a => Show (Interval a) Source # 
Instance details

Defined in Numeric.Interval

Methods

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

show :: Interval a -> String #

showList :: [Interval a] -> ShowS #

lowerBound :: Interval a -> LowerBound a Source #

Returns the lower bound of an interval.

upperBound :: Interval a -> UpperBound a Source #

Returns the upper bound of an interval.

Interval Construction

singleton :: a -> Interval a Source #

Creates an interval with a single element.

interval :: Ord a => LowerBound a -> UpperBound a -> Maybe (Interval a) Source #

Creates an interval with the given lower and upper bounds.

Returns Nothing if the lower bound is greater than the upper bound.

lowerBounded :: LowerBound a -> Interval a Source #

Creates an interval with the given lower bound and a positive infinite upper bound.

upperBounded :: UpperBound a -> Interval a Source #

Creates an interval with the given upper bound and a negative infinite lower bound.

maxInterval :: Interval a Source #

Creates an interval with values ranging from negative infinity to positive infinity.

Interval Combination

difference :: Dist a => Interval a -> Interval a -> [Interval a] Source #

Calculates the difference between two intervals, i.e. difference whole diff returns the intervals which contain all elements of whole that are not in diff.

Returns the empty list if diff contains whole.

Returns a singleton list if whole and diff overlap on one of their bounds.

Returns a list with two intervals if whole contains diff.

intersect :: Ord a => Interval a -> Interval a -> Maybe (Interval a) Source #

Calculates the intersection of two intervals, i.e. intersect ix iy contains all elements that are in both intervals ix and iy.

Returns Nothing if the intervals do not overlap.

merge :: Dist a => Interval a -> Interval a -> Maybe (Interval a) Source #

Merges two intervals into one if they overlap or if they have adjacent bounds.

Note that adjacency depends on the type of the interval values, e.g. the intervals [1,3] and [4,6] can be merged to [1,6] for Interval Int, but not for Interval Double.

Returns Nothing if the intervals do not overlap or if their bounds are not adjacent.

Interval Predicates

member :: Ord a => a -> Interval a -> Bool Source #

Checks if an interval contains a specific value.

isSingleton :: Eq a => Interval a -> Bool Source #

Checks if an interval contains exactly one element.

isInfinite :: Interval a -> Bool Source #

Checks if an interval has a lower bound of negative infinity or an upper bound of positive infinity.

hasNegatives :: (Num a, Ord a) => Interval a -> Bool Source #

Checks if an interval contains negative values.

hasPositives :: (Num a, Ord a) => Interval a -> Bool Source #

Checks if an interval contains positive values.

contains :: Ord a => Interval a -> Interval a -> Bool Source #

contains whole sub checks if the interval sub is contained in the interval whole.

Returns True if the two intervals are the same.

Interval Values

elems :: Enum a => Interval a -> Maybe [a] Source #

Enumerates all elements of an interval in ascending order according to the Enum implementation of the interval value type.

Returns Nothing if any of the two interval bounds is unbounded (see isInfinite).

minValue :: Interval a -> Maybe a Source #

Returns the smallest value of an interval.

Only succeeds if the lower bound is closed.

maxValue :: Interval a -> Maybe a Source #

Returns the greatest value of an interval.

Only succeeds if the upper bound is closed.

Interval Arithmetic

plus :: Num a => Interval a -> Interval a -> Interval a Source #

Adds the value ranges of two intervals.

minus :: Num a => Interval a -> Interval a -> Interval a Source #

Subtracts the value ranges of two intervals.

times :: (Num a, Ord a) => Interval a -> Interval a -> Interval a Source #

Multiplies the value ranges of two intervals.

div :: Integral a => Interval a -> Interval a -> Interval a Source #

Divides the value ranges of two intervals using integer division.

Returns maxInterval if 0 is a member of the divisor interval.

abs :: (Num a, Ord a) => Interval a -> Interval a Source #

Calculates the abs function of an interval and their corresponding values.

negate :: Num a => Interval a -> Interval a Source #

Negates the value range of an interval.

Interval Presentation

pretty :: Show a => Interval a -> String Source #

Returns a pretty string for an interval by using Unicode symbols for infinity.