fixed-point-0.4.0.1: Binary fixed-point arithmetic

Data.Fixed.Binary

Description

This module defines a type for binary fixed-point arithmetic. The main advantage this provides over decimal fixed-point arithmetic is that the point is maintained using fast bit shifts instead of slow div operations. This type is also polymorphic on the underlying representation, so you can use whatever size and signedness you want.

Synopsis

Documentation

div' :: (Real a, Integral b) => a -> a -> b

generalisation of div to any instance of Real

mod' :: Real a => a -> a -> a

generalisation of mod to any instance of Real

divMod' :: (Real a, Integral b) => a -> a -> (b, a)

generalisation of divMod to any instance of Real

data Fixed r a Source

The first type parameter represents the number of bits to devote to the fractional part of the number. The second type parameter is the underlying representation. For example, Fixed E8 Int16 uses eight bits for the integer component (of which one bit is used for the sign) and eight bits for the fractional component.

Instances

class SuperTypeable a whereSource

Instances of SuperTypeable can be cast up to and down from a supertype. If the type is bounded, the supertype must be able to hold at least twice as much information to be a valid instance.

Associated Types

type Super a Source

Methods

superCast :: a -> Super aSource

Losslessly cast to a supertype.

subCast :: Super a -> aSource

Cast to a subtype. Information may be lost.

class HasResolution r whereSource

Instances of this class are useful as the first parameter of Fixed.

Methods

resolution :: Num a => Fixed r a -> IntSource

Given a fixed-point number, give the number of bits used to represent its fractional part.

data E0 Source

Instances

type E1 = S E0Source

type E2 = E1 :+ E1Source

type E4 = E2 :+ E2Source

type E8 = E4 :+ E4Source

type E10 = S (S E8)Source

type E16 = E8 :+ E8Source

data S n Source

Increment a resolution

Instances

type family P a Source

Decrement a resolution

fixedRadix :: (Integral a, Num b) => Fixed r a -> Fixed r bSource

Fast conversion between fixed-point numbers with the same fractional size.

fixedSize :: (HasResolution r, HasResolution s, Bits a) => Fixed r a -> Fixed s aSource

Fast conversion between fixed-point numbers with the same representation size.

fromRealFloat :: (RealFloat a, HasResolution r, Num b) => a -> Fixed r bSource

Fast conversion from floating-point to fixed-point.

type family a :+ b Source

Add resolutions

(*.) :: (Num (Super a), SuperTypeable a) => Fixed r a -> Fixed s a -> Fixed (r :+ s) aSource

Multiplication without throwing away fractional information.

(*!) :: (HasResolution r, Bits a, Num a) => Fixed r a -> Fixed r a -> Fixed r aSource

Perform a multiplication without adding any extra bits for the intermediate steps. This may be faster (especially when you are already working with native-sized integer data), but it's only safe to use if you are sure that the multiplication won't overflow. Normal multiplication is equivalent to x y -> subCast (superCast x *! superCast y).

type family a :- b Source

Subtract resolutions

(/.) :: Integral a => Fixed r a -> Fixed s a -> Fixed (r :- s) aSource

Division while removing unnecessary bits in the result's fractional part.

(/!) :: (HasResolution r, Bits a, Integral a) => Fixed r a -> Fixed r a -> Fixed r aSource

Perform a division without adding any extra bits for the intermediate steps. This may be faster if supercasting brings it up to a non-native size, but you need to be sure that the shifting before the division won't cause an overflow.