Parameterized derived-type contained procedure failure

Hello,

I am trying to use parameterized derived-types that contain procedures (preferably generic operator procedure to add the definition of + to this derived-type). However, I get the following error message (I am compiling using gfortran version 12.2.0):

8 |     procedure, pass(this) :: print => print_out
  |             1
Error: Argument ‘this’ of ‘print_out’ with PASS(this) at (1) must be of the derived-type ‘my_type’

Here is the module:

module my_module
 implicit none

 type, public :: my_type(n)
   integer, len :: n
   real, dimension(n) :: data
 contains
   procedure, pass(this) :: print => print_out
 end type my_type

contains
 subroutine print_out(this)
   implicit none
   class(my_type(*)), intent(in) :: this

   write(*,*) size(this%data), this%data

 end subroutine print_out
end module my_module

And here is the main program calling the module (but probably not necessary/required for highlighting the problem).

program main
 use my_module
 implicit none

 type(my_type(:)), allocatable, dimension(:) :: my_array
 integer :: i, j
 integer, allocatable, dimension(:) :: n_list

 n_list = [1, 4, 3, 2]
 allocate(my_array(0:size(n_list)-1), source=(/ (&
      my_type(&
      n=n_list(i),&
      data=(/(0.0, j=1,n_list(i))/)&
      ), i=1,size(n_list) ) /))

 do i = lbound(my_array,dim=1), ubound(my_array,dim=1)
    write(*,*) i
    call my_array(i)%print()
 end do
end program main

I have a feeling that this may not be possible, but I have only started using parameterized derived-types a couple of hours ago. Any help would be greatly appreciated. :slight_smile:

1 Like

I believe the code you have in the module is valid. So if the compiler is giving you an error there, I think it’s a compiler bug. There are still lots of those in various compilers regarding PDTs, as they aren’t widely used.

That said, the way you try to use it in the program is not valid. You cannot have an array of objects with different length type parameters. As an illustration try using an explicit shape array, or try allocating the whole array without source or mold. It would look like

type(my_type(4) :: my_array(0:3)

or

allocate(my_type(4) :: my_array(0:3))

Thanks for your help, @everythingfunctional. It’d be annoying if it were a compiler bug, but would make sense.

Regarding the program not being valid, I’ve been using this for the past few hours and it has compiled and worked as expected just fine. I’m not sure if this is illegal code that has got past the compiler (is this what you mean by ‘not valid’?), but it works for me and throws up no errors. Find below the edited code and output (I have commented out the contains procedure in the module until I can fix it or know that it won’t work).

If what I have put below in this reply shouldn’t work, but somehow has, let me know and I will be cautious of using it in the future.

Program:

program main
 use my_module
 implicit none
 type(my_type(:)), allocatable, dimension(:) :: my_array
 integer :: i, j
 integer, allocatable, dimension(:) :: n_list

 n_list = [1, 4, 3, 2]
 allocate(my_array(0:size(n_list)-1), source=(/ (&
      my_type(&
      n=n_list(i),&
      data=(/(0.0, j=1,n_list(i))/)&
      ), i=1,size(n_list) ) /))

 call tester(my_array)

contains
 subroutine tester(input)
   implicit none
   type(my_type(*)), dimension(0:), intent(in) :: input
   integer :: i

   do i = lbound(input,dim=1), ubound(input,dim=1)
      write(*,*) i
      write(*,*) size(input(i)%data), input(i)%data
   end do
 end subroutine tester
end program main

Output:

       0
       1   0.00000000    
       1
       4   0.00000000       0.00000000       0.00000000       0.00000000    
       2
       3   0.00000000       0.00000000       0.00000000    
       3
       2   0.00000000       0.00000000

@nedanator ,

Welcome to Fortran Discourse!

Please note the Fortran language standard does not permit what colloquially is sometimes referred to as “jagged arrays”. In the case of parameterized derived types (PDTs), it means each array element shall have the same derived type parameters. With what you show, it is the length-type parameter that has to be the same for each array element.

But with PDTs, please note the compiler support is generally incomplete or faulty, so please beware. You can also consider Intel Fortran which is now free and it has better support though it too has bugs.

Consider the example below for a brief sketch of some aspects to consider:

   type :: t(n)
      integer, len :: n = 1  !<-- default value; consider if you'd prefer this; can be useful 
   end type
   type(t) :: x !<-- x%n has the default value
   type(t(n=:)), allocatable :: u
   type(t(n=:)), allocatable :: v(:)
   allocate( t(n=2) :: u ) ! Ok, u%n = 2
   v = [ t(n=2)(), t(n=3)() ]  !<-- Not allowed: jagged array!
   !allocate( v, source=[ t(n=3)(), t(n=4)() ] )  !<-- Not allowed: jagged array!
end

Hi @FortranFan,

Thank you for the welcome. It’s good to be here. :slight_smile:

You mention that “jagged arrays” are not permitted by Fortran language standard. Does this include all types of “jagged arrays”, or just arrays of PDTs? i.e, is this permitted:

program main
 implicit none
 type :: test_type
   integer, allocatable, dimension(:) :: list
 end type test_type

 type(test_type), allocatable, dimension(:) :: test

 allocate(test(4))
 do i=1,4
    allocate(test(i)%list(i))
 end do

end program main

That is exactly the workaround to “emulate” a ragged array. I do this on a pretty regular basis.

1 Like

@nedanator ,

Please note what the semantics of the Fortran standard require with arrays is type parameter conformity among the elements of the array. Now note there are two type parameters: the so-called kind-type parameter and the length-type parameter. Each element of an array shall have the same kind-type and/or length-type parameters, as applicable to the type in question. So my point above re: “jagged arrays” refers to this aspect of the standard vis-a-vis your PDT that has a length-type parameter.

To understand this more broadly, a good example is the CHARACTER intrinsic type. See this thread. So one can write in Fortran:

..
   integer, parameter :: CK = selected_char_kind('ISO_10646')
  ..
   character(kind=CK, len=*), parameter :: string = CK_'𨉟呐㗂越'
..

So here, note the named constant string has a kind-parameter of CK corresponding to ISO 10646 character set and it has a length-parameter that corresponds to the length required by the processor (compiler) to hold the supplied string literal which is technically in Vietnamese but as represented by the UTF-8 encoding.

Thus if you are creating an array of strings using the CHARACTER intrinsic type, each element of the array shall have the same kind and length.

But now, note the ALLOCATABLE aspect is not a type parameter, rather it involves different semantics pertaining to an attribute of the type component of a derived type or an object (variable) in a program. Thus the use of the so-called wrapper derived type with type components of the ALLOCATABLE attribute is a workaround to have jagged arrays. So with workaround, each element of the array is of the same type i.e., the wrapper derived type. And since this wrapper type has no type parameters, the standard semantics with type parameter conformity is not an issue. That is not the case when you use a parameterized derived type design since such a type has type parameters.

1 Like