Re: GHC with MS .Net 2003 C compiler

Hi all, hi Seth, yes, you're right with the P4 optimizations of the MS .Net Compiler. My tests ran on a P4 1,7 GHz with 1 GB Ram. But anyway, an older C++ compiler (the 6.0 MSVC++ from... 1998?) did also better than Cygwin C++.
I haven't seen your code yet, but I have noticed in the path the Haskell is much more sensitive (compared to C++ and Java) to coding style.
Don't have to tell me, tell my colleages ;-) See, i am just trying to persuade them that using Haskell would save us a LOT of money. (And would let me finally use a language i like - the PL "nice" looks also well, though) Anyway, here comes the code. I am not using "Integer" for performance' sake. (I read about it somewhere...) Basically, this code does an iteration to do some "backward calculation" of interest rate and similar. Btw, i did not start to bother my colleages with logic programming :-) i know that this would work also. module AIBD(aibd, rechneZins, rechneRate, rechneKapital) where import Foreign(unsafePerformIO) type Funktion = Double -> Double data Genauigkeit = Absolut {wert, intervall :: Double} | Intervall Double istOk :: Genauigkeit -> Double -> Double -> Bool istOk (Absolut w i) x _ = abs (x-w) <= i istOk (Intervall i) _ dx = abs dx <= i sekantenVerfahren :: Funktion -> Genauigkeit -> Genauigkeit -> Int -> Double -> Double sekantenVerfahren f gx gy tiefe start = sekantenIter f tiefe gx gy x1 x2 y1 y2 where x1 = start x2 = start + start * 0.1 y1 = f x1 y2 = f x2 sekantenIter _ 0 _ _ _ x2 _ _ = x2 sekantenIter f tiefe gx gy x1 x2 y1 y2 = let x3 = x2 - y2 * (x2 - x1) / (y2 - y1) y3 = f x3 dy = y3 - y2 dx = x3 - x2 in if (istOk gx x3 dx) && (istOk gy y3 dy) then x3 else sekantenIter f (tiefe-1) gx gy x2 x3 y2 y3 foreign import ccall "HAIBDUtil.h caibd" caibd :: Double -> Double -> Double -> Int -> IO Double aibd:: Double -> Double -> Double -> Int -> Double aibd kapital zins rate jahre = unsafePerformIO (caibd kapital zins rate jahre) {- does the same than aibd:: Double -> Double -> Double -> Int -> Double aibd kapital _ _ 0 = kapital aibd kapital zins rate jahre = aibd (kapital + kapital * zins - rate) zins rate (jahre-1) -} rechneZins :: Double -> Double -> Int -> Double rechneZins kapital rate jahre = sekantenVerfahren f (Intervall 0.00001) (Absolut 0 0.001) 100 0.05 where f = \zins -> aibd kapital zins rate jahre rechneRate :: Double -> Double -> Int -> Double rechneRate kapital zins jahre = sekantenVerfahren f (Intervall 0.001) (Absolut 0 0.001) 100 start where start = kapital / (fromIntegral jahre) f = \rate -> aibd kapital zins rate jahre rechneKapital :: Double -> Double -> Int -> Double rechneKapital zins rate jahre = sekantenVerfahren f (Intervall 0.001) (Absolut 0 0.001) 100 start where start = rate * (fromIntegral jahre) f = \kapital -> aibd kapital zins rate jahre

Andreas.Schroeder@gillardon.de wrote, Generally, did you look at http://haskell.org/ghc/docs/latest/html/users_guide/faster.html
module AIBD(aibd, rechneZins, rechneRate, rechneKapital) where import Foreign(unsafePerformIO)
type Funktion = Double -> Double
data Genauigkeit = Absolut {wert, intervall :: Double} | Intervall Double
See the paragraph under "Use strictness annotations" on the above web page on how to use strictness annotations to speed this data type up.
istOk :: Genauigkeit -> Double -> Double -> Bool istOk (Absolut w i) x _ = abs (x-w) <= i istOk (Intervall i) _ dx = abs dx <= i
sekantenVerfahren :: Funktion -> Genauigkeit -> Genauigkeit -> Int -> Double -> Double sekantenVerfahren f gx gy tiefe start = sekantenIter f tiefe gx gy x1 x2 y1 y2 where x1 = start x2 = start + start * 0.1 y1 = f x1 y2 = f x2 sekantenIter _ 0 _ _ _ x2 _ _ = x2 sekantenIter f tiefe gx gy x1 x2 y1 y2 = let x3 = x2 - y2 * (x2 - x1) / (y2 - y1) y3 = f x3 dy = y3 - y2 dx = x3 - x2 in if (istOk gx x3 dx) && (istOk gy y3 dy) then x3 else sekantenIter f (tiefe-1) gx gy x2 x3 y2 y3
Code like this may benefit from using the option "-O2" and possibly also "-fliberate-case-threshold100" http://haskell.org/ghc/docs/latest/html/users_guide/flag-reference.html#AEN5...
foreign import ccall "HAIBDUtil.h caibd" caibd :: Double -> Double -> Double -> Int -> IO Double
aibd:: Double -> Double -> Double -> Int -> Double aibd kapital zins rate jahre = unsafePerformIO (caibd kapital zins rate jahre) {- does the same than aibd:: Double -> Double -> Double -> Int -> Double aibd kapital _ _ 0 = kapital aibd kapital zins rate jahre = aibd (kapital + kapital * zins - rate) zins rate (jahre-1) -}
Two comments with -O2 -fliberate-case-threshold100 the Haskell version may be as fast as the C version. If not, better foreign import as a pure functions foreign import ccall "HAIBDUtil.h caibd" caibd :: Double -> Double -> Double -> Int -> Double and omit the unsafePerformIO. Cheers, Manuel

Hi all,
Generally, did you look at http://haskell.org/ghc/docs/latest/html/users_guide/faster.html
I have to say that one advice is not perfect... "Don't use Floats: "...There's rarely a speed disadvantage -- "modern machines will use the same floating-point "unit for both. ... Assuming an i386 architecture, the way to get really faster code is 1. Use -fexcess-precision, unless you really need the exact (lesser) precision. Otherwise each intermediate result is spilled in memory. This hurts! 2. Use floats rather than doubles. You won't lose so much precision because all intermediate computations will use 80-bit precision. This saves some memory. Plus, GHC doesn't align on 64 bits, which slows down access to doubles. I've made up a simple benchmark with Andreas' code, using the pure haskell "aibd", with main: tt z = print $ sum $ map (\x -> rechneZins x 0.01 z) $ [1..10000] main = do tt 20 tt 21 ... tt 30 ghc -O2 -fglasgow-exts --make Main.hs, a.out runs in 7.82 secs. with -fexcess-precision, runs in 2.97secs; with Float instead of Double, runs in 2.72secs. This is with gcc 3.3.2, ghc 6.0.1, linux and a pentium4 arch. Just my 2 cents, JP. __________________________________ Do you Yahoo!? The New Yahoo! Shopping - with improved product search http://shopping.yahoo.com

G'day all.
Quoting JP Bernardy
1. Use -fexcess-precision, unless you really need the exact (lesser) precision. Otherwise each intermediate result is spilled in memory. This hurts!
Yes, but it does avoid incorrect numerics, which hurts fewer times, but when it does, it hurts a LOT more. :-) Using C, you can often get code like this: float x; if ((x = some_complex_expression()) < 0) { assert(x < 0); /* This assert can fail. */ } The reason is that x has 80 bits of precision when the first test is performed, but by the time you get to the second one, it has been truncated to 32 bits and is now == 0. Cheers, Andrew Bromage

--- ajb@spamcop.net wrote:
Quoting JP Bernardy
: 1. Use -fexcess-precision, unless you really need the exact (lesser) precision. Otherwise each intermediate result is spilled in memory. This hurts!
Yes, but it does avoid incorrect numerics, which hurts fewer times, but when it does, it hurts a LOT more. :-)
With an SSE processor, it is possible to have both speed and exact precision, passing -optc-march=pentium4 -optc-mfpmath=sse to ghc, in addition to -fexcess-precision. BTW, as requested, I've contributed a page about this to the haskell wiki. http://haskell.org/hawiki/FasterFloatingPointWithGhc Cheers, JP. __________________________________ Do you Yahoo!? The New Yahoo! Shopping - with improved product search http://shopping.yahoo.com

--- ajb@spamcop.net wrote:
Quoting JP Bernardy
: 1. Use -fexcess-precision, unless you really need the exact (lesser) precision. Otherwise each intermediate result is spilled in memory. This hurts!
Yes, but it does avoid incorrect numerics, which hurts fewer times, but when it does, it hurts a LOT more. :-)
With an SSE processor, it is possible to have both speed and exact precision, passing -optc-march=pentium4 -optc-mfpmath=sse to ghc, in addition to -fexcess-precision. BTW, as requested, I've contributed a page about this to the haskell wiki. http://haskell.org/hawiki/FasterFloatingPointWithGhc Cheers, JP. __________________________________ Do you Yahoo!? The New Yahoo! Shopping - with improved product search http://shopping.yahoo.com
participants (4)
-
ajb@spamcop.net
-
Andreas.Schroeder@gillardon.de
-
JP Bernardy
-
Manuel M T Chakravarty