Here is some simple benchmark for Int vs Integer performance.
In the system i use, it gives the time ratio Integer/Int
(for the whole task) = 4.5.
The difference is obtained only by switching Z = Integer, Int.
------------------
Sergey Mechveliani
[EMAIL PROTECTED]
------------------------------------------------------------------
type Z = Integer --Int
main = -- compute extended gcd for many x,y and sum the results
let
(d,n,m) = (40,5000,10000) :: (Z,Z,Z)
ns = [n..(n+d)]
ms = [m..(m+d)]
pairs = [(x,y)| x<-ns, y<-ms]
tripls = map (\ (x,y)->(x,y,gcdE x y)) pairs
s = sum (map (\ (_,_,(d,u,v))->d+u-v) tripls)
--boo = all test tripls --this tests gcdE
in
putStr (shows s "\n")
-- gcdE x y -> (d,u,v): d = gcd(x,y) = u*x + v*y
gcdE :: Integral a => a -> a -> (a,a,a)
gcdE 0 y = (y,0,1)
gcdE x y = g (1,0,x) (0,1,y)
where
g (u1,u2,u3) (v1,v2,v3) =
if v3==0 then (u3,u1,u2)
else
case quotRem u3 v3
of
(q,r) -> g (v1,v2,v3) (u1-q*v1, u2-q*v2, r)
test (x,y,(d,u,v)) = d==(u*x+v*y) && d==(gcd x y)