Ranged-sets-0.2.1: Ranged sets for Haskell

Data.Ranged.Ranges

Contents

Description

A range has an upper and lower boundary.

Synopsis

Construction

data Ord v => Range v Source

A Range has upper and lower boundaries.

Constructors

Range 

Instances

emptyRange :: DiscreteOrdered v => Range vSource

The empty range

fullRange :: DiscreteOrdered v => Range vSource

The full range. All values are within it.

Predicates

rangeIsEmpty :: DiscreteOrdered v => Range v -> BoolSource

A range is empty unless its upper boundary is greater than its lower boundary.

rangeIsFull :: DiscreteOrdered v => Range v -> BoolSource

A range is full if it contains every possible value.

rangeOverlap :: DiscreteOrdered v => Range v -> Range v -> BoolSource

Two ranges overlap if their intersection is non-empty.

rangeEncloses :: DiscreteOrdered v => Range v -> Range v -> BoolSource

The first range encloses the second if every value in the second range is also within the first range. If the second range is empty then this is always true.

rangeSingletonValue :: DiscreteOrdered v => Range v -> Maybe vSource

If the range is a singleton, returns Just the value. Otherwise returns Nothing.

Known bug: This always returns Nothing for ranges including BoundaryBelowAll or BoundaryAboveAll. For bounded types this can be incorrect. For instance, the following range only contains one value:

    Range (BoundaryBelow maxBound) BoundaryAboveAll

Membership

rangeHas :: Ord v => Range v -> v -> BoolSource

True if the value is within the range.

rangeListHas :: Ord v => [Range v] -> v -> BoolSource

True if the value is within one of the ranges.

Set Operations

singletonRange :: DiscreteOrdered v => v -> Range vSource

A range containing a single value

rangeIntersection :: DiscreteOrdered v => Range v -> Range v -> Range vSource

Intersection of two ranges, if any.

rangeUnion :: DiscreteOrdered v => Range v -> Range v -> [Range v]Source

Union of two ranges. Returns one or two results.

If there are two results then they are guaranteed to have a non-empty gap in between, but may not be in ascending order.

rangeDifference :: DiscreteOrdered v => Range v -> Range v -> [Range v]Source

range1 minus range2. Returns zero, one or two results. Multiple results are guaranteed to have non-empty gaps in between, but may not be in ascending order.

QuickCheck properties

prop_unionRange :: DiscreteOrdered a => Range a -> Range a -> a -> BoolSource

The union of two ranges has a value iff either range has it.

 prop_unionRange r1 r2 n =
    (r1 `rangeHas` n || r2 `rangeHas` n)
    == (r1 `rangeUnion` r2) `rangeListHas` n

prop_unionRangeLength :: DiscreteOrdered a => Range a -> Range a -> BoolSource

The union of two ranges always contains one or two ranges.

 prop_unionRangeLength r1 r2 = (n == 1) || (n == 2)
    where n = length $ rangeUnion r1 r2

prop_intersectionRange :: DiscreteOrdered a => Range a -> Range a -> a -> BoolSource

The intersection of two ranges has a value iff both ranges have it.

 prop_intersectionRange r1 r2 n =
    (r1 `rangeHas` n && r2 `rangeHas` n)
    == (r1 `rangeIntersection` r2) `rangeHas` n

prop_differenceRange :: DiscreteOrdered a => Range a -> Range a -> a -> BoolSource

The difference of two ranges has a value iff the first range has it and the second does not.

 prop_differenceRange r1 r2 n =
    (r1 `rangeHas` n && not (r2 `rangeHas` n))
    == (r1 `rangeDifference` r2) `rangeListHas` n

prop_intersectionOverlap :: DiscreteOrdered a => Range a -> Range a -> BoolSource

Iff two ranges overlap then their intersection is non-empty.

 prop_intersectionOverlap r1 r2 = 
     (rangeIsEmpty $ rangeIntersection r1 r2) == (rangeOverlap r1 r2)

prop_enclosureUnion :: DiscreteOrdered a => Range a -> Range a -> BoolSource

Range enclosure makes union an identity function.

 prop_enclosureUnion r1 r2 = 
    rangeEncloses r1 r2 == (rangeUnion r1 r2 == [r1])

prop_singletonRangeHas :: DiscreteOrdered a => a -> BoolSource

Range Singleton has its member.

 prop_singletonRangeHas v = singletonRange v `rangeHas` v

prop_singletonRangeHasOnly :: DiscreteOrdered a => a -> a -> BoolSource

Range Singleton has only its member.

 prop_singletonHasOnly v1 v2 =
    (v1 == v2) == (singletonRange v1 `rangeHas` v2)

prop_singletonRangeConverse :: DiscreteOrdered a => a -> BoolSource

A singleton range can have its value extracted.

 prop_singletonRangeConverse v =
    rangeSingletonValue (singletonRange v) == Just v

prop_emptyNonSingleton :: BoolSource

The empty range is not a singleton.

 prop_emptyNonSingleton = rangeSingletonValue emptyRange == Nothing

prop_fullNonSingleton :: BoolSource

The full range is not a singleton.

 prop_fullNonSingleton = rangeSingletonValue fullRange == Nothing

prop_nonSingleton :: Double -> Double -> PropertySource

For real x and y, x < y implies that any range between them is a non-singleton.

prop_intSingleton :: Integer -> Integer -> PropertySource

For all integers x and y, any range formed from boundaries on either side of x and y is a singleton iff it contains exactly one integer.