[Haskell-cafe] Half-integer

Andrew Coppin andrewcoppin at btinternet.com
Sun Jun 28 09:24:30 EDT 2009


I just wrote a small module for dealing with half-integers. (That is, 
any number I/2 where I is an integer. Note that the set of integers is a 
subset of this; Wikipedia seems to reserve "half-integer" for such 
numbers that are *not* integers.)

  module HalfInteger where

  data HalfInteger i

  instance (Eq i) => Eq (HalfInteger i)
  instance (Ord i) => Ord (HalfInteger i)
  instance (Integral i) => Show (HalfInteger i)
  instance (Integral i) => Num (HalfInteger i)

  half :: (Num i) => HalfInteger i

  fromNum :: (Integral i, RealFrac x) => x -> HalfInteger i
  toNum :: (Integral i, Fractional x) => HalfInteger i -> x

  isInteger :: (Integral i) => HalfInteger i -> Bool

Note carefully that the set of half-integers is *not* closed under 
multiplication! This means that for certain arguments, there are two 
reasonable products that could be returned. (E.g., 1/2 * 1/2 = 1/4, so 0 
or 1/2 would be a reasonable rounding.) I haven't put a lot of effort 
into the rounding details of (*) or fromNum; which answer you get is 
kind of arbitrary. (However, addition and subtraction are exact, and for 
multiplications where an exact result is possible, you will get that 
result.)

The Show instance outputs strings such as

  fromInteger 5
  fromInteger 5 + half
  fromInteger (-5) - half

depending on the isInteger predicate.

Now, the question is... Is this useful enough to be worth putting on 
Hackage?



More information about the Haskell-Cafe mailing list