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

Safe HaskellNone

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.

(Eq (Range a), BoundedInt a) => Ord (Range a) 
Show a => Show (Range a) 
(Eq (Range a), BoundedInt a) => Lattice (Range a) 
(BoundedInt a, BoundedInt b, BoundedInt c) => Num (Range a, Range b, Range c) 

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

Convenience alias for bounded integers

Instances

(Ord 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 :: (Show a, BoundedInt a) => a -> StringSource

Shows a bound.

showRange :: (Show a, 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

Lattice 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 :: Ord a => 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 :: forall a. 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

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

rangeByRange ra rb: Computes the range of the following set

 {x | a <- ra, b <- rb, x <- Range a b}

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.

subSat :: BoundedInt a => a -> a -> aSource

Saturating unsigned subtraction

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

Range propagation for subSat

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 :: (Num b, 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, BoundedInt b) => Range a -> Range b -> Range aSource

Propagating range information through shiftLU.

rangeShiftLUUnsigned :: (Bounded a, Bits a, Integral a, Integral b) => Range a -> Range b -> Range aSource

Unsigned case for rangeShiftLU.

rangeShiftRU :: (BoundedInt a, BoundedInt b) => Range a -> Range b -> Range aSource

Propagating range information through shiftRU.

rangeShiftRUUnsigned :: (Num a, Bits a, Ord a, Bounded b, Integral b, Bits b) => Range a -> Range b -> Range aSource

Unsigned case for rangeShiftRU.

correctShiftRU :: (Num a, Bits a, BoundedInt b) => a -> b -> aSource

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.

rangeComplement :: (Bits a, BoundedInt a) => Range a -> Range aSource

Propagating range information through complement

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.

predAbs :: (Bounded a, Eq a, Num a, Enum a) => a -> aSource

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

Propagates range information through div

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

Unsigned case for rangeDiv

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.

rangeLessAbs :: (Bounded a, Integral a, Bits a) => Range a -> Range a -> BoolSource

Writing d `rangeLess` abs r doesn't mean what you think it does because r may contain minBound which doesn't have a positive representation. Instead, this function should be used.

absRangeLessAbs :: (Bounded a, Integral a, Bits a) => Range a -> Range a -> BoolSource

Similar to rangeLessAbs but replaces the expression abs d `rangeLess` abs r instead.

Products of ranges

liftR :: (BoundedInt b, BoundedInt c, BoundedInt d) => (forall a. BoundedInt a => Range a) -> (Range b, Range c, Range d)Source

binopR :: (BoundedInt a, BoundedInt b, BoundedInt c) => (forall d. BoundedInt d => Range d -> Range d -> Range d) -> (Range a, Range b, Range c) -> (Range a, Range b, Range c) -> (Range a, Range b, Range c)Source

mapR :: (BoundedInt a, BoundedInt b, BoundedInt c) => (forall d. BoundedInt d => Range d -> Range d) -> (Range a, Range b, Range c) -> (Range a, Range b, Range c)Source