#1687: A faster (^)-function.
----------------------------------------+-----------------------------------
  Reporter:  [EMAIL PROTECTED]  |          Owner:         
      Type:  bug                        |         Status:  new    
  Priority:  normal                     |      Milestone:         
 Component:  Compiler                   |        Version:  6.6.1  
  Severity:  normal                     |       Keywords:         
Difficulty:  Unknown                    |             Os:  Unknown
  Testcase:                             |   Architecture:  Unknown
----------------------------------------+-----------------------------------
This function performs better for me than the `(^)`-function in GHC. I
 seem to only be able to test it for the Integer type though and its only
 tested with ghc 6.6 (and ghc 6.6.1 by byorgey on #haskell).
 I'm not sure if you really need this or if it is correct, but after
 discussion on #haskell i was asked to make a bug report so here it is!
 Enjoy. :)

 {{{
 module Pow (pow) where
 import Prelude hiding ((^))
 pow = (^)

 (^) :: (Integral b, Num a) => a -> b -> a
 x ^ y | y < 0     = error "Negative exponent"
       | y == 0    = 1
       | y == 1    = x
       | odd y     = x * x^(y - 1)
       | otherwise = let x' = x^(y `div` 2)
                     in x' * x'
 }}}

 Tests

 {{{
 -- TestData.hs
 module TestData where
 e = 10^8
 }}}
 {{{
 -- mytest.hs
 import Pow
 import TestData
 main = print $ (2 `pow` e) `mod` 2
 }}}
 {{{
 -- ghctest.hs
 import TestData
 main = print $ (2 ^ e) `mod` 2
 }}}

 Test results (performance)
 {{{
 $ time ./ghctest
 0

 real    0m11.744s
 user    0m11.449s
 sys     0m0.104s

 $ time ./mytest
 0

 real    0m6.794s
 user    0m6.696s
 sys     0m0.084s

 -}
 }}}

 QuickCheck test
 {{{
 -- qc.hs
 -- $ ./qc
 -- OK, passed 100 tests.

 import Test.QuickCheck
 import Pow

 main = quickCheck prop
 prop x y = y >= 0 ==> x `pow` y == x^y
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/1687>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to