FixedPoint-simple-0.6.1: Fixed point, large word, and large int numerical representations (types and common class instances)

Safe HaskellSafe-Inferred
LanguageHaskell98

Data.FixedPoint

Contents

Description

This FixedPoint module implements arbitrary sized fixed point types and computations. This module intentionally avoids converting to Integer for computations because one purpose is to allow easy translation to other languages to produce stand-alone fixed point libraries. Instead of using Integer, elementary long multiplication and long division are implemented explicitly along with sqrt, exp, and erf functions that are implemented using only primitive operations.

Synopsis

Fixedpoint types

Common Operations

erf' :: (Show a, Eq a, Ord a, Num a, Fractional a) => Int -> a -> a Source

exp' :: (Show a, Ord a, Fractional a, Eq a) => Int -> a -> a Source

sqrt' :: (Ord b, Integral b, Bits b, Integral a, Num a, Bits a, Bits c, FiniteBits b, FiniteBits c) => GenericFixedPoint a b c -> GenericFixedPoint a b c Source

The square root operation converges in O(bitSize input).

Big Int Types

type Int128 = BigInt Word128 Source

A 128 bit int (signed)

type Int256 = BigInt Word256 Source

A 256 bit int (signed)

type Int512 = BigInt Word512 Source

A 512 bit int (signed)

type Int1024 = BigInt Word1024 Source

A 1024 bit int (signed)

type Int2048 = BigInt Word2048 Source

A 2048 bit int (signed)

type Int4096 = BigInt Word4096 Source

A 4096 bit int (signed)

type Int8192 = BigInt Word8192 Source

A 8192 bit int (signed)

Big Word Types

type Word72 = BigWord Word8 Word64 Source

A 72 bit unsigned word

type Word256 = BigWord Word128 Word128 Source

A 256 bit unsigned word

type Word512 = BigWord Word256 Word256 Source

A 512 bit unsigned word

type Word576 = BigWord Word64 Word512 Source

A 576 bit unsigned word

type Word584 = BigWord Word72 Word512 Source

A 584 bit unsigned word

type Word1024 = BigWord Word512 Word512 Source

A 1024 bit unsigned word

type Word1280 = BigWord Word1024 Word256 Source

A 1280 bit unsigned word

type Word2048 = BigWord Word1024 Word1024 Source

A 2048 bit unsigned word

type Word2632 = BigWord Word584 Word2048 Source

A 2632 bit unsigned word

type Word4096 = BigWord Word2048 Word2048 Source

A 4096 bit unsigned word

type Word8192 = BigWord Word4096 Word4096 Source

A 8192 bit unsigned word

Type Constructors

data GenericFixedPoint flat internal fracBitRepr Source

GenericFixedPoint is a type constructor for arbitrarily-sized fixed point tyes. Take note the first type variable, flat, should be a signed int equal to the size of the fixed point integral plus fractional bits. The second type variable, internal, should be unsigned and twice as large a bit size as the flat type. The final type variable, fracBitRepr, should be a data structure of equal bit size to the fractional bits in the fixed point type. See the existing type aliases, such as FixedPoint4816, for examples.

Constructors

FixedPoint 

Fields

toFlat :: flat
 

Instances

(Enum a, Num a, Bits a, Bits c, FiniteBits c) => Enum (GenericFixedPoint a b c) 
Eq flat => Eq (GenericFixedPoint flat internal fracBitRepr) 
(Ord a, Integral a, Bits a, Num a, Bits b, Integral b, Bits c, FiniteBits c) => Fractional (GenericFixedPoint a b c) 
(Ord a, Num a, Bits a, Bits b, Integral a, Integral b, Bits c, FiniteBits c) => Num (GenericFixedPoint a b c) 
Ord flat => Ord (GenericFixedPoint flat internal fracBitRepr) 
(Integral a, Bits a, Integral b, Num a, Bits b, Bits c, FiniteBits c) => Read (GenericFixedPoint a b c) 
(Integral a, Ord a, Num a, Bits a, Bits b, Integral b, Bits c, FiniteBits c) => Real (GenericFixedPoint a b c) 
(Bits b, Bits c, Bits a, Integral a, Integral b, FiniteBits c) => RealFrac (GenericFixedPoint a b c) 
(Integral a, Integral b, Bits a, Bits b, Bits c, FiniteBits c) => Show (GenericFixedPoint a b c) 
Storable flat => Storable (GenericFixedPoint flat i r) 
(Ord a, Bits a, Bits b, Integral a, Integral b, Bits c, FiniteBits c) => Bits (GenericFixedPoint a b c) 
NFData flat => NFData (GenericFixedPoint flat i r) 

newtype BigInt a Source

A type constructor for building 2^n bit signed ints. BigInt is normally just used as a wrapper around BigWord since twos-complement arithmatic is the same, we simply need to provide alternate show, read, and comparison operations.

Constructors

BigInt 

Fields

unBI :: a
 

Instances

(Bounded a, Ord a, Bits a, Num a, FiniteBits a) => Bounded (BigInt a) 
(Bits a, Ord a, Integral a, Bounded a, Num a, FiniteBits a) => Enum (BigInt a) 
Eq a => Eq (BigInt a) 
(Integral a, Bits a, Bounded a, FiniteBits a) => Integral (BigInt a) 
(FiniteBits a, Num a, Bits a, Ord a) => Num (BigInt a) 
(Ord a, Bits a, FiniteBits a) => Ord (BigInt a) 
(Num a, Bits a, Ord a, FiniteBits a) => Read (BigInt a) 
(FiniteBits a, Real a, Bounded a, Integral a, Bits a) => Real (BigInt a) 
(FiniteBits a, Show a, Num a, Bits a, Ord a) => Show (BigInt a) 
Storable a => Storable (BigInt a) 
(Bits a, Num a, Ord a, FiniteBits a) => Bits (BigInt a) 
(Ord a, Num a, FiniteBits a) => FiniteBits (BigInt a) 
NFData a => NFData (BigInt a) 

data BigWord a b Source

A type constuctor allowing construction of 2^n bit unsigned words The type variable represents half the underlying representation, so type Foo = BigWord Word13 would have a bit size of 26 (2*13).

Constructors

BigWord !a !b 

Instances

(Bounded a, Bounded b) => Bounded (BigWord a b) 
(Bounded a, Eq a, Num a, Enum a, Bounded b, Eq b, Num b, Enum b) => Enum (BigWord a b) 
(Ord a, Ord b) => Eq (BigWord a b) 
(Bounded a, Integral a, Bits a, FiniteBits a, Bounded b, Integral b, Bits b, FiniteBits b) => Integral (BigWord a b) 
(Integral a, Bits a, Num a, Ord a, Bounded a, Bits b, Num b, Ord b, Integral b, Bounded b, FiniteBits a, FiniteBits b) => Num (BigWord a b) 
(Ord a, Ord b) => Ord (BigWord a b) 
(Integral a, Num a, Bits a, Ord a, Bounded a, Integral b, Num b, Bits b, Ord b, Bounded b, FiniteBits a, FiniteBits b) => Read (BigWord a b) 
(Bits a, Real a, Bounded a, Integral a, Bits b, Real b, Bounded b, Integral b, FiniteBits a, FiniteBits b) => Real (BigWord a b) 
(Bounded a, Bits a, Integral a, FiniteBits a, Bounded b, Bits b, Integral b, FiniteBits b) => Show (BigWord a b) 
(Storable a, Storable b) => Storable (BigWord a b) 
(Ord a, Bits a, Integral a, Bounded a, Ord b, Bits b, Integral b, Bounded b, FiniteBits b, FiniteBits a) => Bits (BigWord a b) 
(Bounded a, Bounded b, FiniteBits a, FiniteBits b, Ord b, Ord a, Integral b, Integral a) => FiniteBits (BigWord a b) 
(NFData a, NFData b) => NFData (BigWord a b) 

Helpers

fracBits :: FiniteBits c => GenericFixedPoint a b c -> Int Source

Obtain the number of bits used to represent the fractional component of this fixed point.