Data-pointer-object and unlimited polymorphic target

program main
    implicit none
    type pair
        sequence
        real::x
        integer::y
    end type pair
    type(pair),target::p
    type(pair),pointer::ptr_pair
    integer,target::i
    integer,pointer::i_ptr
    p=pair(1.0,2)
    ptr_pair=>view(p)
    print*,ptr_pair
    i=1  
    i_ptr => view(i)!WRONG
    print*,i_ptr
contains
   function view(a)result(b)
      class(*),intent(in),target::a
      class(*),pointer::b
      b=>a
   end function view
end program main

Compilation error

app/example.f90:16:5:

   16 |     i_ptr => view(i)
      |     1~~~~~
Error: Data-pointer-object at (1) must be unlimited polymorphic, or of a type with the BIND or SEQUENCE attribute, to be compatible with an unlimited polymorphic target

Why intrinsic type pointer not permit point to polymorphic, but user defined type allowed. Is intrinsic type has sequence attribute?

I think the reason is that a derived type can be used as the parent of another type, whereas intrinsic types cannot. (At least that seems a plausible difference :).) It does not matter whether there are any actual procedures/methods connected to the type.

Worth testing with different compilers.

Flang:

error: Semantic errors in /app/example.f90
/app/example.f90:13:5: error: function result type 'CLASS(*)' is not compatible with pointer type 'pair'
      ptr_pair=>view(p)
      ^^^^^^^^^^^^^^^^^
/app/example.f90:16:5: error: function result type 'CLASS(*)' is not compatible with pointer type 'INTEGER(4)'
      i_ptr => view(i)!WRONG
      ^^^^^^^^^^^^^^^^
Compiler returned: 1

NAG:

> nagfor example.f90 
NAG Fortran Compiler Release 7.2(Shin-Urayasu) Build 7203
Error: example.f90, line 16: Pointer assignment of CLASS(*) target to INTEGER pointer
[NAG Fortran Compiler error termination, 1 error]

Seems a bit like a dark corner of the language. It is probably worth looking into the J3 Fortran interpretation document to see what it says about a pointer to an unlimited polymorphic variable.

As shown in 24-007.pdf, same as gfortran report

C1017 (R1034) If data-target is unlimited polymorphic, data-pointer-object shall be unlimited polymorphic, or 
of a type with the BIND attribute or the SEQUENCE attribute.

I did not know about this, but omg, who thought this was a good idea?

Seems like it has something to do with alignment constraints which both C structs and sequence types have.
It also suggests a workaround to get the desired result:

    type :: int_seq
        sequence
        integer :: i
    end type
    integer,target::i
    type(int_seq),pointer::i_ptr
    i=1  
    i_ptr => view(i) ! Now it works
    print*, i_ptr%i

It does look like a loophole in the Wirth sense.

Exactly. Why on earth would you want something like this to be valid?

type :: four_bytes
  sequence
  integer(c_int8) :: i1, i2, i3, i4
end type
type(who_tf_knows), target :: thing
type(four_bytes), pointer :: rep
thing = ...
! lets just see what four of the bytes
! starting at the beginning of this object look like
rep => view(thing)
print *, rep

I’m guessing there is some other text somewhere that still says this is invalid, but the compiler really ought to yell loudly about it.

Maybe it is useful to write some dictionary-like object where the return type is polymorphic? But I don’t understand why intrinsic types aren’t supported, if sequence types are. It would be nice to hear from the standard-bearers on why they thought this feature is useful.

Yep, found it. 10.2.2.3 Data pointer assignment

If the pointer object is of a type with the BIND attribute or the SEQUENCE attribute, the dynamic type of the pointer target shall be that type.

1 Like

I think that is still interesting, because you can write a function that returns objects with different dynamic types:

module tmod
    implicit none
    type :: t_int
        integer :: val
    end type
    type :: t_real
        real :: val
    end type
    type :: t_logical
        sequence
        logical :: val = .false.
    end type

    integer, parameter :: tf_int = 1
    integer, parameter :: tf_real = 2
    integer, parameter :: tf_logical = 3

    type(t_int), target :: a = t_int(42)
    type(t_real), target :: b = t_real(33.0)
    type(t_logical), target :: c

contains

    function ret(iflag)
        integer :: iflag
        class(*), pointer :: ret
        select case(iflag)
        case(tf_int)
            ret => a
        case(tf_real)
            ret => b
        case(tf_logical)
            ret => c
        case default
            ret => null()
        end select
    end function

end module

program main
    use tmod

    integer :: i, iflag
    class(*), pointer :: r
    type(t_logical), pointer :: rl

    iflag = 1
    do i = 1, 9
        
        r => ret(iflag)
        if (.not. associated(r)) cycle
        if (iflag == tf_logical) then
            rl => r
            print *, rl%val
        else
            select type(r)
            type is (t_int)
                print *, r%val
            type is (t_real)
                print *, r%val
            end select
        end if
        iflag = modulo(i,3) + 1
    end do

end program

By the way, I wish that fortran intrinsic function like findloc can be used for user defined type with sequence attribute.It just combined with static type,so it should have something like Eq Trait

Can’t you just use component selection?

type :: t_int
   sequence
   integer :: val 
end type

type(t_int) :: a(100)

a = t_int(100)
a(42) = t_int(1)

print *, find(a, t_int(1))

contains
    
    pure function find(a, val) result(res)
        type(t_int), intent(in) :: a(:), val
        integer :: res
        intrinsic :: findloc
        res = findloc(a%val,val%val,dim=1)
   end function

end