One possible pattern may be like this…?
field_mod.f90:
module field_mod
implicit none
type Field3
integer :: ndims(3), nsize
real, allocatable :: data(:,:,:)
contains
procedure :: init, show
end type
contains
subroutine init(this, ndims)
class(Field3), target :: this
integer, intent(in) :: ndims(3)
this% ndims(:) = ndims(:)
this% nsize = product( ndims )
allocate( this% data( ndims(1), ndims(2), ndims(3) ) )
end subroutine
subroutine show(this)
class(Field3), intent(in) :: this
integer :: i3
print *, "Field values:"
do i3 = 1, this% ndims(3)
print "(a,i0,a,*(2x,g0))", " val(:,:,",i3,") =", this% data(:,:,i3)
end do
end subroutine
end module
elec_field_mod.f90:
module elec_field_mod
use field_mod, only: Field3
implicit none
type, extends(Field3) :: ElecField
real, pointer, contiguous :: Ex(:,:,:) !! Cartesian array view
real, pointer, contiguous :: Ex_lin(:) !! linear array view
contains
procedure :: init => EF_init
end type
contains
subroutine EF_init(this, ndims)
class(ElecField), target :: this
integer, intent(in) :: ndims(3)
call this% Field3% init( ndims=ndims )
this% Ex => this% data !! Cartesian access
this% Ex_lin( 1 : this%nsize ) => this% data !! linear access
end subroutine
end module
main.f90:
program main
use elec_field_mod, only: ElecField
implicit none
type(ElecField), target :: ef
integer :: i, n
n = 2
call ef% init( ndims=[n,n,n] )
print *, "shape( ef% Ex ) = ", shape( ef% Ex )
print *, "shape( ef% Ex_lin ) = ", shape( ef% Ex_lin )
ef% Ex_lin(:) = [(i, i = 1, n**3)]
call ef% show()
end program
build.sh:
comp="gfortran -fcheck=all -Wall -Wextra"
# comp="flang -pedantic"
echo "comp = ${comp}"
${comp} field_mod.f90 elec_field_mod.f90 main.f90
# ${comp} field_mod.f90 elec_field_compo_mod.f90 main.f90
Results (on macOS 15.6):
!! gfortran-15.1
shape( ef% Ex ) = 2 2 2
shape( ef% Ex_lin ) = 8
Field values:
val(:,:,1) = 1.00000000 2.00000000 3.00000000 4.00000000
val(:,:,2) = 5.00000000 6.00000000 7.00000000 8.00000000
!! flang-21.1
shape( ef% Ex ) = 2 2 2
shape( ef% Ex_lin ) = 8
Field values:
val(:,:,1) = 1. 2. 3. 4.
val(:,:,2) = 5. 6. 7. 8.
Actually, I guess “composition” might be more flexible (though depending on cases…). In that case the next version might be more convenient (which gives the same result as elec_field_mod.f90
).
elec_field_compo_mod.f90:
module elec_field_mod
use field_mod, only: Field3
implicit none
type :: ElecField
type(Field3) :: field
real, pointer, contiguous :: Ex(:,:,:) !! Cartesian array view
real, pointer, contiguous :: Ex_lin(:) !! linear array view
contains
procedure :: init, show
end type
contains
subroutine init(this, ndims)
class(ElecField), target :: this
integer, intent(in) :: ndims(3)
call this% field% init( ndims=ndims )
this% Ex => this% field% data !! Cartesian access
this% Ex_lin( 1 : this% field% nsize ) => this% field% data !! linear access
end subroutine
subroutine show(this)
class(ElecField), intent(in) :: this
call this% field% show() !! forwarding
end subroutine
end module
Indeed, I hope that future Fortran will provide an “alias” like feature for defining alternative name access for type components (rather than using pointers, like above…), so as to avoid various pitfalls of pointers (eg, it may be necessary to define custom assignment). So something like…
type :: ElecField
type(Field3) :: field
alias :: Ex => field% data
!! or
forwarding :: Ex => field% data, show => field% show
!! etc
end type
I think such a feature will also be convenient for gradual “refactoring” (renaming of components).