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.