affinely-extended-0.1.0.0

Safe HaskellNone
LanguageHaskell2010

Data.AffinelyExtend

Description

This package has four ways to extend any numerical type to add infinities:

  1. Both infinities with GADT: AffinelyExtendBoth, creation: affinelyExtendBoth
  2. Positive infinity only with GADT: AffinelyExtendPos, creation: affinelyExtendPos
  3. Both infinities with upper/lower bounds as infinity: AffinelyExtendBoundedBoth, creation: affinelyExtendBoundedBoth
  4. Positive infinities only with upper bound as infinity: AffinelyExtendBoundedPos, creation: affinelyExtendBoundedPos

The function affinelyExtend is a generic creation function that calls one of the above based on the derived type of the output.

A few notes. Firstly, option 3, the AffinelyExtendBoundedBoth option, does not actually use maxBound and minBound as positive and negative infinity respectively, it actually takes the smallest absolute value maxBound and minBound as positive infinity and the negation of that as negative infinity.

This means, for example, on an Int8, +127 is positive infinity, but -127 is negative infinity, not -128. So the valid finite range for the type becomes [-126..126].

Storable and unboxed instances for bounded types (i.e. AffinelyExtendBoundedBoth and AffinelyExtendBoundedPos) should be trivial to create.

This package refers to the first two types, namely AffinelyExtendBoth and AffinelyExtendPos as unpacked types. When they're used directly, packing and unpacking is just id, but when the bounded types are used, they are unpacked into these types and packed back into themselves.

For most operations, the bounded types simply unpack to the unbounded types, perform the unpacked operation, and then pack themselves.

But there's two optimisations to this process

  1. For operations like negate, there is no need for special checking for infinities, so the unbounded types just apply negate directly to their own representation.
  2. There's rewrite rules that remove 'unpack . pack' sequences.

There's competing advantages to both formats. The bounded formats obviously take up less storage space, and can perform some operations like negate without a pattern match.

However, chains of operations on the "packed" bounded types that do need to check for infinity will check everytime, because there's no way for the compiler to disguish between and operation that has overflowed and "accidently" became infinity and actual infinity.

So the rewrite rules are intended to help chains of operations use the "unpacked" represenation, which hopefully should reduce the infinity checks to the first operation in the sequence (as after that the compiler should be able to statically prove at compile time that the latter operations are/are not infinities.

This package is currently without a test suite and needs more documentation, so if you find any bugs, please report them.

Documentation

data AffinelyExtend hasNegativeInfinity a where Source #

Instances

(Ord a, Enum a) => Enum (AffinelyExtendPos a) Source # 
(Ord a, Enum a) => Enum (AffinelyExtendBoth a) Source # 
Eq a => Eq (AffinelyExtendPos a) Source # 
Eq a => Eq (AffinelyExtendBoth a) Source # 
(Ord a, Fractional a) => Fractional (AffinelyExtendPos a) Source # 
(Ord a, Fractional a) => Fractional (AffinelyExtendBoth a) Source # 
Integral a => Integral (AffinelyExtendPos a) Source # 
Integral a => Integral (AffinelyExtendBoth a) Source # 
(Ord a, Num a) => Num (AffinelyExtendPos a) Source # 
(Ord a, Num a) => Num (AffinelyExtendBoth a) Source # 
Ord a => Ord (AffinelyExtendPos a) Source # 
Ord a => Ord (AffinelyExtendBoth a) Source # 
(Show a, Read a) => Read (AffinelyExtendPos a) Source # 
(Show a, Read a) => Read (AffinelyExtendBoth a) Source # 
Real a => Real (AffinelyExtendPos a) Source # 
Real a => Real (AffinelyExtendBoth a) Source # 
Show a => Show (AffinelyExtendPos a) Source # 
Show a => Show (AffinelyExtendBoth a) Source # 
CanAffinelyExtendPos (AffinelyExtendPos a) Source # 
CanAffinelyExtend (AffinelyExtendPos a) Source # 
CanAffinelyExtend (AffinelyExtendBoth a) Source # 
HasBothInfinities (AffinelyExtendBoth a) Source # 
HasPositiveInfinity (AffinelyExtendPos a) Source # 
HasPositiveInfinity (AffinelyExtendBoth a) Source # 
type BaseType (AffinelyExtendPos a) Source # 
type BaseType (AffinelyExtendBoth a) Source # 
type UnpackType (AffinelyExtendPos a) Source # 
type UnpackType (AffinelyExtendBoth a) Source # 

data AffinelyExtendBoundedBoth a Source #

Instances

(Bounded a, Ord a, Enum a, Num a) => Enum (AffinelyExtendBoundedBoth a) Source # 
Eq a => Eq (AffinelyExtendBoundedBoth a) Source # 
(Ord a, Bounded a, Fractional a) => Fractional (AffinelyExtendBoundedBoth a) Source # 
(Bounded a, Integral a) => Integral (AffinelyExtendBoundedBoth a) Source # 
(Ord a, Num a, Bounded a) => Num (AffinelyExtendBoundedBoth a) Source # 
Ord a => Ord (AffinelyExtendBoundedBoth a) Source # 
(Bounded a, Ord a, Num a, Read a, Show a) => Read (AffinelyExtendBoundedBoth a) Source # 
(Real a, Bounded a) => Real (AffinelyExtendBoundedBoth a) Source # 
(Ord a, Bounded a, Num a, Show a) => Show (AffinelyExtendBoundedBoth a) Source # 
(Ord a, Bounded a, Num a) => CanAffinelyExtend (AffinelyExtendBoundedBoth a) Source # 
(Bounded a, Ord a, Num a) => HasBothInfinities (AffinelyExtendBoundedBoth a) Source # 
(Bounded a, Ord a, Num a) => HasPositiveInfinity (AffinelyExtendBoundedBoth a) Source # 
type BaseType (AffinelyExtendBoundedBoth a) Source # 
type UnpackType (AffinelyExtendBoundedBoth a) Source # 

data AffinelyExtendBoundedPos a Source #

Instances

(Bounded a, Ord a, Enum a, Num a) => Enum (AffinelyExtendBoundedPos a) Source # 
Eq a => Eq (AffinelyExtendBoundedPos a) Source # 
(Ord a, Bounded a, Fractional a) => Fractional (AffinelyExtendBoundedPos a) Source # 
(Bounded a, Integral a) => Integral (AffinelyExtendBoundedPos a) Source # 
(Ord a, Num a, Bounded a) => Num (AffinelyExtendBoundedPos a) Source # 
Ord a => Ord (AffinelyExtendBoundedPos a) Source # 
(Bounded a, Eq a, Read a, Show a) => Read (AffinelyExtendBoundedPos a) Source # 
(Real a, Bounded a) => Real (AffinelyExtendBoundedPos a) Source # 
(Eq a, Bounded a, Show a) => Show (AffinelyExtendBoundedPos a) Source # 
(Eq a, Bounded a) => CanAffinelyExtendPos (AffinelyExtendBoundedPos a) Source # 
(Eq a, Bounded a) => CanAffinelyExtend (AffinelyExtendBoundedPos a) Source # 
(Eq a, Bounded a) => HasPositiveInfinity (AffinelyExtendBoundedPos a) Source # 
type BaseType (AffinelyExtendBoundedPos a) Source # 
type UnpackType (AffinelyExtendBoundedPos a) Source # 

class CanAffinelyExtend a where Source #

Minimal complete definition

affinelyExtend_c

Associated Types

type BaseType a Source #

type UnpackType a Source #

Instances

CanAffinelyExtend Double Source # 
CanAffinelyExtend Float Source # 
(Eq a, Bounded a) => CanAffinelyExtend (AffinelyExtendBoundedPos a) Source # 
(Ord a, Bounded a, Num a) => CanAffinelyExtend (AffinelyExtendBoundedBoth a) Source # 
CanAffinelyExtend (AffinelyExtendPos a) Source # 
CanAffinelyExtend (AffinelyExtendBoth a) Source #