inf-interval-0.1.0.1: Non-contiguous interval data types with potentially infinite ranges.

Safe HaskellNone
LanguageHaskell2010

Numeric.Interval.Infinite

Contents

Description

This package is intended to be imported qualified, so many of the names of APIs provided will conflict with the Data.Set module in the containers package.

Synopsis

The Inf data type

data Inf c

Enumerable elements with the possibility of infinity.

Constructors

NegInf

negative infinity

PosInf

positive infinity

Finite !c

a single point

Instances

Functor Inf 
Eq c => Eq (Inf c) 
Ord c => Ord (Inf c) 
Read c => Read (Inf c) 
Show c => Show (Inf c) 
Monoid c => Monoid (Inf c) 
NFData a => NFData (Inf a) 
Typeable (* -> *) Inf 

stepDown :: (Eq c, Enum c, InfBound c) => Inf c -> Inf c

Decrement a given value, but if the value is minBound, returns NegInf. In some circumstances this is better than incrementing fmap pred because pred evaluates to an error when passing maxBound as the argument. This function will never evaluate to an error.

stepUp :: (Eq c, Enum c, InfBound c) => Inf c -> Inf c

Increment a given value, but if the value is maxBound, return PosInf. In some circumstances this is better than incrementing with fmap succ because succ evaluates to an error when passing maxBound as the argument. This function will never evaluate to an error.

toFinite :: Inf c -> Maybe c

Retrieve the value contained in an Inf, if it exists.

class InfBound c where

Like Bounded, except the bounds might be infinite, and return NegInf or PosInf for the bounds. Using the GHC "flexible instances" and "undecidable instances" feature, any data type that is an instance of Bounded is also a memberM of BoundInf.

Methods

minBoundInf :: Inf c

maxBoundInf :: Inf c

the Interval data type

data Interval c

This is a data type specifying an inclusive interval between exactly two points (which may be the same point). This is the building block of an Interval Set.

Instances

Functor Interval 
Eq c => Eq (Interval c) 
Ord c => Ord (Interval c) 
(Eq c, Ord c, InfBound c, Read c) => Read (Interval c) 
Show c => Show (Interval c) 
NFData a => NFData (Interval a) 
Ord i => SubBounded (Interval i) i 
Typeable (* -> *) Interval 

toPair :: Interval c -> (Inf c, Inf c)

fromPair :: (Eq c, Ord c) => Inf c -> Inf c -> Maybe (Interval c)

interval :: (Ord c, InfBound c) => c -> c -> Interval c

Construct a Interval from two values.

point :: Ord c => c -> Interval c

Construct a Interval that is only a single unit, i.e. it starts at X and ends at X.

wholeInterval :: Interval c

Construct the infiniteM Interval

negInfTo :: InfBound c => c -> Interval c

Construct a Interval from negative infinity to a given value.

toPosInf :: InfBound c => c -> Interval c

Construct a Interval from a given value to positive infinity.

toBounded :: Bounded c => Inf c -> c

If an Inf is also Bounded then you can convert it to some value in the set of Bounded items. NegInf translates to minBound, PosInf translates to maxBound, and Finite translates to the value at that pointM.

toBoundedPair :: Bounded c => Interval c -> (c, c)

Like toBounded, but operates on a interval and returns a pair of values.

enumBoundedPair :: (Enum c, Bounded c) => Interval c -> [c]

intervalMember :: (Eq c, Ord c) => Interval c -> c -> Bool

Tests whether an element is a memberM is enclosed by the Interval.

singular :: Interval a -> Maybe (Inf a)

If the Interval was constructed with single, return the pointM (possibly PosInf or NegInf) value used to construct it, otherwise return Nothing.

plural :: Interval a -> Maybe (Inf a, Inf a)

If the Interval was constructed with interval, return a pair of points (possibly PosInf or NegInf) value used to construct it, otherwise return Nothing.

canonicalInterval :: (Eq c, Ord c, InfBound c) => Interval c -> [Interval c]

This gets rid of as many infiniteM elements as possible. All Single PosInf and Single NegInf points are eliminated, and if an NegInf or PosInf can be replaced with a corresponding minBoundInf or maxBoundInf, then it is. This function is intended to be used as a list monadic function, so use it like so: let myListOfSegments = [...] in myListOfSegments >>= delInfPoints

intervalNub :: (Ord c, Enum c, InfBound c) => [Interval c] -> [Interval c]

Eliminate overlapping and duplicate Intervals from a list of segments.

intervalInvert :: (Ord c, Enum c, InfBound c) => Interval c -> Set c

Evaluates to the set of all elements not selected by the given Interval.

intervalUnion :: (Ord c, Enum c, InfBound c) => Interval c -> Interval c -> Set c

Performs a set union on two Intervals of elements to create a new _interval. If the elements of the new _interval are not contiguous, each _interval is returned separately and unchanged. The first item in the pair of items returned is True if any of the items were modified.

intervalIntersect :: (Ord c, Enum c, InfBound c) => Interval c -> Interval c -> Set c

Performs a set intersection on two Intervals of elements to create a new _interval. If the elements of the new _interval are not contiguous, this function evaluates to an empty list.

intervalDelete :: (Ord c, Enum c, InfBound c) => Interval c -> Interval c -> Set c

Performs a set "delete" operation, deleteing any elements selected by the first _interval if they are contained in the second _interval. This operation is not associative, i.e. intervalDelete a b /= intervalDelete b a.

intervalExclusion :: (Ord c, Enum c, InfBound c) => Interval c -> Interval c -> Set c

Analogous to a bitwise exclusive-OR operation, returns the set of Intervals produced from combining two Intervals such that only the portions of the Intervals that do not interlap are included.

areIntersecting :: (Eq c, Ord c) => Interval c -> Interval c -> Bool

Returns true if two Intervals are intersecting.

areConsecutive :: (Ord c, Enum c, InfBound c) => Interval c -> Interval c -> Bool

Returns true if two Intervals are consecutive, that is, if the end is the predecessor of the start of the other.

class Ord i => SubBounded dat i where

Describes a class of data types that contained a range of values described by an upper and lower bound, a subset of the range of values of the minBoundInf and maxBoundInf. Unlike Bounded or InfBound, this class describes data types like Arrays which contain information about the upper and lower bound of the data type.

Methods

subBounds :: dat -> Interval i

Instances

Ord i => SubBounded (Interval i) i 
(Ord i, Ix i, InfBound i) => SubBounded (i, i) i 
(Ord i, Ix i, InfBound i) => SubBounded (Array i o) i 

Predicates on Intervals

envelop :: (Ord c, InfBound c) => Interval c -> Interval c -> Interval c

Construct the minimum Interval that is big enough to hold both given segments.

intervalSpanAll :: (Ord c, InfBound c) => [Interval c] -> Maybe (Interval c)

Computes the minimum Interval that can contain the list of all given EnumRanges. Nothing indicates the empty set.

intLength :: Integral c => Interval c -> Inf Integer

Evaluates to the number of elements covered by this region. Returns PosInf if there are an infinite number of elements. For data of a type that is not an instance of Integral, for example Interval Char, use enumLength instead, or else fmap the element type to an Integer.

enumLength :: (Ord c, Enum c, InfBound c) => Interval c -> Inf Integer

Like intLength, but works on Intervals of Enum elements rather than Integral elements.

intervalIntSize :: (Bounded c, Integral c) => Interval c -> Integer

Return the number of points included the set for sets of points that are both Bounded and Integral.

intervalEnumSize :: (Bounded c, Enum c) => Interval c -> Int

Return the number of points included the set for sets of points that are both Bounded and Enum.

isWithin :: (Eq c, Ord c) => Inf c -> Interval c -> Bool

Tests whether an Inf is within the _interval. It is handy when used with backquote noation: enumInf isWithin _interval

intervalHasEnumInf :: Interval c -> Bool

A predicate evaluating whether or not a interval includes an PosInf or NegInf value. This should not be confused with a predicate evaluating whether the set of elements included by the rangeM is infiniteM, because types that are instances of Bounded may also contain PosInf or NegInf elements, values of these types may be evaluated as "infintie" by this function, even though they are Bounded. To check if a interval is infiniteM, use intervalIsInfinite instead.

intervalIsInfinite :: InfBound c => Interval c -> Bool

A predicate evaluating whether or not a interval is infiniteM. Types that are Bounded are always finite, and thus this function will always evaluate to False for these types.

The Set data type

data Set c

Instances

(Enum c, Ord c, InfBound c) => Eq (Set c) 
(Enum c, Ord c, InfBound c) => Ord (Set c) 
(Eq c, Ord c, Enum c, Read c, InfBound c) => Read (Set c) 
(Eq c, Ord c, Enum c, Show c, InfBound c) => Show (Set c) 
(Ord c, Enum c, InfBound c) => Monoid (Sum (Set c)) 
(Ord c, Enum c, InfBound c) => Monoid (Product (Set c)) 
NFData a => NFData (Set a) 
Typeable (* -> *) Set 

empty :: Set c

whole :: Set c

fromList :: (Ord c, Enum c, InfBound c) => [Interval c] -> Set c

fromPairs :: (Ord c, Enum c, InfBound c) => [(c, c)] -> Set c

fromPoints :: (Ord c, Enum c, InfBound c) => [c] -> Set c

range :: (Ord c, Enum c, InfBound c) => c -> c -> Set c

singleton :: (Ord c, Enum c, InfBound c) => c -> Set c

map :: (Eq b, Ord b, Enum b, InfBound b) => (a -> b) -> Set a -> Set b

Set is not a functor, but you can map over values as long as the type of values you map to satisfy the class constraints Eq, Ord, Enum, and InfBound

toList :: (Ord c, Enum c, InfBound c) => Set c -> [Interval c]

intSize :: (Ord c, Integral c, InfBound c, Bounded c) => Set c -> Integer

Evaluate an Integer size on a set of Bounded Integral elements.

enumSize :: (Ord c, Enum c, Bounded c, InfBound c) => Set c -> Int

Evaluate an Int size on a set of Bounded Enum elements.

cardinality :: (Ord c, Enum c, InfBound c) => Set c -> Inf Integer

Evaluate a possibly infinite Integer value counting the number of elements in the set.

elems :: (Ord c, Enum c, Bounded c, InfBound c) => Set c -> [c]

member :: (Ord c, InfBound c) => Set c -> c -> Bool

null :: (Ord c, Enum c, InfBound c) => Set c -> Bool

True if the Set is null.

isWhole :: (Ord c, Enum c, InfBound c) => Set c -> Bool

True if the Set spans the whole interval.

isSingleton :: (Ord c, Enum c, InfBound c) => Set c -> Maybe c

Set Operators for non-monadic Sets

invert :: (Ord c, Enum c, InfBound c) => Set c -> Set c

exclusive :: (Ord c, Enum c, InfBound c) => Set c -> Set c -> Set c

Exclusive union, similar to the binary exclusive-OR operator, returns the union of a and b excluding all Intervals where a and b intersect. This function is equal to

(a `'union'` b) `'delete'` (a `'intersect'` b)

union :: (Ord c, Enum c, InfBound c) => Set c -> Set c -> Set c

unions :: (Ord c, Enum c, InfBound c) => [Set c] -> Set c

intersections :: (Ord c, Enum c, InfBound c) => [Set c] -> Set c

intersect :: (Ord c, Enum c, InfBound c) => Set c -> Set c -> Set c

delete :: (Ord c, Enum c, InfBound c) => Set c -> Set c -> Set c

Miscelaneous

innerProduct :: (Ord c, Enum c, InfBound c) => (Interval c -> Interval c -> Set c) -> [Interval c] -> [Interval c] -> Set c

This function takes a multiplication function, usually intervalIntersect or intervalDelete. It works like polynomial multiplication, with the provided reduction function computing the product of every pair of Intervals, and then the "sum" (actually the intervalUnion) of all products are taken. The intersect and exclusive functions are defined to use this function.