Implementation of scaled integers

Hi all, is there a library for Haskell that implements scaled integers, i.e. integers with a fixed scale factor so that the scale factor does not need to be stored, but is part of the type? In particular it would be useful (i.e. for signal processing) to have numbers based on Int scaled such that they fall into the range [-1.0 .. 1.0). Or other scale factors which are powers of 2. Addition and subtraction would then map to the ordinary operations for Int, while Multiplication and Division would have to apply the scale factor to correct the result of normal Int operations (which would be a shift operation). If it doesn't exist yet, have you got ideas how to implement that for maximum efficiency? Cheers Stefan

The tricky part to get efficient is multiply and divide. Say you pick Int32 as the underlying type, when multiplying you really want the 64 bit result and then scale that. AFAIK, there are no such primitives exposed to the user. What you can do is cast to 64 bit, multiply, shift, and cast back again. It shouldn't be too bad. As for having the scale factor be part of the type, that shouldn't be a problem. -- Lennart On Feb 13, 2007, at 19:15 , Stefan Heinzmann wrote:
Hi all,
is there a library for Haskell that implements scaled integers, i.e. integers with a fixed scale factor so that the scale factor does not need to be stored, but is part of the type?
In particular it would be useful (i.e. for signal processing) to have numbers based on Int scaled such that they fall into the range [-1.0 .. 1.0). Or other scale factors which are powers of 2. Addition and subtraction would then map to the ordinary operations for Int, while Multiplication and Division would have to apply the scale factor to correct the result of normal Int operations (which would be a shift operation).
If it doesn't exist yet, have you got ideas how to implement that for maximum efficiency?
Cheers Stefan
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 2/13/07, Stefan Heinzmann
Hi all,
is there a library for Haskell that implements scaled integers, i.e. integers with a fixed scale factor so that the scale factor does not need to be stored, but is part of the type?
In particular it would be useful (i.e. for signal processing) to have numbers based on Int scaled such that they fall into the range [-1.0 .. 1.0). Or other scale factors which are powers of 2. Addition and subtraction would then map to the ordinary operations for Int, while Multiplication and Division would have to apply the scale factor to correct the result of normal Int operations (which would be a shift operation).
If it doesn't exist yet, have you got ideas how to implement that for maximum efficiency?
What you're looking for is usually referred to as "fixed point arithmetic", sadly the term "fixed point" when talking about functional languages means something entirely different so it's a bit tricky to google for it! :-) As for implementation tips, I would recommend that you take a look at Data.Bits for shifting (assuming that the scaling factor is a power of two). The only caveat is that when you perform the "(a<< s)/b" and "(a*b)>>s" operations that you need for multiplication and division, the inner multiplication/shift needs to have enough precision in its result value to avoid overflow (i.e. for Int32, you'll need to use a multiplication which has a 64 bit result type -- probably easiest to just convert both operands to Int64 before multiplying). -- Sebastian Sylvan +46(0)736-818655 UIN: 44640862

Stefan Heinzmann wrote:
Hi all,
is there a library for Haskell that implements scaled integers, i.e. integers with a fixed scale factor so that the scale factor does not need to be stored, but is part of the type?
Data.Fixed [1] does exactly that, only it is based on Integer. Using fixed point with finite sized integers is more tricky, because you have to be careful not to get overflows in intermediate results. Twan [1] http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Fixed.html

On Tue, 13 Feb 2007, Twan van Laarhoven wrote:
Stefan Heinzmann wrote:
Hi all,
is there a library for Haskell that implements scaled integers, i.e. integers with a fixed scale factor so that the scale factor does not need to be stored, but is part of the type?
Data.Fixed [1] does exactly that, only it is based on Integer. Using fixed point with finite sized integers is more tricky, because you have to be careful not to get overflows in intermediate results.
Is it a good idea to put the HasResolution type class and the types E6 and E12 in Data.Fixed? They are useful for every application where integers shall be encoded in types.

Stefan Heinzmann wrote:
is there a library for Haskell that implements scaled integers, i.e. integers with a fixed scale factor so that the scale factor does not need to be stored, but is part of the type?
I dimly remember that there has been some work done on this in connection with (and by the creator of) the new time package. Can't remember any specifics, though. Ben

Stefan Heinzmann wrote:
is there a library for Haskell that implements scaled integers, i.e. integers with a fixed scale factor so that the scale factor does not need to be stored, but is part of the type?
In particular it would be useful (i.e. for signal processing) to have numbers based on Int scaled such that they fall into the range [-1.0 .. 1.0). Or other scale factors which are powers of 2. Addition and subtraction would then map to the ordinary operations for Int, while Multiplication and Division would have to apply the scale factor to correct the result of normal Int operations (which would be a shift operation).
I'm answering myself, as I've come up with a naïve and probably embarrassing first try, which I'm presenting here below so that I can improve my (so far very limited) Haskell skills. Division isn't efficient yet, I just wanted some solution to allow trying it out. I'm sure this can be improved a lot, either in style or in efficiency. So please comment. Cheers Stefan --------------------------------------------------------------------- module ShiftedInt (Int0B31) where import Data.Int import Data.Bits import Data.Ratio data Int0B31 = Int0b31 Int32 instance Show Int0B31 where show (Int0b31 a) = show ((fromIntegral a) * sfD) instance Fractional Int0B31 where fromRational a = Int0b31(fromInteger(quot((numerator a)*sfI) (denominator a))) (/) (Int0b31 a) (Int0b31 b) = fromRational ((fromIntegral a) % (fromIntegral b)) instance Num Int0B31 where negate (Int0b31 a) = Int0b31 (negate a) abs (Int0b31 a) = Int0b31 (abs a) signum (Int0b31 a) = Int0b31 (signum a) fromInteger a = Int0b31 (fromInteger a) (+) a b = a + b (*) (Int0b31 a) (Int0b31 b) = Int0b31 (mul64 (fromIntegral a) (fromIntegral b)) instance Ord Int0B31 where (<=) (Int0b31 a) (Int0b31 b) = a <= b instance Eq Int0B31 where (==) (Int0b31 a) (Int0b31 b) = a == b mul64 :: Int64 -> Int64 -> Int32 mul64 a b = fromIntegral ((a * b) `shift` shiftamount) sfD = 2.0 ^^ shiftamount sfI = 2 ^ (-shiftamount) shiftamount = -31 ---------------------------------------------------------------------

On Tue, 13 Feb 2007, Stefan Heinzmann wrote:
Hi all,
is there a library for Haskell that implements scaled integers, i.e. integers with a fixed scale factor so that the scale factor does not need to be stored, but is part of the type?
I have implemented them in a generic way for NumericPrelude type classes: http://darcs.haskell.org/numericprelude/src/Number/FixedPoint.hs So far, I have only the interface http://darcs.haskell.org/numericprelude/src/Number/FixedPoint/Check.hs where the denominator is stored in the numbers and checked for each operation. But it would be easy to add another interface which retrieves the denominator from the type.
participants (6)
-
Benjamin Franksen
-
Henning Thielemann
-
Lennart Augustsson
-
Sebastian Sylvan
-
Stefan Heinzmann
-
Twan van Laarhoven