0

I am converting a legacy code and employing allocatable arrays

Now a subroutine(STIFFR) calls another subroutine(RADaU5) which needs workspace and tolerance specifying arrays. Since these depend on the dimensionality of the problem (passed to STIFFR), all arrays are declared allocatable in STIFFR, passed, along with their dimensions to RADAU5, and then deallocated. It's on deallocating the last that gfortran crashes.

SUBROUTINE STIFFR(FCN ,OUTSLA,DJAC ,NEQ,Y, DU,DUDUM,PD
 z ,LDATIMES,NIWRKRAD,NRWRKRAD,TIMES,NSUP,URESUR,URESUI,
 z ITOT  ,KEY )


      IMPLICIT DOUBLE PRECISION(A-h,o-z)
         EXTERNAL FCN,OUTSLA,djac, SOLOUT,DUMMAS

    DIMENSION Y(NEQ),IPAR(1),RPAR(1),
 z INFO(15) ,DU(NEQ),DUDUM(NEQ)

   DIMENSION TIMES(LDATIMES),URESUI(NSUP,NSUP,LDATIMES),
 z URESUR(NSUP,NSUP,LDATIMES),ITOT(NSUP),PD(NEQ,NEQ)

   DOUBLE PRECISION, dimension(:), ALLOCATABLE :: ATOL ,RTOL   
    DOUBLE PRECISION, dimension(:), ALLOCATABLE ::  WORK
   integer, DIMENSION(:), allocatable :: IWORK 
     LOGICAL FLAGODE
       COMMON/ODEFLAG/FLAGODE
      COMMON/ISTAT/IPT
      COMMON/IOUTCOM/IOUT
         FLAGODE=.FALSE.
       NTIMES=LDATIMES-1
           idiD=-35
       NDM=NEQ
       allocate (RTOL(NEQ ), stat=iaLLOCATEstatus)
      if (IALLOCATEstatUS /= 0) then
  write(6,*)'ERROR trying to allocate rtol in solve0U0'
         stop 1
       end if
     allocate (ATOL(NEQ ), stat=iaLLOCATEstatus)
      if (IALLOCATEstatUS /= 0) then
  write(6,*)'ERROR trying to allocate atol in solve0U0'
         stop 1
       end if      
           
  allocate (WORK(NRWRKRAD), stat=iaLLOCATEstatus)
      if (IALLOCATEstatUS /= 0) then
  write(6,*)'ERROR trying to allocate  WORK  in solveOU0'
         stop 1
       end if
     allocate (IWORK(NIWRKRAD), stat=iaLLOCATEstatus)
      if (IALLOCATEstatUS /= 0) then
  write(6,*)'ERROR trying to allocate IWORK  in solve0U0'
         stop 1
       end if  
             DO 33 K=1,NTIMES-1
               T=TIMES(K)
                TOUT=TIMES(K+1)
     

......................

22      CALL RADAU5( NEQ,FCN,
 z T,Y,TOUT,H,
 &                  RTOL,ATOL,ITOL,
 &                  DJAC,
 & IJAC,MLJAC,MUJAC,
 &                  DUMMAS,
 z  IMAS,MLMAS,MUMAS,
 &                  SOLOUT,0, 
 z          LDATIMES,NSUP,URESUR,URESUI,
 &                 WORK,NRWRKRAD,
 z IWORK,NIWRKRAD,RPAR,IPAR,
 z IDID)  

...............

33      CONTINUE

....

         deallocate (IWORK , stat=IALLOCATEstatus)
     deallocate ( WORK , stat=IALLOCATEstatus)
     deallocate (ATOL, stat=IALLOCATEstatus)

c The next line is the offending line, whether or not I check if alocated

    if(allocated(rtol))     deallocate (RTOL, stat=IALLOCATEstatus)  
                  RETURN
                  END
  

Next, I tried gdb, which complains about a missing routine when calling deallocate, whereas deallocated was called many times before without any apparent problems:

     (gdb) p rtol
$5 = (0.00010000000000000007, 0.0001, 0.0001, 0.0001, 0.0001, 0.0001, 0.0001, 0.0001)
(gdb) p allocated(rtol)
No symbol "allocated" in current context.
(gdb) next
free(): invalid pointer
Program received signal SIGABRT, Aborted.
__GI_raise (sig=sig@entry=6) at ../sysdeps/unix/sysv/linux/raise.c:51
51  ../sysdeps/unix/sysv/linux/raise.c: No such file or directory.
(gdb)  

Any ideas on what might be the problem??

  • 1
    Welcome. Please take the [tour] and use tag [tag:fortran] for all Fortran questions to get more attention. When you get segmentation faults, you need to enable all compiler checks. Use `gfortran -g -fbacktrace -fcheck=all -Wall` and report the results. – Vladimir F Героям слава Dec 16 '20 at 07:46
  • 1
    Is it possible for you to provide a **minimal working example** which still shows the same error, i.e. provide a `program` and shorten your subroutines (explicitly assume array lengths and such)? – jack Dec 16 '20 at 08:24
  • free(): invalid pointer Program received signal SIGABRT: Process abort signal. Backtrace for this error: #0 0x7fd1c91d8d01 in ??? #1 0x7fd1c91d7ed5 in ??? #2 0x7fd1c8ea220f in ??? #3 0x7fd1c8ea218b in ??? #4 0x7fd1c8e81858 in ??? #5 0x7fd1c8eec3ed in ??? #6 0x7fd1c8ef447b in ??? #7 0x7fd1c8ef5cab in ??? – cfelix cfelix Dec 16 '20 at 08:34
  • #8 0x55e0dad8bb4b in stiffr_ at /home/me/DEVELOPMENT/HLINEARRADAUtst/ft186.f:31140 #9 0x55e0dad44910 in solve0u0_ at /home/me/DEVELOPMENT/HLINEARRADAUtst/ft186.f:7430 #10 0x55e0dae69687 in MAIN__ at /home/me/DEVELOPMENT/HLINEARRADAUtst/ft186.f:1453 #11 0x55e0dae9d4c3 in main at /home/me/DEVELOPMENT/HLINEARRADAUtst/ft186.f:4556 Aborted (core dumped) – cfelix cfelix Dec 16 '20 at 08:35
  • 2
    please compile again with the debugging flags enabled (see Vladimir F's comment above) and print those error messages. I hope they are more revealing. (please add them to your question and delete the comments. keeps the question+comments cleaner) – jack Dec 16 '20 at 09:49
  • There wer eno error messages, just warnings, e.g. tabs instead of spaces (lots of those). Also some intrinsics like DGAMMA and DASINH, DACOSH. Should I post the output of gfortran -g -fbacktrace -fcheck=all -Wall ? It is long because of these 'warnings'. Meanwhile I created a minimal code with the same structure which thus far ran ok. So I am adding complexity to see where it will break. – cfelix cfelix Dec 16 '20 at 10:45
  • No, not those warnings. But re-run your code after compiling with those flags and give us the output. It should give you actual information and not uncomprehensible stuff like `#8 0x55e0dad8bb4b `. And please read about a [mcve]. It is a piece of code that reproduces the error and that is small enough so what we can test it. – Vladimir F Героям слава Dec 16 '20 at 11:56
  • You should use `implicit none` in all your subroutines. This definitely help catch more errors when compiling, and it may help find your bug. – BenBoulderite Dec 17 '20 at 09:41

0 Answers0