[Haskell-cafe] gcd

Steve stevech1097 at yahoo.com.au
Fri May 1 22:05:17 EDT 2009


[Question moved over from Haskell-Beginners]

I had a look at the gcd definition in GHC 6.10.1
ghc-6.10.1/libraries/base/GHC/Real.lhs

-- | @'gcd' x y@ is the greatest (positive) integer that divides both
@x@
-- and @y@; for example @'gcd' (-3) 6@ = @3@, @'gcd' (-3) (-6)@ = @3@,
-- @'gcd' 0 4@ = @4 at .  @'gcd' 0 0@ raises a runtime error.
gcd             :: (Integral a) => a -> a -> a
gcd 0 0         =  error "Prelude.gcd: gcd 0 0 is undefined"
gcd x y         =  gcd' (abs x) (abs y)
                   where gcd' a 0  =  a
                         gcd' a b  =  gcd' b (a `rem` b)

Why is gcd 0 0 undefined?

http://en.wikipedia.org/wiki/Greatest_common_divisor says:
"It is useful to define gcd(0, 0) = 0 and lcm(0, 0) = 0 because then the
natural numbers become a complete distributive lattice with gcd as meet
and lcm as join operation. This extension of the definition is also
compatible with the generalization for commutative rings given below."

An added advantage, for haskell, of defining gcd 0 0 = 0 is that gcd
would change from being a partial function to a total function.

Regards,
Steve




More information about the Haskell-Cafe mailing list