Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
Announcements
FPGA community forums and blogs have moved to the Altera Community. Existing Intel Community members can sign in with their current credentials.
29314 Discussions

Question about finalization of allocatable arrays

Daniel_Dopico
New Contributor I
2,354 Views

The Intel fortran documentation says the following about allocatable arrays: "When an allocatable entity is deallocated, it is finalized". 

How to correct my code to finalize the elements of the allocatable array list_pts? Here it is the code, it never enters in the FINAL routine:

MODULE module_final
    TYPE PUNTO
	    REAL(8),POINTER,DIMENSION(:)::rpt
        LOGICAL::isallocated=.false.
    CONTAINS
        FINAL::FINAL_PUNTO
    END TYPE PUNTO
    
CONTAINS
    SUBROUTINE FINAL_PUNTO(pt)
        TYPE(PUNTO)::pt
    
        IF(isallocated) THEN
            DEALLOCATE(pt%rpt)
            isallocated=.true.
        ENDIF
        NULLIFY(pt%rpt)
        print *,"Inside the final routine of type PUNTO"
    END SUBROUTINE FINAL_PUNTO
    
    SUBROUTINE ALLOC_PUNTO(pt)
        TYPE(PUNTO)::pt
        
        IF(.not.isallocated) THEN
            ALLOCATE(pt%rpt(3))
            isallocated=.true.
        ENDIF
    END SUBROUTINE ALLOC_PUNTO
END MODULE module_final
    
program main_final
    USE module_final
    IMPLICIT NONE
    TYPE(PUNTO),ALLOCATABLE::list_pts(:)
    REAL(8),DIMENSION(3),TARGET::pt
    
    ALLOCATE(list_pts(2))
    CALL ALLOC_PUNTO(list_pts(1))
    list_pts(2)%rpt=>pt
    
    DEALLOCATE(list_pts) !This deallocate doesn't call the FINAL of the single elements.
end program main_final

 

0 Kudos
1 Solution
FortranFan
Honored Contributor III
2,354 Views

Daniel Dopico wrote:

.. I tried the subroutine and it doesn't seem to solve the problem ..

@Daniel Dopico,

Note the FINAL subroutine is rank-specific by default: what you show in the original post specifies instructions to finalize a scalar (rank 0) object only.  But now you have an object (list_pts) in your program (main_final) which is a rank 1 array.  So you would need to either introduce a binding with your derived type (PUNTO) for another FINAL subroutine which accepts a dummy argument which is rank 1 and specifies the instructions to finalize using such an argument.  Or you can make your code compact by using the ELEMENTAL attribute on the FINAL subprogram (https://software.intel.com/en-us/fortran-compiler-developer-guide-and-reference-elemental).  Since ELEMENTAL subprograms are PURE by default, during any (temporary?) "debugging" on an ELEMENTAL FINAL subprogram via print statements, you can consider the IMPURE attribute.

You may also want to consider always introducing the INTENT attribute with your subprogram dummy arguments: Fortran standard says FINAL subprogram dummy argument of the passed object shall have the INTENT(INOUT) attribute.

 

View solution in original post

0 Kudos
12 Replies
Steve_Lionel
Honored Contributor III
2,354 Views

[Deleted]

0 Kudos
jimdempseyatthecove
Honored Contributor III
2,354 Views

While this doesn't help the Final issue, line 15 should be setting isallocated=.false.

Dops, try this:

subroutine sub_final
    USE module_final
    IMPLICIT NONE
    TYPE(PUNTO),ALLOCATABLE::list_pts(:)
    REAL(8),DIMENSION(3),TARGET::pt
    
    ALLOCATE(list_pts(2))
    CALL ALLOC_PUNTO(list_pts(1))
    list_pts(2)%rpt=>pt
    
    DEALLOCATE(list_pts) !This deallocate doesn't call the FINAL of the single elements.
end subroutine sub_final

program main_final
    call sub_final
end program main_final


I seem to have a fuzzy recollection of finalization issues in the PROGRAM procedure. I do not recall if this was fixed (or an issue).

Jim Dempsey

0 Kudos
Daniel_Dopico
New Contributor I
2,354 Views

Thank you very much Jim.

You are right about line 15. In fact it should be pt%isallocated=.false. and there are a bunch of errors more because I forgot the IMPLICIT NONE in the module.

Anyway, I tried the subroutine and it doesn't seem to solve the problem. In fact the original code (which motivated this sample) doesn't have any main program because it is a library.

Thanks!

0 Kudos
FortranFan
Honored Contributor III
2,355 Views

Daniel Dopico wrote:

.. I tried the subroutine and it doesn't seem to solve the problem ..

@Daniel Dopico,

Note the FINAL subroutine is rank-specific by default: what you show in the original post specifies instructions to finalize a scalar (rank 0) object only.  But now you have an object (list_pts) in your program (main_final) which is a rank 1 array.  So you would need to either introduce a binding with your derived type (PUNTO) for another FINAL subroutine which accepts a dummy argument which is rank 1 and specifies the instructions to finalize using such an argument.  Or you can make your code compact by using the ELEMENTAL attribute on the FINAL subprogram (https://software.intel.com/en-us/fortran-compiler-developer-guide-and-reference-elemental).  Since ELEMENTAL subprograms are PURE by default, during any (temporary?) "debugging" on an ELEMENTAL FINAL subprogram via print statements, you can consider the IMPURE attribute.

You may also want to consider always introducing the INTENT attribute with your subprogram dummy arguments: Fortran standard says FINAL subprogram dummy argument of the passed object shall have the INTENT(INOUT) attribute.

 

0 Kudos
Daniel_Dopico
New Contributor I
2,354 Views

Thank you Fan.

You are right. I misunderstood the documentation. After declaring the subroutine as ELEMENTAL the code enters exactly as you said. It makes sense that you need a rank specific finalization. Moreover I think that it is the first time that I declare an elemental procedure.

0 Kudos
FortranFan
Honored Contributor III
2,354 Views

Daniel Dopico wrote:

.. Moreover I think that it is the first time that I declare an elemental procedure.

If you seek highly performant code for physics and multibody dynamics, strive to make all your Fortran subprograms PURE and also consider the ELEMENTAL attribute as much as possible, particularly with type-bound procedures.  Your codes will be enhanced greatly in terms of reliability and robustness and things will get better and better over time as compiler(s) improve in terms of optimization, vectorization, and parallelization capabilities.

0 Kudos
jimdempseyatthecove
Honored Contributor III
2,354 Views

>>Note the FINAL subroutine is rank-specific by default: what you show in the original post specifies instructions to finalize a scalar (rank 0) object only.

Then this might be an opportunity for a warning by the compiler (-warn:all)

Jim Dempsey

0 Kudos
jimdempseyatthecove
Honored Contributor III
2,354 Views

Dops,

I wish to caution you about use of PUNTO in a multi-threaded application whereby the allocating thread exits before the other threads. You will have to assure that this does not happen.

Jim Dempsey

0 Kudos
Daniel_Dopico
New Contributor I
2,354 Views

jimdempseyatthecove wrote:

>>Note the FINAL subroutine is rank-specific by default: what you show in the original post specifies instructions to finalize a scalar (rank 0) object only.

Then this might be an opportunity for a warning by the compiler (-warn:all)

Jim Dempsey

Thanks Jim. Do you mean that the -warn:all warns you about this situation or do you mean that it should warn you but it doesn't?

0 Kudos
Daniel_Dopico
New Contributor I
2,354 Views

jimdempseyatthecove wrote:

Dops,

I wish to caution you about use of PUNTO in a multi-threaded application whereby the allocating thread exits before the other threads. You will have to assure that this does not happen.

Jim Dempsey

I was having a look at the FINAL subroutine for PUNTO and I don't understand the problem. There are no states or module variables inside the FINAL, then, what is the problem for generating parallel code?

Thanks!

0 Kudos
jimdempseyatthecove
Honored Contributor III
2,354 Views

>> what is the problem for generating parallel code?

Now that I think about it, it should be no problem as you cannot get to the dtor (FINAL) while a team is pending.

*** at least for a sane programmer.

For us insane programmers...

program main_final
  USE omp_lib
  USE module_final
  IMPLICIT NONE
  REAL(8),DIMENSION(3),TARGET::pt
    
  !$omp parallel
    !$omp single
      block
        TYPE(PUNTO),ALLOCATABLE::list_pts(:)
        ALLOCATE(list_pts(omp_get_max_threads()*2))
        !$omp task
          CALL ALLOC_PUNTO(list_pts(omp_get_thread_num()*2))
          list_pts(omp_get_thread_num()*2+1)%rpt=>pt
        !$omp end task
        DEALLOCATE(list_pts) !This deallocate doesn't call the FINAL of the single elements.
      end block
    !$omp end single
  !$omp end parallel
end program main_final

Note, assumes working FINAL, and the explicit DEALLOCATE could be omitted and thus implicit deallocation occurs at end of block. The thread occupying the single section can exit the block while enqueued tasks are running.

Jim Dempsey

0 Kudos
Daniel_Dopico
New Contributor I
2,354 Views

FortranFan wrote:

If you seek highly performant code for physics and multibody dynamics, strive to make all your Fortran subprograms PURE and also consider the ELEMENTAL attribute as much as possible, particularly with type-bound procedures.  Your codes will be enhanced greatly in terms of reliability and robustness and things will get better and better over time as compiler(s) improve in terms of optimization, vectorization, and parallelization capabilities.

Thank you Fan for your suggestion. I need to revisit my code to pay a closer attention to this. My use of PURE procedures is rare, I incorporated it to some recently developed ones of minor relevance.

0 Kudos
Reply