Ranged-sets-0.4.0: Ranged sets for Haskell

Safe HaskellSafe
LanguageHaskell2010

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
DiscreteOrdered a => Eq (Range a) Source # 
Instance details

Defined in Data.Ranged.Ranges

Methods

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

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

DiscreteOrdered a => Ord (Range a) Source # 
Instance details

Defined in Data.Ranged.Ranges

Methods

compare :: Range a -> Range a -> Ordering #

(<) :: Range a -> Range a -> Bool #

(<=) :: Range a -> Range a -> Bool #

(>) :: Range a -> Range a -> Bool #

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

max :: Range a -> Range a -> Range a #

min :: Range a -> Range a -> Range a #

(Show a, DiscreteOrdered a) => Show (Range a) Source # 
Instance details

Defined in Data.Ranged.Ranges

Methods

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

show :: Range a -> String #

showList :: [Range a] -> ShowS #

(Arbitrary v, DiscreteOrdered v, Show v) => Arbitrary (Range v) Source # 
Instance details

Defined in Data.Ranged.Ranges

Methods

arbitrary :: Gen (Range v) #

shrink :: Range v -> [Range v] #

(CoArbitrary v, DiscreteOrdered v, Show v) => CoArbitrary (Range v) Source # 
Instance details

Defined in Data.Ranged.Ranges

Methods

coarbitrary :: Range v -> Gen b -> Gen b #

emptyRange :: DiscreteOrdered v => Range v Source #

The empty range

fullRange :: DiscreteOrdered v => Range v Source #

The full range. All values are within it.

Predicates

rangeIsEmpty :: DiscreteOrdered v => Range v -> Bool Source #

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

rangeIsFull :: DiscreteOrdered v => Range v -> Bool Source #

A range is full if it contains every possible value.

rangeOverlap :: DiscreteOrdered v => Range v -> Range v -> Bool Source #

Two ranges overlap if their intersection is non-empty.

rangeEncloses :: DiscreteOrdered v => Range v -> Range v -> Bool Source #

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 v Source #

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 -> Bool Source #

True if the value is within the range.

rangeListHas :: Ord v => [Range v] -> v -> Bool Source #

True if the value is within one of the ranges.

Set Operations

singletonRange :: DiscreteOrdered v => v -> Range v Source #

A range containing a single value

rangeIntersection :: DiscreteOrdered v => Range v -> Range v -> Range v Source #

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 -> Bool Source #

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 -> Bool Source #

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 -> Bool Source #

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 -> Bool Source #

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 -> Bool Source #

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 -> Bool Source #

Range enclosure makes union an identity function.

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

prop_singletonRangeHas :: DiscreteOrdered a => a -> Bool Source #

Range Singleton has its member.

prop_singletonRangeHas v = singletonRange v `rangeHas` v

prop_singletonRangeHasOnly :: DiscreteOrdered a => a -> a -> Bool Source #

Range Singleton has only its member.

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

prop_singletonRangeConverse :: DiscreteOrdered a => a -> Bool Source #

A singleton range can have its value extracted.

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

prop_emptyNonSingleton :: Bool Source #

The empty range is not a singleton.

prop_emptyNonSingleton = rangeSingletonValue emptyRange == Nothing

prop_fullNonSingleton :: Bool Source #

The full range is not a singleton.

prop_fullNonSingleton = rangeSingletonValue fullRange == Nothing

prop_nonSingleton :: Double -> Double -> Property Source #

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

prop_intSingleton :: Integer -> Integer -> Property Source #

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.