[Haskell-cafe] Perl-style numeric type

Henning Thielemann lemming at henning-thielemann.de
Wed Jun 20 14:03:12 EDT 2007


On Wed, 20 Jun 2007, Brent Yorgey wrote:

> isSquare :: (Integral a) => a -> Bool
> isSquare n = (floor . sqrt $ fromIntegral n) ^ 2 == n
>
> Is there any way to write that without the fromIntegral?  If you leave out
> the fromIntegral and the explicit type signature, it type checks, but the
> type constraints are such that there are no actual types that you can call
> it on.

This is a good example: You wonder, whether fromIntegral can be avoided. I
wonder, whether fromIntegral fulfills the task at all. Actually, it does
not. It fails for big integers, because there is no Double that represents
10^1000. That is you have to rescale the number. Even below this number,
'isSquare' will fail due to rounding errors:

Prelude> isSquare ((10^100)^2)
False

 That is, 'isSquare' does not do what it promises.

Btw. I would at least use 'round' because the Double sqrt might be
slightly below the true root.

Unfortunately we don't have access to the native sqrt implementation of
the GNU multiprecision library GMP so we have to roll our own version:

(^!) :: Num a => a -> Int -> a
(^!) x n = x^n

{- |
Compute the floor of the square root of an Integer.
-}
squareRoot :: Integer -> Integer
squareRoot 0 = 0
squareRoot 1 = 1
squareRoot n =
   let twopows = iterate (^!2) 2
       (lowerRoot, lowerN) =
          last $ takeWhile ((n>=) . snd) $ zip (1:twopows) twopows
       newtonStep x = div (x + div n x) 2
       iters = iterate newtonStep (squareRoot (div n lowerN) * lowerRoot)
       isRoot r  =  r^!2 <= n && n < (r+1)^!2
   in  head $ dropWhile (not . isRoot) iters



Btw. I think that 'squareRoot' is the basic problem and I'd like to change
the Wiki article accordingly.


More information about the Haskell-Cafe mailing list