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

problem with "deallocate"

mirco_v_
Beginner
1,161 Views

This simple dummy program I have done to show the problem will compile with both ( gfortran 4.9.2.10 and ifort 17.0.0 20160315 ).

With gfortran it works smoothly while with ifort it generates a SEGFAULT in the deallocation phase.

I can't understand if this is a problem of the program or a problem of the compiler.

>>=====================================================================================

MODULE container
IMPLICIT NONE
TYPE :: container_t
  PRIVATE
  INTEGER, DIMENSION(:), POINTER :: A=>NULL()
CONTAINS
  PROCEDURE, PASS, PUBLIC :: BIND=>container_bind
  PROCEDURE, PASS, PUBLIC :: FREE=>container_free
END TYPE
CONTAINS
SUBROUTINE container_bind( hobj, dat )
  CLASS(container_t),             INTENT(INOUT) :: hobj
  CLASS(*), DIMENSION(:), TARGET, INTENT(IN)    :: dat
  SELECT TYPE  ( A => dat )
  TYPE IS (INTEGER)
    hobj%A => A
  END SELECT
END SUBROUTINE container_bind
SUBROUTINE container_free( hobj )
  CLASS(container_t),     INTENT(INOUT) :: hobj
  IF ( ASSOCIATED(hobj%A) ) DEALLOCATE(hobj%A)
END SUBROUTINE container_free
END MODULE container

PROGRAM test
  USE :: container
IMPLICIT NONE
  TYPE(container_t) :: T
  INTEGER, DIMENSION(:), POINTER :: A=>NULL()
  ALLOCATE(A(10))
  WRITE(*,*) 'Allocated...'
  CALL T%BIND( A )
  WRITE(*,*) 'Bounded...'
  CALL T%FREE()
  WRITE(*,*) 'Finished...'
END PROGRAM test

>>=====================================================================================

 

 

0 Kudos
1 Solution
FortranFan
Honored Contributor II
1,161 Views

See this thread: https://software.intel.com/en-us/forums/intel-fortran-compiler-for-linux-and-mac-os-x/topic/656711, especially Message #2.

View solution in original post

0 Kudos
11 Replies
jimdempseyatthecove
Honored Contributor III
1,161 Views

What happens if you...

SELECT TYPE  ( A => dat )
  TYPE IS (INTEGER)
    hobj%A => dat
  END SELECT

Jim Dempsey

0 Kudos
mirco_v_
Beginner
1,161 Views

 The compiler generates the following error:

~$ error #8803: If the target is unlimited polymorphic, the pointer object must be unlimited polymorphic, or of a type with the BIND or SEQUENCE attribute.  

    hobj%A => dat
---------^

 

0 Kudos
FortranFan
Honored Contributor II
1,162 Views

See this thread: https://software.intel.com/en-us/forums/intel-fortran-compiler-for-linux-and-mac-os-x/topic/656711, especially Message #2.

0 Kudos
mirco_v_
Beginner
1,161 Views

FortranFan wrote:

See this thread: https://software.intel.com/en-us/forums/intel-fortran-compiler-for-linux..., especially Message #2.

Thanks now it is all clear, it is due Fortran 2008 standard (final sentence of F2008 6.7.3.3p1).

I found this thread:  https://software.intel.com/en-us/forums/intel-visual-fortran-compiler-for-windows/topic/518263 which is also very useful.

Steve Lionel (Intel) wrote:

... The relevant part of the standard is 6.7.3.3, Deallocation of pointer targets, as modified by interpretation F08/0010, which adds the sentence "A pointer shall not be deallocated if its target or any subobject thereof is argument associated with a dummy argument or construct associated with an associate name."

Mirco Valentini

0 Kudos
mirco_v_
Beginner
1,161 Views

What about this modification?

MODULE container
IMPLICIT NONE
TYPE :: container_t
  PRIVATE
  INTEGER, DIMENSION(:), ALLOCATABLE :: A
CONTAINS
  PROCEDURE, PASS, PUBLIC :: BIND=>container_bind
  PROCEDURE, PASS, PUBLIC :: FREE=>container_free
END TYPE
CONTAINS
SUBROUTINE container_bind( hobj, dat )
  CLASS(container_t),                          INTENT(INOUT) :: hobj
  CLASS(*), DIMENSION(:), ALLOCATABLE, TARGET, INTENT(INOUT) :: dat
  SELECT TYPE  ( A => dat )
  TYPE IS (INTEGER)
    CALL MOVE_ALLOC( A, hobj%A )
  END SELECT
END SUBROUTINE container_bind
SUBROUTINE container_free( hobj )
  CLASS(container_t),     INTENT(INOUT) :: hobj
  IF ( ALLOCATED(hobj%A) ) DEALLOCATE(hobj%A)
END SUBROUTINE container_free
END MODULE container

PROGRAM test
  USE :: container
IMPLICIT NONE
  TYPE(container_t) :: T
  INTEGER, DIMENSION(:), ALLOCATABLE :: A
  ALLOCATE(A(10))
  WRITE(*,*) 'Allocated...'
  CALL T%BIND( A )
  WRITE(*,*) 'Bounded...'
  CALL T%FREE()
  WRITE(*,*) 'Finished...'
END PROGRAM test

The compiler gives the following error:

error #8195: The argument to the MOVE_ALLOC intrinsic subroutine shall be an allocatable object

0 Kudos
IanH
Honored Contributor II
1,161 Views

mirco v. wrote:

Quote:

FortranFan wrote:

 

See this thread: https://software.intel.com/en-us/forums/intel-fortran-compiler-for-linux..., especially Message #2.

 

 

Thanks now it is all clear, it is due Fortran 2008 standard (final sentence of F2008 6.7.3.3p1).

There are no allocatable entities in your example program in the opening post.  The last sentence of 6.7.3.3p1 of F2008 as originally published is not applicable.

At the time the pointer is deallocated, it is also not associated with a dummy argument.  The text added to 6.7.3.3p1 by interpretation F08/0010 is therefore also not applicable.

I suspect this is just a compiler bug.

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,161 Views

In #6 the program section declared A without the target attribute.

The dummy in container_bind has the target attribute on dummy dat. You cannot change the attribute of the actual argument in this way. The compiler should have issued an error or warning.

Note, the MOVE_ALLOC (without TARGET) should have been sufficient..

*** However in the program section the CALL T%BIND(A) is not intuitive that A gets deleted. Perhaps T%TAKES(A) would be a better choice of names.

Jim Dempsey

0 Kudos
FortranFan
Honored Contributor II
1,161 Views

mirco v. wrote:

What about this modification? .. The compiler gives the following error:

error #8195: The argument to the MOVE_ALLOC intrinsic subroutine shall be an allocatable object

See this thread: https://software.intel.com/en-us/forums/intel-visual-fortran-compiler-for-windows/topic/541980

0 Kudos
FortranFan
Honored Contributor II
1,161 Views

ianh wrote:

.. There are no allocatable entities in your example program in the opening post.  The last sentence of 6.7.3.3p1 of F2008 as originally published is not applicable. ..

For the two compilers mentioned here, the run-time behavior is the same if the A variable in the main program in the original post is given an ALLOCATABLE or POINTER attribute; go figure!  It'd appear only a select few are able to discern the difference between the two attributes in the Fortran standard under various circumstances and compiler implementations still struggle with them, how many years is it since the release!

ianh wrote:

.. I suspect this is just a compiler bug.

Hopefully Steve and co. at Intel will notice this and take a look.

0 Kudos
Kevin_D_Intel
Employee
1,161 Views

Thanks everyone for the discussion. I will have a look.

0 Kudos
Kevin_D_Intel
Employee
1,161 Views

I submitted the original run-time seg-fault issue to Development (see internal tracking id below).

I’m confused by posts #8 and #9, specifically whether the variant in post #6 with the TARGET attribute removed is expected to compile and run. Can Jim and/or FortranFan please help clarify?

@Jim – I noted your point about the compiler should have issued an error/warning related to the attribute mismatch between the actual/dummy and can file a report on that too; however, without TARGET the sample still trips on error #8195. Is there some variant here that can show the missed finding for the attribute mismatch?

(Internal tracking id: DPD200413240)

0 Kudos
Reply