Topic: EXP function in dll crashing

I am stuck with a problem I am unable to solve:

- I have a exe which runs wonderfully. It uses a lot of intrinsic mathematical functions such as SQRT, ABS, EXP etc.
- Now I convert the exe to a dll. The dll compiles and links successfully. However, when I use the dll from another executable it would crash. My investigation lead me to the EXP calls. The point is that the call is a legal call with the right argument (the value being passed into EXP has a legitimate answer). When I comment out the EXP calls the program seems to work fine until it crashes due to unreasonable numbers resulting from not calculating EXP. Another thing I did was to add a SQRT just in front of the EXP call where the number passed into SQRT is not permitted (such as SQRT(-2)). IOn this situation the SQRT(-2) is calculated as NaN and program continues until it crashes at EXP.

I am really lost on why the EXP call works in EXE mode but not in DLL mode. While researching about this, I came to know that functions such as SQRT, ABS are calculated inline and functions like EXP requires run time libraries. Is this a reason? If so what run time libraries are needed. My gcc/gfortran is located in the path.

I am using Simply Fortran 1.45 (build 1256)

Any help will be greatly appreciated.

Regards
Sankar

Regards
skp

Re: EXP function in dll crashing

Sankar,

I'll  need to investigate this bug more fully.  I'm away on business for the weekend, but I'll be able to address your concerns this coming week. 

Another user reported issues with EXP for REAL*16 values even when statically linked.  It appears that the runtime library's EXP  function is a bit of a problem.

Jeff Armstrong
Approximatrix, LLC

Re: EXP function in dll crashing

Actually, square roots of negative numbers are sometimes permitted. Can you post any of the code?

--
David

4 (edited by drfrank 2014-04-13 19:30:44)

Re: EXP function in dll crashing

SF Users,

Regarding the gfortran EXP() function, I've had problems with some mathematical functions containing EXP()s.  Although I'm not sure if the problem is with the EXP() function or my regression algorithm, however I thought it was worth mentioning here.  On some occasions I've resorted to using the following algorithm in place of fortran's intrinsic EXP() function.

            Function VEXP(x)

            IMPLICIT REAL*8 (A-H,O-Z), INTEGER*4 (I-N)
            !
            REAL(dpr),INTENT(IN) :: x
            REAL(dpr) :: VEXP

            REAL(dpr) :: xx, E, F, G, H, B, C, D
            REAL(dpr) :: P, Q, R, A, AA, Y, Z, W
            INTEGER(lpr) :: I, K, N

            PARAMETER ( F = 0.50D0, G = 1.0D0, H = 0.D0 )
            PARAMETER ( P = 0.50D0, Q = 0.333333333333D0, R = 0.25D0 )
            PARAMETER ( B = 690.D0, C = 1.D-34, D = 1.D+35 )

            !--- Precision
            PARAMETER ( N = 9 )

            ALLOCATABLE A(:), W(:)

            E = 2.7182818284590452353602874713527D0

            xx = x

            !--- real, parameter:: inf= 1./0., nan= 0./0., minf= -1./0.0
            !--- NaN is never equal to anything
            IF ( xx .NE. xx ) xx = C

            !--- INFINITE(xx) = 1./0. IF xx IS INFINITE
            ! ERROR! >>> IF ( (xx + G) .EQ. xx ) xx = B <<<
            ! REPLACED 'G' WITH 'HUGE'
            IF ( (xx + HUGE(1.D308)) .EQ. xx ) xx = 690.D0

            If (DABS(xx) .LE. C) Then
                VEXP = G
                RETURN
            ElseIf (Abs(xx) .GE. B) Then
                IF ( xx .LT. H ) THEN
                    xx = -B
                    VEXP = C
                    RETURN
                ELSE
                    xx = +B
                    VEXP = D
                    RETURN
                END IF
            End If

            ALLOCATE( A(N), W(N) )

            !--- A(i) = DEXP(0.5**i)
            A(1) = 1.6487212707001281468486507878142D0
            A(2) = 1.2840254166877414840734205680624D0
            A(3) = 1.1331484530668263168290072278118D0
            A(4) = 1.0644944589178594295633905946429D0
            A(5) = 1.0317434074991026709387478152815D0
            A(6) = 1.0157477085866857474585350720824D0
            A(7) = 1.0078430972064479776934535597601D0
            A(8) = 1.0039138893383475734436096039035D0
            A(9) = 1.0019550335910028120465188980475D0

            K = INT(xx)
            xx = xx - DBLE(K)
            AA = F

            Z = xx
            DO I = 1, N
                W(I) = H
                IF ( Z .GT. AA ) W(I) = G
                Z = Z - W(I)*AA
                AA = F * AA
            END DO

            Y = G
            DO I = 1, N
                IF (W(I) .GT. H) Y = Y * A(I)
            END DO

            Y = Y*(G + Z*(G + P*Z * (G + Q*Z * (G + R*Z))))

            IF (K .LT. 0) E = G / E

            IF (ABS(K) .GE. 1) THEN
                DO I = 1, ABS(K)
                    Y = Y * E
                END DO
                xx = xx + K
            END IF

            VEXP = Y

            DEALLOCATE( A, W )

            End Function VEXP

Some SF users may find this useful, although slow.

Frank

Re: EXP function in dll crashing

Jeff:

Thank you for your assistance.

David:
The dll contains the following subroutine. This subroutine is then called from a different exe.

SUBROUTINE TryDll(Var1,Var2,Var3,Var4)

  !DEC$ ATTRIBUTES DLLEXPORT :: TryDLL
  
  REAL, INTENT(IN) :: Var1
  REAL, INTENT(IN) :: Var2
  REAL             :: ReturnResult
  
  REAL, INTENT(OUT) :: Var3
  REAL, INTENT(OUT) :: Var4
  
  Var3 = Add(Var1,Var2)
  ReturnResult = Subtract(Var1,Var2)
  Var4 = EXP(ReturnResult)

END SUBROUTINE

The above subroutine works well when called from the calling program as long as the argument to EXP is declared as REAL. But when I convert that to DOUBLE PRECISION, the subroutine crashes when called from outside exe.

I have the Options -> Compiler -> Use Double Precision for all REALS as checked.

Thank you for the help!!

Frank:

That routine looks interesting. Will try and let you know how it goes. Thanks

Regards
Sankar

Regards
skp

Re: EXP function in dll crashing

Jeff:

Any updates on the EXP function issue?

Thank you for your support.

Regards
skp

Re: EXP function in dll crashing

I've been experimenting with various configurations, and I can't personally get the wrong answer to occur when using a DLL.  However, my test case may be overly simple.  I do believe you are seeing an issue simply based on earlier reports of issues with quad-precision exponential calls.  I'm still looking into it further.

A new compiler version and accompanying runtime library will be coming soon that could fix the issue, but I wouldn't guarantee that it will.  I'll keep investigating.

Jeff Armstrong
Approximatrix, LLC