GHC with MS .Net 2003 C compiler

Andreas.Schroeder at gillardon.de Andreas.Schroeder at gillardon.de
Tue Oct 14 19:16:58 EDT 2003


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




More information about the Glasgow-haskell-users mailing list