feldspar-language-0.4.0.2: A functional embedded language for DSP and parallelism

Feldspar.Range

Contents

Description

Bounded integer ranges

Synopsis

Definition

data Range a Source

A bounded range of values of type a

Constructors

Range 

Fields

lowerBound :: a
 
upperBound :: a
 

Instances

Eq a => Eq (Range a) 
BoundedInt a => Num (Range a)

Implements fromInteger as a singletonRange, and implements correct range propagation for arithmetic operations.

Show a => Show (Range a) 
(BoundedInt a, Arbitrary a) => Arbitrary (Range a) 
BoundedInt a => Set (Range a) 
BoundedInt a => FullProp (Range a) 

class (Eq a, Ord a, Show a, Num a, Bounded a, Integral a, Bits a) => BoundedInt a Source

Convenience alias for bounded integers

Instances

(Eq a, Ord a, Show a, Num a, Bounded a, Integral a, Bits a) => BoundedInt a 

handleSign :: forall a b. BoundedInt a => (Range a -> b) -> (Range a -> b) -> Range a -> bSource

A convenience function for defining range propagation. handleSign propU propS chooses propU for unsigned types and propS for signed types.

showBound :: BoundedInt a => a -> StringSource

Shows a bound.

showRange :: BoundedInt a => Range a -> StringSource

A textual representation of ranges.

mapMonotonic :: (a -> b) -> Range a -> Range bSource

Requires a monotonic function

mapMonotonic2 :: (a -> b -> c) -> Range a -> Range b -> Range cSource

Requires a monotonic function

Set operations

emptyRange :: BoundedInt a => Range aSource

The range containing no elements

fullRange :: BoundedInt a => Range aSource

The range containing all elements of a type

range :: a -> a -> Range aSource

Construct a range

singletonRange :: a -> Range aSource

The range containing one element

naturalRange :: BoundedInt a => Range aSource

The range from 0 to the maximum element

negativeRange :: BoundedInt a => Range aSource

The range from the smallest negative element to -1. Undefined for unsigned types

rangeSize :: BoundedInt a => Range a -> aSource

The size of a range. Beware that the size may not always be representable for signed types. For instance rangeSize (range minBound maxBound) :: Int gives a nonsense answer.

isEmpty :: BoundedInt a => Range a -> BoolSource

Checks if the range is empty

isFull :: BoundedInt a => Range a -> BoolSource

Checks if the range contains all values of the type

isSingleton :: BoundedInt a => Range a -> BoolSource

Checks is the range contains exactly one element

isSubRangeOf :: BoundedInt a => Range a -> Range a -> BoolSource

r1 `isSubRangeOf` r2 checks is all the elements in r1 are included in r2

isNatural :: BoundedInt a => Range a -> BoolSource

Checks whether a range is a sub-range of the natural numbers.

isNegative :: BoundedInt a => Range a -> BoolSource

Checks whether a range is a sub-range of the negative numbers.

inRange :: BoundedInt a => a -> Range a -> BoolSource

a `inRange` r checks is a is an element of the range r.

rangeOp :: BoundedInt a => (Range a -> Range a) -> Range a -> Range aSource

A convenience function for defining range propagation. If the input range is empty then the result is also empty.

rangeOp2 :: BoundedInt a => (Range a -> Range a -> Range a) -> Range a -> Range a -> Range aSource

See rangeOp.

rangeUnion :: BoundedInt a => Range a -> Range a -> Range aSource

Union on ranges.

rangeIntersection :: BoundedInt a => Range a -> Range a -> Range aSource

Intersection on ranges.

disjoint :: BoundedInt a => Range a -> Range a -> BoolSource

disjoint r1 r2 returns true when r1 and r2 have no elements in common.

rangeGap :: BoundedInt a => Range a -> Range a -> Range aSource

rangeGap r1 r2 returns a range of all the elements between r1 and r2 including the boundary elements. If r1 and r2 have elements in common the result is an empty range.

rangeLess :: BoundedInt a => Range a -> Range a -> BoolSource

r1 `rangeLess` r2:

Checks if all elements of r1 are less than all elements of r2.

rangeLessEq :: BoundedInt a => Range a -> Range a -> BoolSource

r1 `rangeLessEq` r2:

Checks if all elements of r1 are less than or equal to all elements of r2.

Propagation

rangeAbs :: BoundedInt a => Range a -> Range aSource

Propagates range information through abs.

rangeSignum :: BoundedInt a => Range a -> Range aSource

Propagates range information through signum.

rangeSignumSigned :: BoundedInt a => Range a -> Range aSource

Signed case for rangeSignum.

rangeSignumUnsigned :: BoundedInt a => Range a -> Range aSource

Unsigned case for rangeSignum.

rangeNeg :: BoundedInt a => Range a -> Range aSource

Propagates range information through negation.

rangeNegUnsigned :: BoundedInt a => Range a -> Range aSource

Unsigned case for rangeNeg.

rangeNegSigned :: BoundedInt a => Range a -> Range aSource

Signed case for rangeNeg.

rangeAdd :: BoundedInt a => Range a -> Range a -> Range aSource

Propagates range information through addition.

rangeAddUnsigned :: BoundedInt a => Range a -> Range a -> Range aSource

Unsigned case for rangeAdd.

rangeAddSigned :: BoundedInt a => Range a -> Range a -> Range aSource

Signed case for rangeAdd.

rangeSub :: BoundedInt a => Range a -> Range a -> Range aSource

Propagates range information through subtraction.

rangeSubUnsigned :: BoundedInt a => Range a -> Range a -> Range aSource

Unsigned case for rangeSub.

rangeMul :: BoundedInt a => Range a -> Range a -> Range aSource

Propagates range information through multiplication

rangeMulSigned :: forall a. BoundedInt a => Range a -> Range a -> Range aSource

Signed case for rangeMul.

rangeMulUnsigned :: forall a. BoundedInt a => Range a -> Range a -> Range aSource

Unsigned case for rangeMul.

bits :: Bits b => b -> IntSource

Returns the position of the highest bit set to 1. Counting starts at 1. Beware! It doesn't terminate for negative numbers.

rangeExp :: BoundedInt a => Range a -> Range a -> Range aSource

Propagates range information through exponentiation.

rangeExpUnsigned :: BoundedInt a => Range a -> Range a -> Range aSource

Unsigned case for rangeExp.

rangeExpSigned :: BoundedInt a => Range a -> Range a -> Range aSource

Sigend case for rangeExp

rangeOr :: forall a. BoundedInt a => Range a -> Range a -> Range aSource

Propagates range information through .|..

rangeOrUnsignedCheap :: BoundedInt a => Range a -> Range a -> Range aSource

Cheap and inaccurate range propagation for .|. on unsigned numbers.

maxPlus :: BoundedInt a => a -> a -> aSource

a `maxPlus` b adds a and b but if the addition overflows then maxBound is returned.

minOrUnsigned :: BoundedInt a => a -> a -> a -> a -> aSource

Accurate lower bound for .|. on unsigned numbers.

maxOrUnsigned :: BoundedInt a => a -> a -> a -> a -> aSource

Accurate upper bound for .|. on unsigned numbers.

rangeOrUnsignedAccurate :: BoundedInt a => Range a -> Range a -> Range aSource

Accurate range propagation through .|. for unsigned types.

rangeAnd :: forall a. BoundedInt a => Range a -> Range a -> Range aSource

Propagating range information through .&..

rangeAndUnsignedCheap :: BoundedInt a => Range a -> Range a -> Range aSource

Cheap and inaccurate range propagation for .&. on unsigned numbers.

rangeXor :: forall a. BoundedInt a => Range a -> Range a -> Range aSource

Propagating range information through xor.

rangeXorUnsigned :: BoundedInt a => Range a -> Range a -> Range aSource

Unsigned case for rangeXor.

rangeShiftLU :: BoundedInt a => Range a -> Range Word32 -> Range aSource

Propagating range information through shiftLU.

rangeShiftRU :: BoundedInt a => Range a -> Range Word32 -> Range aSource

Unsigned case for rangeShiftLU.

Propagating range information through shiftRU.

correctShiftRU :: Bits a => a -> Word32 -> aSource

Unsigned case for rangeShiftRU.

This is a replacement fror Haskell's shiftR. If we carelessly use Haskell's variant then we will get left shifts for very large shift values.

rangeMax :: BoundedInt a => Range a -> Range a -> Range aSource

Propagates range information through max.

rangeMin :: BoundedInt a => Range a -> Range a -> Range aSource

Analogous to rangeMax

rangeMod :: BoundedInt a => Range a -> Range a -> Range aSource

Propagates range information through mod. Note that we assume Haskell semantics for mod.

rangeRem :: BoundedInt a => Range a -> Range a -> Range aSource

Propagates range information through rem. Note that we assume Haskell semantics for rem.

rangeQuot :: BoundedInt a => Range a -> Range a -> Range aSource

Propagates range information through quot.

rangeQuotU :: BoundedInt a => Range a -> Range a -> Range aSource

Unsigned case for rangeQuot.

Testing

rangeTy :: Range t -> t -> Range tSource

atAllTypes :: Monad m => (forall t. (BoundedInt t, Random t, Arbitrary t, Typeable t) => t -> m a) -> m ()Source

Applies a (monadic) function to all the types we are interested in testing with for Feldspar.

Example usage: 'atAllTypes (quickCheck . prop_mul)'

Set operations

Propagation

prop_propagation1 :: (BoundedInt t, Random t) => t -> (forall a. Num a => a -> a) -> Range t -> PropertySource

rangePropagationSafetyPre :: (Random t, BoundedInt t, BoundedInt a) => t -> (t -> t -> a) -> (Range t -> Range t -> Range a) -> (t -> t -> Bool) -> Range t -> Range t -> PropertySource

This function is useful for range propagation functions like rangeMax, rangeMod etc. It takes two ranges, picks an element out of either ranges and checks if applying the operation to the individual elements is in the resulting range after range propagation.

The third argument is a precondition that is satisfied before the test is run. A good example is to make sure that the second argument is non-zero when testing division.

rangePropagationSafetyPre2 :: (Random t, BoundedInt t, Random t2, BoundedInt t2, BoundedInt a) => t -> (t -> t2 -> a) -> (Range t -> Range t2 -> Range a) -> (t -> t2 -> Bool) -> Range t -> Range t2 -> PropertySource

prop_propagation2 :: (BoundedInt t, Random t) => t -> (forall a. Num a => a -> a -> a) -> Range t -> Range t -> PropertySource

Running

data TestCase Source

Constructors

forall t . Testable t => TC String t 

typedTests :: forall a. (BoundedInt a, Random a, Arbitrary a, Integral a) => a -> [TestCase]Source