forums.silverfrost.com Forum Index forums.silverfrost.com
Welcome to the Silverfrost forums
 
 FAQFAQ   SearchSearch   MemberlistMemberlist   UsergroupsUsergroups   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

Insufficient Stack

 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> 64-bit
View previous topic :: View next topic  
Author Message
EKruck



Joined: 09 Jan 2010
Posts: 224
Location: Aalen, Germany

PostPosted: Thu Jan 04, 2018 7:05 pm    Post subject: Insufficient Stack Reply with quote

Hi,

What's to do with this error message?

Silverfrost exception report on ...
Insufficient virtual stak (FTN95 /VSTACK <MB-value>) at adress ...

I used :
FTN95 name.f90 /64 /no_banner /optimize /VSTACK 5000

Erwin
Back to top
View user's profile Send private message Visit poster's website
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7912
Location: Salford, UK

PostPosted: Thu Jan 04, 2018 7:44 pm    Post subject: Reply with quote

Erwin

I can't give you a quick answer.

Do you get the same result without /optimize?

Can you demonstrate the same error report with a small sample?

One use of the virtual stack is to pass an array via the name of a function in a call to a function. Are you using very large arrays in this way?
Back to top
View user's profile Send private message AIM Address
EKruck



Joined: 09 Jan 2010
Posts: 224
Location: Aalen, Germany

PostPosted: Fri Jan 05, 2018 8:16 am    Post subject: Reply with quote

Paul,

a small example is not possible. It's a large program with up to six theads. Only very few and really small arrays.

Without /optimize I get the same problem.

According to the error message it happens within this function:

Code:
    INTEGER FUNCTION WaitForProg (iSilent)                 ! Start program and wait for completion

    USE      ProcNameS
    IMPLICIT NONE
    INCLUDE  <clearwin.ins>
    INTEGER, INTENT(IN) :: iSilent

    CHARACTER   CTX*256, cPROGname*128, cPROGrunStr*128
    INTEGER     iStat
!- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    cPROGname   = PNameL
    cPROGrunStr = RunStr

    iStat = START_PROCESS_AND_WAIT@ ('"'//TRIM(cPROGname)//'"', TRIM(cPROGrunStr), -1)   !  -1: Wait;   0: Return immediately

    IF (INDEX(cPROGname, 'BingoMP') .GT. 1 .OR. INDEX(cPROGname, 'Bingo64') .GT. 1) THEN
       iStat = START_PROCESS_AND_WAIT@ ('PipeClose', ' ', -1)
    ENDIF

    WRITE (CTX(1:12),'(A8,2I2)') '_thread1', iSilent, iStat
    CTX(13:) = char(0)

    PNameL = cPROGname
    RunStr = cPROGrunStr
    CALL TextMsg (CTX)                                     ! Message to BINGO manager main thread function CB_GETXT

    WaitForProg = 1
    RETURN
    END FUNCTION WaitForProg

When compiling with /debug, the error message points to another function.

Without a solution I have to go another time back to 32 bits.
Back to top
View user's profile Send private message Visit poster's website
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7912
Location: Salford, UK

PostPosted: Fri Jan 05, 2018 9:08 am    Post subject: Reply with quote

I have made a note to look into this as soon as possible.
Back to top
View user's profile Send private message AIM Address
EKruck



Joined: 09 Jan 2010
Posts: 224
Location: Aalen, Germany

PostPosted: Fri Jan 05, 2018 9:20 am    Post subject: Reply with quote

Code:
  MODULE ProcNameS
   
    CHARACTER     PNameL*128    ! Process Name
    CHARACTER     RunStr*128    ! Run string

  END MODULE ProcNameS
Back to top
View user's profile Send private message Visit poster's website
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7912
Location: Salford, UK

PostPosted: Fri Jan 05, 2018 10:52 am    Post subject: Reply with quote

This failure report is generated from within one of two functions in salflibc64.dll. The two functions are __alloc_pseudo_stack and __alloc_quasi_stack. Both of these use a virtual stack.

You will be able to see these calls if you compile with /EXPLIST and then look at the resulting .LIS files (i.e. do a global search through the .LIS files).

You should also be able to see a traceback when your application fails. Hopefully this will indicate a failure in one or other of these two functions and also show the traceback to a routine in your code where the failure occurred.

The EXPLIST at this point might possibly be used to work out how much memory was requested and maybe why a failure occurred.

Since you are using multiple threads it may be useful to identify if the problem is limited to a particular thread and if there are any potential issues regarding thread safety. In particular the two stack functions mentioned above are not thread safe. So any Fortran feature (like passing arrays as function values) that uses the virtual stack should be avoided within a thread.
Back to top
View user's profile Send private message AIM Address
EKruck



Joined: 09 Jan 2010
Posts: 224
Location: Aalen, Germany

PostPosted: Fri Jan 05, 2018 2:10 pm    Post subject: Reply with quote

Thank you for your hints. I made several tests; then
Funny: I added some write statements and the probram works fine !?
Code:
    INTEGER FUNCTION StartModule (ProgName, ParamString, Key)

    USE      bbmanData
    USE      GlobalData
    IMPLICIT NONE
    INCLUDE  <win32api.ins>
    CHARACTER*(*), INTENT(IN) :: ProgName, ParamString, Key

    INTEGER*4  J
    LOGICAL    L
    INTEGER, EXTERNAL :: ModStart, ModWait
!!!write (*, '(A)') 'StartModule started'
    IF (DROP_FILE .NE. ' ') THEN
   
       CALL setWorkDir (DROP_FILE, I4ERR)
       I2ERR = I4ERR
       CALL DOSERR@ (I2ERR)
       IF (INDEX (ProgName, 'Bingo') .GE. 1) THEN
          IF (iUseBgoMP .GE. 1) THEN
             L = SetEnvironmentVariable ('Bingo_Options', 'MP')
          ELSE
             L = SetEnvironmentVariable ('Bingo_Options', ' ')
          ENDIF
       ELSE
          L = SetEnvironmentVariable ('Bingo_Options', 'NoPipe')
       ENDIF
       L = L

       IF (KEY .EQ. 'W') THEN
write (*, '(A)') 'calling Bingo via ModWait'
          J = ModWait  (ProgName, ParamString, 1)
write (*, '(A)') 'Return from ModWait'
       ELSE
write (*, '(A)') 'calling Program via ModStart'
          J = ModStart (ProgName, ParamString, 1)
write (*, '(A)') 'Return from ModStart'
       ENDIF
    ELSE
       CALL SHOW_ERR ('Please select a directory and try again', ' ', 0)
    ENDIF
    StartModule = J
    RETURN
    END FUNCTION StartModule

writes are going to a CW window.
Back to top
View user's profile Send private message Visit poster's website
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7912
Location: Salford, UK

PostPosted: Sat Jan 06, 2018 9:11 am    Post subject: Reply with quote

If you are running a thread that is written using modern Fortran features (i.e. Fortran 90 and after) then it is possible that FTN95 will call upon a virtual stack. If it does then the whole program will become unsafe and you may get random failures and/or incorrect results. The way to check for this is outlined above.

Note that it is the sharing of the virtual stack that causes the problem. So, for example, it is OK to use the virtual stack in the main code but not in any of the threads.

We are currently working on implementing an alternative approach that does not have this limitation (and other limitations) of StartThread@.
Back to top
View user's profile Send private message AIM Address
EKruck



Joined: 09 Jan 2010
Posts: 224
Location: Aalen, Germany

PostPosted: Mon Jan 08, 2018 12:01 am    Post subject: Reply with quote

Paul,

thank you for your explanations. I found a lot of calls to __alloc_pseudo_stack but no calls to __alloc_quasi_stack.
There are only very few arrays with maximum size of up to 100.
To create threads I use
Code:
!   STDCALL CreateThread 'CreateThread'  (REF,VAL,REF,REF,VAL,REF) : INTEGER*4 ! Original
    STDCALL CreateThread 'CreateThread'  (VAL,VAL,REF,REF,VAL,REF) : INTEGER*4 ! Nodified to call with NULL pointer

I use CreateThread only to run other executables with wait.
What are the conditions that pseudo_stack is used. I was not able to find it out from the assembler listring. Is there a simple rule? Can I avoid it?
In my threads I did not yet find variables that are used in the main thread and in sub-threads.
Is it possible that %rm or %dl starts an extra thread?
Back to top
View user's profile Send private message Visit poster's website
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7912
Location: Salford, UK

PostPosted: Mon Jan 08, 2018 8:38 am    Post subject: Reply with quote

If you are using StartThread@ to load a simple subroutine that only runs an executable then there should be no problem with thread safety. In any case you only need make sure that the virtual stack is not used in the subroutine that is called via StartThead@.

The virtual stack is used by FTN95 in various contexts. The only satisfactory way to test for this is to compile everything using /explist and then do a global search in the resulting .lis files, searching for the two functions mentioned above.
Back to top
View user's profile Send private message AIM Address
EKruck



Joined: 09 Jan 2010
Posts: 224
Location: Aalen, Germany

PostPosted: Mon Jan 08, 2018 9:05 am    Post subject: Reply with quote

I compiled all envolved functions - as well from my libraries - and found everywhere may be 50 times __alloc_pseudo_stack, but I'm not able to interprete these lis file.
But I have as well another suspicion: The problem occures only when I run several .exe files with wait in fast sequence. Is in this range any problem known?
Back to top
View user's profile Send private message Visit poster's website
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7912
Location: Salford, UK

PostPosted: Mon Jan 08, 2018 11:44 am    Post subject: Reply with quote

You don't need to understand the content of the .lis file except to find the start of the assembler code for your thread routine and then to see if it calls either __alloc_quasi_stack or __alloc_pseudo_stack before its end. The same will apply to other routines (if any) that are called by the primary thread routine.
Back to top
View user's profile Send private message AIM Address
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> 64-bit All times are GMT + 1 Hour
Page 1 of 1

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


Powered by phpBB © 2001, 2005 phpBB Group