Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

Mysterious crash

dondilworth
New Contributor II
879 Views

My Fortran code calls some subroutines that call others, and the chain ends up in some C++ code that draws lines on the screen.  Occasionally it crashes.  In debug mode I see the message Run-Time Check Failure #0 -- The value of ESP was not properly saved across a function call ....

Could this be causing the crash in release mode?  I use the same subroutines, called from elsewhere, with no problems.

 

 

 

0 Kudos
1 Solution
mecej4
Honored Contributor III
879 Views

Does the description given at https://support.microsoft.com/en-us/kb/822039 seem relevant to the problem described in #1? Does the crash occur only when among the actual arguments you have an array larger than 64 kB?  If so, you may wish to go through the ritual of reproducing the problem as described there, and use the knowledge gained from the exercise to avoid the same issues in your code. It is possible that using a more recent VC compiler or using a different C compiler will make the problem go away.

View solution in original post

0 Kudos
9 Replies
Steven_L_Intel1
Employee
879 Views

Yes, that could be an indicator of a problem. Usually this is due to a mismatch of calling mechanisms - C vs, STDCALL. What happens is that the stack gets corrupted - whether you notice a problem or not depends on how the program uses the stack, but the problem is still there. What Fortran compile options are you using? How is the C++ procedure declared (what is its prototype in C++ and how do you declare it in Fortran?)

0 Kudos
dondilworth
New Contributor II
879 Views

It could be related to my use of OpenGL code.  Here is how my Fortran handles it:

REAL XOGL,YOGL,ZOGL

    INTERFACE TO SUBROUTINE startOGLPolyStrip[C,ALIAS:'_startOGLPolyStrip'] (X, Y, Z)
        REAL X [VALUE]
        REAL Y [VALUE]
        REAL Z [VALUE]
    END

...

CALL startOGLPolyStrip( XOGL, YOGL, ZOGL )

In my C++ code:

extern "C" void startOGLPolyStrip( float x, float y, float z );

void startOGLPolyStrip( float x, float y, float z )
{
    myOGLView->OGLstartPolyStrip( x, y, z );
}

...

#include "freeglut.h"

void CmyOGLView::OGLstartPolyStrip(float x, float y, float z)    // start
{
    m_vertexCount = 0;
    glBegin( GL_QUAD_STRIP );

    updatePanelColor();
    OGLaddPolyStrip( x, y, z );
}

The funny thing is, when it crashes, the debugger points to the END statement of the Fortran code, not somewhere in the C++.  So OpenGL may not be involved in the crash.  Here's my command line:

/nologo /debug:full /MP /Od /I"Debug/" /reentrancy:none /extend_source:132 /Qopenmp /Qopenmp-report1 /warn:unused /warn:truncated_source /Qauto /align:rec4byte /align:commons /assume:byterecl /Qtrapuv /Qzero /fpe:1 /fp:strict /Qfp_port /fpconstant /Qftz /iface:cvf /module:"Debug/" /object:"Debug/" /traceback /check:all /libs:dll /threads /winapp /c

Let me know what you find, please.

0 Kudos
Steven_L_Intel1
Employee
879 Views

Wow - old PowerStation code (INTERFACE TO). You are corrupting the stack because you build with /iface:cvf, that tells the compiler to use the STDCALL convention, but your use of ALIAS papers that over as the C++ code uses the C convention. Try removing /iface:cvf on the Fortran build and see what happens.

0 Kudos
dondilworth
New Contributor II
879 Views

Steve:

I tried that.  If I select any option other than CVF, I get a zillion errors such as

Error    136     error #5528: The REFERENCE attribute cannot be used with a passed length CHARACTER variable on this platform    C:\SYNOPSYSV14\GlassTable.for    2187   

My program has nearly 700 subroutines and I'm not eager to rework the call lists for the whole mess.  Well, maybe not "mess", but it's spaghetti code for sure.  Any other ideas?  Remember, the crash is intermittent; if I restart and run the same features again, it always works.  Does that give you any clues?

0 Kudos
JVanB
Valued Contributor II
879 Views

I don't think there is a mismatch here. The 'C' keyword before the ALIAS (where is this documented in the ifort manual? Under INTERFACE TO there is just one brief unexplained example with a typo [C. instead of [C.) seems to override the /iface:cvf. Here is a test file:

subroutine S
INTERFACE TO SUBROUTINE Sub[C,ALIAS:'_Sub'] (X)
   REAL X
END
   integer i
   real x
   do i = 1, 10
      call sub(x)
   end do
end subroutine S

If I compile with ifort /FA /c /iface:cvf fps.f90 the inner loop reads:

.B1.2:                          ; Preds .B1.3 .B1.1
        push      esi                                           ;9.12
        call      _Sub                                          ;9.12
                                ; LOE ebx ebp esi edi
.B1.7:                          ; Preds .B1.2
        add       esp, 4                                        ;9.12
                                ; LOE ebx ebp esi edi
.B1.3:                          ; Preds .B1.7
        inc       edi                                           ;10.4
        cmp       edi, 10                                       ;10.4
        jle       .B1.2         ; Prob 90%                      ;10.4

That add esp, 4 instruction is the caller cleaning up the stack, so it's using the C calling convention. If you change that [C, to [STDCALL, then that instruction goes away, consistent with the STDCALL convention. My conclusion is that the calling convention in the INTERFACE TO statement overrides that requested on the command line.

 

0 Kudos
Steven_L_Intel1
Employee
879 Views

You're probably right about that, RO. Thanks for pointing it out.

Given that, I don't know what is wrong without seeing a full test case. The error message does suggest a convention mismatch somewhere.

0 Kudos
dondilworth
New Contributor II
879 Views

I have new information.  my code calls a subroutine as follows:

        CALL SEDGE(SSIN,SCOS,JXC,JREC,JSLS,MM)  ! THIS GIVES AN ESP ERROR MESSAGE!

Arrays SSIN and SCOS are real values of dimension 301 (via the parameter NBANG).  The other arguments are integers.  This CALL happens from many places in my code with the same arguments and never gives an error message -- except in one place.  The error then shows up even if the first statement in SEDGE is a RETURN statement.  So that subroutine is then not doing anything.  Here is the start of SEDGE:

    SUBROUTINE SEDGE(SSIN,SCOS,JREC,JSLS,MM)
C DRAWS EDGES FOR SOLID

    IMPLICIT DOUBLE PRECISION (A-H,O-Z)
    SAVE
      INCLUDE 'LENS200.INC'
    PARAMETER (MXIY=1800,MXJX=1400)
    COMMON/A/KIN,KOUT,I1DUM,I2DUM,JDATSW(110),ISFLAGS(250),SFLAGS(250),JCONF
    REAL SSIN,SCOS
    REAL XOGL,YOGL,ZOGL
    LOGICAL TPL(0:NBANG)
    COMMON/PERCOM/SXPL(0:NBANG),SYPL(0:NBANG),SXPLO(0:NBANG),SYPLO(0:NBANG),ZHOLD,ISHADE(NBANG),TPL,JCFLAG(0:NBANG)
    REAL ZPIX(MXIY,MXJX),PIXV(MXIY,MXJX)
    INTEGER*4 CPIX(MXIY,MXJX)
    COMMON/HUGEARRAY/PIXV,ZPIX,CPIX
    LOGICAL ISOPENGLPANELS
    COMMON/OGL/IRED(7),IBLUE(7),IGREEN(7),LENSR(NS),LENSB(NS),LENSG(NS),ISN,JOPENGLSTRIP,ISOPENGLPANELS
    LOGICAL ISCUT,ISOPENGL
    COMMON/SOLIDC/SZPL(0:NBANG),SZPLO(0:NBANG),
     $GCA(NS),GCB(NS),GCC(NS),GCD(NS),GCE(NS),GCF(NS),
     $GCG(NS),GCH(NS),GCI(NS),GCJ(NS),GCK(NS),GCL(NS),JGREY,ISCUT,JTHISR,JTHISB,JTHISG,ISOPENGL,CMFUDGE
    REAL XOGLPOLY(5),YOGLPOLY(5),ZOGLPOLY(5)
    DIMENSION SSIN(NBANG),SCOS(NBANG)

    INTERFACE TO SUBROUTINE startOGLPolyStrip[C,ALIAS:'_startOGLPolyStrip'] (X, Y, Z)
        REAL X [VALUE]
        REAL Y [VALUE]
        REAL Z [VALUE]
    END

    INTERFACE TO SUBROUTINE addOGLPolyStrip[C,ALIAS:'_addOGLPolyStrip'] (X, Y, Z)
        REAL X [VALUE]
        REAL Y [VALUE]
        REAL Z [VALUE]
    END

    INTERFACE TO SUBROUTINE endOGLPolyStrip[C,ALIAS:'_endOGLPolyStrip'] ()
    END
    INTERFACE TO SUBROUTINE changeOGLpen[C,ALIAS:'_changeOGLpen'] (X, Y, Z, A)
        REAL X [VALUE]
        REAL Y [VALUE]
        REAL Z [VALUE]
        REAL A [VALUE]
    END
    INTERFACE TO SUBROUTINE addOGLQuad[C,ALIAS:'_addOGLQuad'] (X1,Y1,Z1, X2,Y2,Z2, X3,Y3,Z3, X4,Y4,Z4)
        REAL X1 [VALUE]
        REAL Y1 [VALUE]
        REAL Z1 [VALUE]
        REAL X2 [VALUE]
        REAL Y2 [VALUE]
        REAL Z2 [VALUE]
        REAL X3 [VALUE]
        REAL Y3 [VALUE]
        REAL Z3 [VALUE]
        REAL X4 [VALUE]
        REAL Y4 [VALUE]
        REAL Z4 [VALUE]
    END

C THIS SECTION DRAWS EDGES BETWEEN DATA POINTS SXPL, SXPLO
C JREC = 0 FOR CIRCLE EDGE
C       1 FOR RAO
C       2 AND UP FOR PRISM FAKE RAO'S

C CAOs:
C JSLS + KOS = 37     START POINT FOR EDGE DARKNESS GRADIENT IN COSINE CURVE
C JSLS - KOS = 62
C JSLS = 2; IS BEVEL, FIX BRIGHTNESS
C JSLS 0 KOS = 0

C ISHADE(J) = 0 USE ABOVE RULES
C            1 FIXED LEVEL FOR FLAT EDGES FOR COMBO

C RAO EFILE MIRRORS:
C JSLS =    1    FLAT AB
C        2    BEVEL BC
C        3    CYLINDER AT C
C        4    BEVEL CD
C        5    FLAT ON BACK

C JXC + CLOCKWISE CIRCLE
C JXC - ANTICLOCKWISE

    IF (BTEST(IOPTD(ISN,JCONF),18)) RETURN    ! IS NOEDGE
      
     RETURN

...

In this test, none of the C++ routines identified by the INTERFACE sections ever get called.  Do you see anything suspicious?  I cannot.

0 Kudos
mecej4
Honored Contributor III
880 Views

Does the description given at https://support.microsoft.com/en-us/kb/822039 seem relevant to the problem described in #1? Does the crash occur only when among the actual arguments you have an array larger than 64 kB?  If so, you may wish to go through the ritual of reproducing the problem as described there, and use the knowledge gained from the exercise to avoid the same issues in your code. It is possible that using a more recent VC compiler or using a different C compiler will make the problem go away.

0 Kudos
dondilworth
New Contributor II
879 Views

Right on.  I removed the SSIN and SCOS from the argument list and the error vanished.  Many thanks for the prompt help!

0 Kudos
Reply