Hello all – I’m trying to debug a problem with asinh in Windows.

 

On Linux (Ubuntu 18.04.5 LTS) running GHC 8.10.7, I get (I think correctly):

 

GHCi, version 8.10.7: https://www.haskell.org/ghc/  :? for help

Prelude> asinh 1.7976931348623157e308

710.4758600739439

 

But on Windows I get:

 

GHCi, version 8.10.7: https://www.haskell.org/ghc/  :? for help

Prelude> asinh 1.7976931348623157e308

NaN

 

My understanding is that, since commit c6f4eb4f8 (released in GHC 8.8.1, I think), asinh is defined as a primop that just calls the c asinh function, so I tried the following code:

 

In Main.hs:

 

{-# LANGUAGE ForeignFunctionInterface #-}

{-# LANGUAGE CApiFFI #-}

 

module Main (main) where

 

import Foreign

import Foreign.C.Types

 

foreign import ccall unsafe "math.h   asinh"   c_asinh      :: Double -> Double

foreign import ccall unsafe "CAsinh.c testFn"  c_testFn     :: IO ()

 

main :: IO ()

main = do

  putStrLn $ "asinh   1.7976931348623157e308 = " ++ show (  asinh 1.7976931348623157e308)

  putStrLn $ "c_asinh 1.7976931348623157e308 = " ++ show (c_asinh 1.7976931348623157e308)

 

  putStrLn "Calling c_testFn..."

  c_testFn

 

In CAsinh.c:

 

#include <stdio.h>

#include <math.h>

 

void testFn ()

{

  printf ("in testFn\n");

 

  printf ("asinh(1.7976931348623157e308) = %f\n", asinh(1.7976931348623157e308));

 

  double x = 1.7976931348623157e308;

  printf ("asinh(x) = %f\n", asinh(x));

}

 

In Linux, this all works fine:

 

asinh   1.7976931348623157e308 = 710.4758600739439

c_asinh 1.7976931348623157e308 = 710.4758600739439

Calling c_testFn...

in testFn

asinh(1.7976931348623157e308) = 710.475860

asinh(x) = 710.475860

 

But on Windows I get weird results:

 

asinh   1.7976931348623157e308 = NaN

c_asinh 1.7976931348623157e308 = NaN

Calling c_testFn...

in testFn

asinh(1.7976931348623157e308) = 710.475860

asinh(x) = -1.#IND00

 

The primop call from Haskell to asinh and the FFI call to c_asinh give the same (incorrect) result, as I expected. But the first call to asinh from the c testFn gives the correct result. So why is that different to the FFI call from Haskell?

 

And why doesn’t the second call from testFn return the right result?

 

I also tested on 9.0.1 on Windows, with a slightly different result for the final asinh:

 

...

asinh(x) = nan

 

I’ve investigated the things I can think of (different foreign declarations, size of double being different, checking the code in cpp.sh), but can’t find an explanation. Am I doing something silly? Is this a (known) bug?

 

Note that on Windows, values up to asinh 1.3407807929942596e154 work correctly.

 

(As a little background: I was trying to implement the Kahan functions to give the correct branch cuts for complex trig functions, something I think the current Haskell implementation doesn’t do correctly. These depend on asinh, etc, on RealFloat numbers).

 

Thanks very much for any help,

David.