GHC with MS .Net 2003 C compiler

Manuel M T Chakravarty chak at cse.unsw.edu.au
Thu Oct 16 16:02:13 EDT 2003


Andreas.Schroeder at 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#AEN5918

> 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


More information about the Glasgow-haskell-users mailing list