Strange behaviour of an array of types constituted by two or more integers

Hello everyone,
I’ve encountered a strange problem when using derived datatypes with two or more integers.
Here is the class A. It has set and get methods for the two only integer attributes

module a_class

implicit none

type, public :: a

private

integer :: var=-1
integer :: varlen=-1

contains

procedure, public :: set_var => set_var_fn
procedure, public :: set_varlen => set_varlen_fn
procedure, public :: get_var => get_var_fn
procedure, public :: get_varlen => get_varlen_fn

end type a

private 

contains 

subroutine set_var_fn(this,v)
implicit none

class(a), intent(out) :: this
integer, intent(in)   :: v

this%var=v

end subroutine set_var_fn

subroutine set_varlen_fn(this,v)
implicit none
class(a), intent(out) :: this
integer, intent(in)   :: v
        
this%varlen=v
end subroutine set_varlen_fn

subroutine get_var_fn(this,v)
implicit none

class(a), intent(in) :: this
integer, intent(out)   :: v

v=this%var

end subroutine get_var_fn

subroutine get_varlen_fn(this,v)
implicit none
class(a), intent(in) :: this
integer, intent(out)   :: v
    
v=this%varlen
end subroutine get_varlen_fn
end module a_class

This is the b_class, just an array of A types

module b_class

use a_class
implicit none

type, public :: b

private

type(a), allocatable, dimension(:) :: a_list
integer :: a_list_len=0

contains

procedure, public :: add_a   => add_a_fn


end type b

private 

contains 

subroutine add_a_fn(this,av,av1)
    implicit none
class(b),intent(inout) :: this
integer, intent(in)    :: av,av1
type(a), allocatable, dimension(:) :: temp
integer :: v,i
type(a)     :: aa

call aa%set_var(av)
call aa%set_varlen(av1)

if (.not.(allocated(this%a_list))) then
    allocate(this%a_list(1))
    this%a_list_len=1
    this%a_list(1)=aa
else
    allocate(temp(this%a_list_len+1))
    temp=this%a_list
    temp(this%a_list_len+1)=aa
    deallocate(this%a_list)
    allocate(this%a_list(this%a_list_len+1))
    this%a_list=temp
    deallocate(temp)
    this%a_list_len=this%a_list_len+1
endif
write(6,*)'a added'
do i=1,this%a_list_len
    call this%a_list(i)%get_var(v)
    write(6,*)'a ',i,'var ',v
end do

end subroutine add_a_fn
end module b_class

And this is a test program. It tests only the insertion of one A types…so let’s forget at the moment the array resizing

program test
use b_class
implicit none
type(b) :: bb

call bb%add_a(30,31)

end program test

But the output is

a added
a            1 var           -1

when I expected

 a added
 a            1 var           30

Anyone who knows the answer?
Thanks

2 Likes

Try changing all the lines like
class(a), intent(out) :: this
to
class(a), intent(inout) :: this
or
class(a) :: this
Then I get the expected result. (FYI, I usually avoid using intent(out) for derived-type arguments for several reasons…)

2 Likes

Thank you.
I cannot understand why is acting like this… Intent(out) must work, it only read data from that class…

@Rob777,

Look into the standard (or Modern Fortran Explained) for the semantics of INTENT(OUT).

With your call aa%set_varlen(av1) instruction, the “set” instruction in the previous line gets effectively nullified because aa variable gets defined via the dummy argument to “set_varlen” procedure and the ‘var’ member of ‘aa’ gets initialized with a value of -1.

Modern Fortran Style and Usage by Clerman and Spector is a good book you can review to get a detailed and structured explanation of a lot of such intricacies in the language.

4 Likes

My rule of thumb for deciding between intent(out) and intent(in out) is to ask if I’m mutating an existing value (in out) or if I’m giving it a value for the first time (out). Another way to read @FortranFan’s answer is that intent(out) means the variable comes into the procedure as a “clean slate”. For that reason, it is pretty rare in OOP to declare the class argument as intent(out), since it is usually not intended that all its internal state be lost.

3 Likes

Thanks to everyone for your help and explanations.