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

Derived type pointer components and intent(in) are out?

IanH
Honored Contributor III
1,249 Views
This is a bit similar to the stuff discussed some time previously.

The attached code snippet fails (11.1.067) with error 6780 ("A dummy argument with INTENT(IN) attribute shall not appear in a variable definition context") flagged against the line marked ! ###. But I think that error is in error.

[fortran]MODULE my_mod
  IMPLICIT NONE  
  
  TYPE :: PtrCompType
    INTEGER :: comp
  END TYPE PtrCompType
  
  TYPE :: TypeWithPointerComp
    INTEGER, POINTER :: ptr_comp
    TYPE(PtrCompType), POINTER :: dt_ptr_comp
  END TYPE TypeWithPointerComp    
  
  ! Uncomment for defined assignment of PtrCompType.
  !INTERFACE ASSIGNMENT(=)
  !  MODULE PROCEDURE foo_foo
  !END INTERFACE ASSIGNMENT(=)
CONTAINS
  SUBROUTINE proc(arg)
    TYPE(TypeWithPointerComp), INTENT(IN) :: arg
    !****
    CALL foo(arg%dt_ptr_comp)   ! ###
    arg%ptr_comp = 2
    arg%dt_ptr_comp = PtrCompType(2)
  END SUBROUTINE proc
  
  SUBROUTINE foo(obj)
    TYPE(PtrCompType), INTENT(OUT) :: obj
    obj%comp = 2
  END SUBROUTINE foo    

  SUBROUTINE foo_foo(lhs, rhs)
    TYPE(PtrCompType), INTENT(OUT) :: lhs
    TYPE(PtrCompType), INTENT(IN) :: rhs
    lhs%comp = rhs%comp
  END SUBROUTINE foo_foo
END MODULE my_mod

PROGRAM define_me
  USE my_mod
  IMPLICIT NONE
  
  TYPE(PtrCompType), TARGET :: dt_targ
  INTEGER, TARGET :: targ
  
  TYPE(TypeWithPointerComp) :: a
  !****  
  dt_targ%comp = 1
  targ = 1
  
  a%dt_ptr_comp => dt_targ
  a%ptr_comp => targ
  
  CALL proc(a)    
  
  PRINT "(I0)", dt_targ%comp
  PRINT "(I0)", targ
END PROGRAM define_me
[/fortran]


My logic from the f2003 std: Because it is a pointer, dt_ptr_comp is only a sub-object when "in contexts that pertain to its pointer association status" (6.1.2). Because the dummy argument to foo doesn't have the pointer attribute, the call to foo isn't in such a context, so hence the call isn't a "variable definition context" for (part of) arg. Besides which, the INTENT(IN) spiel from 5.1.2.7 in the error message is for non-pointer objects, which dt_ptr_comp isn't (6.1.2 again, bit further along) so the compiler should get told off anyway for prattling irrelevance.

Beyond logic: if I can get away with intrinsic assignment of the derived type (but not defined assignment - which is a bit suspicious!), then calling foo should be fair game.

Note though, when following the various links in the std I often ended up right back where I started. My brain doesn't have the recursive attribute, so I could be the one prattling irrelevance.

module pointer_pointer

type data_struct

integer :: int_data

integer, pointer :: int_ptr

end type

contains

subroutine sub1( ptr )

implicit none

type( data_struct ), pointer, intent( in ) :: ptr

type( data_struct ), pointer :: null_ptr => null( )

integer, target :: x

ptr => null_ptr !**** This should cause an error

ptr%int_data = x !**** This should not

ptr%int_ptr => x !**** This should not

end subroutine

subroutine sub2( ptr )

implicit none

type( data_struct ), pointer, intent( in ) :: ptr

type( data_struct ), pointer :: tmp_ptr

integer, target :: x

tmp_ptr => ptr

tmp_ptr%int_data = x

tmp_ptr%int_ptr => x

end subroutine

end module

0 Kudos
8 Replies
abhimodak
New Contributor I
1,249 Views
Hi Ian

Just sharing my thoughts; I don't mean to be doing any "value-addition"...

What if one says:

(1) Acutal argument arg%dt_ptr_component is a pointer. Dummy argument obj is non-pointer.

Therefore, (a) arg%dt_ptr_component must be associated and (b) target of arg%dt_ptr_component is associated with obj as if there were no pointers involved.

(2) Then, the question is whether target of arg%dt_ptr_component is allowed to have INTENT(OUT). I think it is allowed since the INTENT(IN) applied to dummy argument arg in subroutine proc applies to association status of its pointer components. Hence, your program is valid.

Abhi
0 Kudos
Steven_L_Intel1
Employee
1,249 Views
Ian,

I believe that you are correct and the compiler is not. Note 5.13 in F2003 seems especially relevant. Here's the words from F2008 (Note 5.16 there):

If a dummy argument is a derived-type object with a pointer component, then the pointer as a pointer is
a subobject of the dummy argument, but the target of the pointer is not. Therefore, the restrictions on
subobjects of the dummy argument apply to the pointer in contexts where it is used as a pointer, but not in
contexts where it is dereferenced to indicate its target. For example, if X is a dummy argument of derived
type with an integer pointer component P, and X is INTENT (IN), then the statement

X%P => NEW_TARGET

is prohibited, but

X%P = 0

is allowed (provided that X%P is associated with a defi nable target).
Similarly, the INTENT restrictions on pointer dummy arguments apply only to the association of the
dummy argument; they do not restrict the operations allowed on its target.

You are passing the target, not the pointer, hence the INTENT(IN) attribute does not apply.

I will comment that there was some ambiguity in the language relating to INTENT and pointers that was cleared up through an interpretation and codified in F2003. I suspect the compiler did not fully catch up to that.

I will report this to the developers.
0 Kudos
IanH
Honored Contributor III
1,249 Views
Another INTENT(IN) wrinkle, this time to do with polymorphic components. Both procedures take an INTENT(IN) argument, but the compiler (11.1.067) thinks that the type bound procedure (DoesNotModifyAType) might be up to no good when called from DoesNotModifyWrapper.

[fortran]MODULE Wrapper

IMPLICIT NONE

TYPE :: AType
INTEGER :: i
CONTAINS
PROCEDURE :: DoesNotModifyAType
END TYPE AType

TYPE :: WrapperType
CLASS(AType), ALLOCATABLE :: item
END TYPE WrapperType

CONTAINS

SUBROUTINE DoesNotModifyAType(arg)
CLASS(AType), INTENT(IN) :: arg
!****
PRINT *, arg%i
END SUBROUTINE DoesNotModifyAType

SUBROUTINE DoesNotModifyWrapper(arg)
TYPE(WrapperType), INTENT(IN) :: arg(:)
CALL arg(1)%item%DoesNotModifyAType
END SUBROUTINE DoesNotModifyWrapper

END MODULE Wrapper

PROGRAM snoop_dog
USE Wrapper
IMPLICIT NONE
TYPE(WrapperType), ALLOCATABLE :: dizzee_rascal(:)
ALLOCATE(dizzee_rascal(2))
ALLOCATE(AType:: dizzee_rascal(1)%item)
dizzee_rascal(1)%item%i = 1
CALL DoesNotModifyWrapper(dizzee_rascal)
END PROGRAM snoop_dog
[/fortran]

(Edit to add...)

Replace/augment the relevant parts of the module with the following for a work around, or an internal compiler error, at the programmers option:

[fortran] SUBROUTINE DoesNotModifyWrapper(arg)
    TYPE(WrapperType), INTENT(IN) :: arg(:)
    !CALL arg(1)%item%DoesNotModifyAType
    CALL zzz(arg(1))
  END SUBROUTINE DoesNotModifyWrapper
  
  SUBROUTINE zzz(arg)
    !TYPE(WrapperType), INTENT(IN) :: arg    ! This one for ICE
    CLASS(WrapperType), INTENT(IN) :: arg    ! This one works.
    CALL arg%item%DoesNotModifyAType
  END SUBROUTINE zzz
  
[/fortran]


0 Kudos
Steven_L_Intel1
Employee
1,249 Views
The original issue is escalated as DPD200164419. The F2003 standard clarifies that INTENT(IN) applies to the pointer itself and not the pointer's target.

Your other issue appears resolved in version 12. I get neither the error nor the ICE.
0 Kudos
Steven_L_Intel1
Employee
1,249 Views
I expect this issue to be resolved in Update 3.
0 Kudos
IanH
Honored Contributor III
1,249 Views
12.1.x and 13.0.0 erroneously prevent use of an associate name in a variable definition context when that associate name is associated with a pointer component of an argument that is intent(in): [fortran] MODULE ATypeAndAProc IMPLICIT NONE TYPE :: AType INTEGER, POINTER :: ptr_comp END TYPE AType CONTAINS SUBROUTINE AProc(arg) TYPE(AType), INTENT(IN) :: arg !**** arg%ptr_comp = 1 ! This is now ok... ASSOCIATE (i => arg%ptr_comp) i = 1 ! but this is not (#6780) END ASSOCIATE END SUBROUTINE AProc END MODULE ATypeAndAProc PROGRAM AssocateAndPointerIntent USE ATypeAndAProc IMPLICIT NONE INTEGER, TARGET :: i TYPE(AType) :: obj obj%ptr_comp => i CALL AProc(obj) END PROGRAM AssocateAndPointerIntent [/fortran] [plain] >ifort /check:all /warn:all /standard-semantics AssociateAndPointerIntent.f90 Intel(R) Visual Fortran Compiler XE for applications running on IA-32, Version 13.0.0.089 Build 20120731 Copyright (C) 1985-2012 Intel Corporation. All rights reserved. AssociateAndPointerIntent.f90(12): error #6780: A dummy argument with the INTENT(IN) attribute shall not be defined nor become undefined. i = 1 ! but this is not (#6780) ------^ compilation aborted for AssociateAndPointerIntent.f90 (code 1) [/plain]
0 Kudos
Steven_L_Intel1
Employee
1,249 Views
Thanks - escalated as issue DPD200236088.
0 Kudos
Steven_L_Intel1
Employee
1,249 Views

This last issue (error 6780) is fixed for a release later this year.

0 Kudos
Reply