Search code examples
fortrangfortran

Dynamic memory deallocation in procedure from derrived type


I am new to Fortran so I would like to have some insight regarding the allocation of dynamic memory

I read about dynamic memory allocation and various sources have a different take to this subject. For example, one book states that every single block of allocated dynamic memory must be deallocated at the end of the program to avoid memory leaks. However, other sources (books and various web pages) claim that is invalid as compilers (gfortran and alike) deallocate all dynamic objects, arrays, etc automatically at the end of the program.

So in my sample code, I do not know if there is a need to deallocate dynamic array NN_VOD from CALCULATE_DATA_DM procedure.

What do I need to do with this sample code if I want to avoid memory leak and are there any memory leak in this code? (My IDE is Code::Blocks 17.12 with MinGW compiler 6.3.0)

MODULE DERRIVED_TYPE_TMP

  INTEGER, PUBLIC :: I, J, K, ALLOC_ERR

  TYPE, PUBLIC :: DM_ELEMENT
     CHARACTER( 50 ), PRIVATE :: ELE_NAME
     INTEGER,         PRIVATE :: ELE_NUMBER
   CONTAINS
     PROCEDURE, PUBLIC :: CALCULATE_ELEMENT => CALCULATE_DATA_ELEMENT
  END TYPE DM_ELEMENT

  PRIVATE :: CALCULATE_DATA_ELEMENT

  TYPE, EXTENDS(DM_ELEMENT), PUBLIC :: VOD_DM
     INTEGER, ALLOCATABLE, PRIVATE :: NN_VOD( : )
   CONTAINS

     PROCEDURE, PUBLIC :: CALCULATE_ELEMENT => CALCULATE_DATA_DM
     PROCEDURE, PUBLIC ::           TAKE_DM =>      TAKE_DATA_DM
  END TYPE VOD_DM

  PRIVATE :: CALCULATE_DATA_DM
  PRIVATE :: TAKE_DATA_DM

CONTAINS

  SUBROUTINE CALCULATE_DATA_ELEMENT ( THIS, NUMBER_TMP )
    CLASS( DM_ELEMENT )   :: THIS
    INTEGER, INTENT( IN ) :: NUMBER_TMP
  END SUBROUTINE CALCULATE_DATA_ELEMENT

  SUBROUTINE CALCULATE_DATA_DM( THIS, NUMBER_TMP )
    CLASS( VOD_DM )       :: THIS
    INTEGER, INTENT( IN ) :: NUMBER_TMP

    IF ( .NOT. ALLOCATED( THIS%NN_VOD ) ) ALLOCATE( THIS%NN_VOD( NUMBER_TMP ), STAT = ALLOC_ERR )
    IF ( ALLOC_ERR .NE. 0 )                STOP ( "PROBLEM SA ALOKACIJOM MEMORIJE - THIS%T !!!" )
    DO J = 1, NUMBER_TMP
       THIS%NN_VOD( J ) = J + NUMBER_TMP
    END DO
  END SUBROUTINE CALCULATE_DATA_DM

  FUNCTION TAKE_DATA_DM( THIS, INDX ) RESULT( RESULT_TMP )
    CLASS( VOD_DM )        :: THIS
    INTEGER, INTENT( IN ) :: INDX
    INTEGER               :: RESULT_TMP

    RESULT_TMP = THIS%NN_VOD( INDX )
  END FUNCTION TAKE_DATA_DM

END MODULE DERRIVED_TYPE_TMP

PROGRAM DO_LOOP_ALLOCATION
  USE, NON_INTRINSIC :: DERRIVED_TYPE_TMP
  IMPLICIT NONE

  INTEGER,   PARAMETER :: N_NN_DM = 3
  INTEGER,   PARAMETER :: AN_NN_DM( N_NN_DM ) = [ 2, 3, 4 ]

  TYPE :: NN_VOD
     TYPE( VOD_DM ), ALLOCATABLE :: ID( : )
  END TYPE NN_VOD

  CLASS( DM_ELEMENT ),             POINTER :: P_DM_ELEMENT
  TYPE     ( NN_VOD ), ALLOCATABLE, TARGET ::   PAR_NN_VOD( : )

  IF ( .NOT. ALLOCATED( PAR_NN_VOD ) ) ALLOCATE( PAR_NN_VOD( N_NN_DM ), STAT = ALLOC_ERR )
  IF ( ALLOC_ERR .NE. 0 )              STOP ( "ALLOCATION ERROR - PAR_NN_VOD !!!" )

  DO K = 1, N_NN_DM
     IF ( .NOT. ALLOCATED( PAR_NN_VOD( K )%ID ) ) ALLOCATE( PAR_NN_VOD( K )%ID( AN_NN_DM( K ) ), STAT = ALLOC_ERR )
     IF ( ALLOC_ERR .NE. 0 )                      STOP ( "ALLOCATION ERROR - PAR_NN_VOD%ID !!!")
  END DO

  DO K = 1, N_NN_DM
     DO I = 1, AN_NN_DM( K )
        P_DM_ELEMENT => PAR_NN_VOD( K )%ID( I )
        CALL P_DM_ELEMENT%CALCULATE_ELEMENT( K + I )
     END DO
  END DO

END PROGRAM DO_LOOP_ALLOCATION

Solution

  • From Fortran95 onwards the language is designed so that with a standard conforming compiler it is impossible to have a memory leak when using allocatable arrays, as once an allocatable object goes out of scope it becomes deallocated. This is one of the big advantages of allocatable arrays, and one of the reasons why they should always be used in preference to pointers where possible. Now when a variable goes out of scope may well be long after a variable stops being used, and so you may wish to manually deallocate earlier to save memory, but there is no need to deallocate purely to avoid a memory leak. Thus in your code use allocatable arrays and there will be no memory leak.

    In Fortran 90 this was not true, memory leaks with allocatables were possible. But this standard has long been superseded by Fortran 95 and it, and thus Fortran 90 and all earlier standards should not be being used today.