! Two-dimensional contiguous array class with non-uniform second dimension stored in shared memory. It is implemented this way to ! yield maximal memory efficiency ! Templated for these types ! And these integer kinds can be used for indexing and allocation module shared_ragged_array use constants, only: dp, int32, int64 use shared_array, only: shared_array_real_t, shared_array_int32_t, shared_array_int64_t, & shared_array_cmplx_t, shared_array_bool_t implicit none private public :: shared_ragged_array_real_t ! This type only serves the purpose to create an addressing array for quasi-2D-access -> allows to directly get pointers to ! sub-arrays type :: auxiliary_real_t real(dp), pointer :: res(:) => null() end type auxiliary_real_t !> Shared memory 2-D array template with non-uniform 2nd dimension ("ragged") of type real type :: shared_ragged_array_real_t private ! Actual shared resource type(shared_array_real_t) :: data_array ! Indexing array to hold pointers to the sub-arrays type(auxiliary_real_t), allocatable :: ptr(:) ! Sizes of the sub-arrays integer(int64), allocatable :: store_sizes(:) contains ! These functions work with different integer kinds as index values (index_types) ! Generic interfaces ! generic :: shared_alloc => shared_alloc_real_int32 ! sub returns a pointer to a 1d subarray (sub1d) or a specific entry (sub2d) generic :: sub => pos_1d_real_int32, pos_2d_real_int32 ! Set val sets a specific value of the array generic :: set_val => set_val_real_int32 ! Index kind-specific implementations procedure :: shared_alloc_real_int32 procedure :: pos_1d_real_int32 procedure :: pos_2d_real_int32 procedure :: set_val_real_int32 ! Generic interfaces ! generic :: shared_alloc => shared_alloc_real_int64 ! sub returns a pointer to a 1d subarray (sub1d) or a specific entry (sub2d) generic :: sub => pos_1d_real_int64, pos_2d_real_int64 ! Set val sets a specific value of the array generic :: set_val => set_val_real_int64 ! Index kind-specific implementations procedure :: shared_alloc_real_int64 procedure :: pos_1d_real_int64 procedure :: pos_2d_real_int64 procedure :: set_val_real_int64 procedure :: shared_dealloc => shared_dealloc_real ! Sync synchronizes the content of the array within the inter-node communicator procedure :: sync => sync_real ! For setting up the subarray pointers procedure :: reassign_pointers => reassign_pointers_real end type shared_ragged_array_real_t public :: shared_ragged_array_int64_t ! This type only serves the purpose to create an addressing array for quasi-2D-access -> allows to directly get pointers to ! sub-arrays type :: auxiliary_int64_t integer(int64), pointer :: res(:) => null() end type auxiliary_int64_t !> Shared memory 2-D array template with non-uniform 2nd dimension ("ragged") of type int64 type :: shared_ragged_array_int64_t private ! Actual shared resource type(shared_array_int64_t) :: data_array ! Indexing array to hold pointers to the sub-arrays type(auxiliary_int64_t), allocatable :: ptr(:) ! Sizes of the sub-arrays integer(int64), allocatable :: store_sizes(:) contains ! These functions work with different integer kinds as index values (index_types) ! Generic interfaces ! generic :: shared_alloc => shared_alloc_int64_int32 ! sub returns a pointer to a 1d subarray (sub1d) or a specific entry (sub2d) generic :: sub => pos_1d_int64_int32, pos_2d_int64_int32 ! Set val sets a specific value of the array generic :: set_val => set_val_int64_int32 ! Index kind-specific implementations procedure :: shared_alloc_int64_int32 procedure :: pos_1d_int64_int32 procedure :: pos_2d_int64_int32 procedure :: set_val_int64_int32 ! Generic interfaces ! generic :: shared_alloc => shared_alloc_int64_int64 ! sub returns a pointer to a 1d subarray (sub1d) or a specific entry (sub2d) generic :: sub => pos_1d_int64_int64, pos_2d_int64_int64 ! Set val sets a specific value of the array generic :: set_val => set_val_int64_int64 ! Index kind-specific implementations procedure :: shared_alloc_int64_int64 procedure :: pos_1d_int64_int64 procedure :: pos_2d_int64_int64 procedure :: set_val_int64_int64 procedure :: shared_dealloc => shared_dealloc_int64 ! Sync synchronizes the content of the array within the inter-node communicator procedure :: sync => sync_int64 ! For setting up the subarray pointers procedure :: reassign_pointers => reassign_pointers_int64 end type shared_ragged_array_int64_t public :: shared_ragged_array_int32_t ! This type only serves the purpose to create an addressing array for quasi-2D-access -> allows to directly get pointers to ! sub-arrays type :: auxiliary_int32_t integer(int32), pointer :: res(:) => null() end type auxiliary_int32_t !> Shared memory 2-D array template with non-uniform 2nd dimension ("ragged") of type int32 type :: shared_ragged_array_int32_t private ! Actual shared resource type(shared_array_int32_t) :: data_array ! Indexing array to hold pointers to the sub-arrays type(auxiliary_int32_t), allocatable :: ptr(:) ! Sizes of the sub-arrays integer(int64), allocatable :: store_sizes(:) contains ! These functions work with different integer kinds as index values (index_types) ! Generic interfaces ! generic :: shared_alloc => shared_alloc_int32_int32 ! sub returns a pointer to a 1d subarray (sub1d) or a specific entry (sub2d) generic :: sub => pos_1d_int32_int32, pos_2d_int32_int32 ! Set val sets a specific value of the array generic :: set_val => set_val_int32_int32 ! Index kind-specific implementations procedure :: shared_alloc_int32_int32 procedure :: pos_1d_int32_int32 procedure :: pos_2d_int32_int32 procedure :: set_val_int32_int32 ! Generic interfaces ! generic :: shared_alloc => shared_alloc_int32_int64 ! sub returns a pointer to a 1d subarray (sub1d) or a specific entry (sub2d) generic :: sub => pos_1d_int32_int64, pos_2d_int32_int64 ! Set val sets a specific value of the array generic :: set_val => set_val_int32_int64 ! Index kind-specific implementations procedure :: shared_alloc_int32_int64 procedure :: pos_1d_int32_int64 procedure :: pos_2d_int32_int64 procedure :: set_val_int32_int64 procedure :: shared_dealloc => shared_dealloc_int32 ! Sync synchronizes the content of the array within the inter-node communicator procedure :: sync => sync_int32 ! For setting up the subarray pointers procedure :: reassign_pointers => reassign_pointers_int32 end type shared_ragged_array_int32_t public :: shared_ragged_array_cmplx_t ! This type only serves the purpose to create an addressing array for quasi-2D-access -> allows to directly get pointers to ! sub-arrays type :: auxiliary_cmplx_t complex(dp), pointer :: res(:) => null() end type auxiliary_cmplx_t !> Shared memory 2-D array template with non-uniform 2nd dimension ("ragged") of type cmplx type :: shared_ragged_array_cmplx_t private ! Actual shared resource type(shared_array_cmplx_t) :: data_array ! Indexing array to hold pointers to the sub-arrays type(auxiliary_cmplx_t), allocatable :: ptr(:) ! Sizes of the sub-arrays integer(int64), allocatable :: store_sizes(:) contains ! These functions work with different integer kinds as index values (index_types) ! Generic interfaces ! generic :: shared_alloc => shared_alloc_cmplx_int32 ! sub returns a pointer to a 1d subarray (sub1d) or a specific entry (sub2d) generic :: sub => pos_1d_cmplx_int32, pos_2d_cmplx_int32 ! Set val sets a specific value of the array generic :: set_val => set_val_cmplx_int32 ! Index kind-specific implementations procedure :: shared_alloc_cmplx_int32 procedure :: pos_1d_cmplx_int32 procedure :: pos_2d_cmplx_int32 procedure :: set_val_cmplx_int32 ! Generic interfaces ! generic :: shared_alloc => shared_alloc_cmplx_int64 ! sub returns a pointer to a 1d subarray (sub1d) or a specific entry (sub2d) generic :: sub => pos_1d_cmplx_int64, pos_2d_cmplx_int64 ! Set val sets a specific value of the array generic :: set_val => set_val_cmplx_int64 ! Index kind-specific implementations procedure :: shared_alloc_cmplx_int64 procedure :: pos_1d_cmplx_int64 procedure :: pos_2d_cmplx_int64 procedure :: set_val_cmplx_int64 procedure :: shared_dealloc => shared_dealloc_cmplx ! Sync synchronizes the content of the array within the inter-node communicator procedure :: sync => sync_cmplx ! For setting up the subarray pointers procedure :: reassign_pointers => reassign_pointers_cmplx end type shared_ragged_array_cmplx_t public :: shared_ragged_array_bool_t ! This type only serves the purpose to create an addressing array for quasi-2D-access -> allows to directly get pointers to ! sub-arrays type :: auxiliary_bool_t logical, pointer :: res(:) => null() end type auxiliary_bool_t !> Shared memory 2-D array template with non-uniform 2nd dimension ("ragged") of type bool type :: shared_ragged_array_bool_t private ! Actual shared resource type(shared_array_bool_t) :: data_array ! Indexing array to hold pointers to the sub-arrays type(auxiliary_bool_t), allocatable :: ptr(:) ! Sizes of the sub-arrays integer(int64), allocatable :: store_sizes(:) contains ! These functions work with different integer kinds as index values (index_types) ! Generic interfaces ! generic :: shared_alloc => shared_alloc_bool_int32 ! sub returns a pointer to a 1d subarray (sub1d) or a specific entry (sub2d) generic :: sub => pos_1d_bool_int32, pos_2d_bool_int32 ! Set val sets a specific value of the array generic :: set_val => set_val_bool_int32 ! Index kind-specific implementations procedure :: shared_alloc_bool_int32 procedure :: pos_1d_bool_int32 procedure :: pos_2d_bool_int32 procedure :: set_val_bool_int32 ! Generic interfaces ! generic :: shared_alloc => shared_alloc_bool_int64 ! sub returns a pointer to a 1d subarray (sub1d) or a specific entry (sub2d) generic :: sub => pos_1d_bool_int64, pos_2d_bool_int64 ! Set val sets a specific value of the array generic :: set_val => set_val_bool_int64 ! Index kind-specific implementations procedure :: shared_alloc_bool_int64 procedure :: pos_1d_bool_int64 procedure :: pos_2d_bool_int64 procedure :: set_val_bool_int64 procedure :: shared_dealloc => shared_dealloc_bool ! Sync synchronizes the content of the array within the inter-node communicator procedure :: sync => sync_bool ! For setting up the subarray pointers procedure :: reassign_pointers => reassign_pointers_bool end type shared_ragged_array_bool_t contains subroutine shared_alloc_real_int32(this, sizes) class(shared_ragged_array_real_t), intent(inout) :: this integer(int32), intent(in) :: sizes(:) integer(int64) :: n_entries ! Allocate the shared resource call this%data_array%shared_alloc(int(sum(sizes), int64)) ! Assign the pointers n_entries = size(sizes, kind=int64) allocate(this%ptr(n_entries)) ! Keep a local copy of sizes (fortran 2003 automatic allocation) allocate(this%store_sizes(n_entries)) this%store_sizes(1:n_entries) = int(sizes(1:n_entries), int64) ! Set the internal pointers call this%reassign_pointers() end subroutine shared_alloc_real_int32 subroutine shared_alloc_real_int64(this, sizes) class(shared_ragged_array_real_t), intent(inout) :: this integer(int64), intent(in) :: sizes(:) integer(int64) :: n_entries ! Allocate the shared resource call this%data_array%shared_alloc(int(sum(sizes), int64)) ! Assign the pointers n_entries = size(sizes, kind=int64) allocate(this%ptr(n_entries)) ! Keep a local copy of sizes (fortran 2003 automatic allocation) allocate(this%store_sizes(n_entries)) this%store_sizes(1:n_entries) = int(sizes(1:n_entries), int64) ! Set the internal pointers call this%reassign_pointers() end subroutine shared_alloc_real_int64 !------------------------------------------------------------------------------------------! subroutine shared_dealloc_real(this) class(shared_ragged_array_real_t), intent(inout) :: this call this%data_array%shared_dealloc() if (allocated(this%ptr)) deallocate(this%ptr) if (allocated(this%store_sizes)) deallocate(this%store_sizes) end subroutine shared_dealloc_real !------------------------------------------------------------------------------------------! subroutine reassign_pointers_real(this) class(shared_ragged_array_real_t), intent(inout) :: this integer(int64) :: n_entries integer(int64) :: i, win_start, win_end n_entries = size(this%store_sizes, kind=int64) win_start = 1 do i = 1, n_entries win_end = win_start - 1 + this%store_sizes(i) this%ptr(i)%res => this%data_array%ptr(win_start:win_end) win_start = win_end + 1 end do end subroutine reassign_pointers_real !------------------------------------------------------------------------------------------! subroutine set_val_real_int32(this, i, j, val) class(shared_ragged_array_real_t), intent(inout) :: this integer(int32), intent(in) :: i, j real(dp), intent(in) :: val this%ptr(i)%res(j) = val end subroutine set_val_real_int32 subroutine set_val_real_int64(this, i, j, val) class(shared_ragged_array_real_t), intent(inout) :: this integer(int64), intent(in) :: i, j real(dp), intent(in) :: val this%ptr(i)%res(j) = val end subroutine set_val_real_int64 !------------------------------------------------------------------------------------------! subroutine sync_real(this) class(shared_ragged_array_real_t), intent(inout) :: this call this%data_array%sync() end subroutine sync_real !------------------------------------------------------------------------------------------! function pos_2d_real_int32(this, i, j) result(val) class(shared_ragged_array_real_t), intent(inout) :: this integer(int32), intent(in) :: i, j real(dp) :: val val = this%ptr(i)%res(j) end function pos_2d_real_int32 !------------------------------------------------------------------------------------------! function pos_1d_real_int32(this, i) result(pt) class(shared_ragged_array_real_t), intent(inout) :: this integer(int32), intent(in) :: i real(dp), pointer :: pt(:) pt => this%ptr(i)%res end function pos_1d_real_int32 function pos_2d_real_int64(this, i, j) result(val) class(shared_ragged_array_real_t), intent(inout) :: this integer(int64), intent(in) :: i, j real(dp) :: val val = this%ptr(i)%res(j) end function pos_2d_real_int64 !------------------------------------------------------------------------------------------! function pos_1d_real_int64(this, i) result(pt) class(shared_ragged_array_real_t), intent(inout) :: this integer(int64), intent(in) :: i real(dp), pointer :: pt(:) pt => this%ptr(i)%res end function pos_1d_real_int64 subroutine shared_alloc_int64_int32(this, sizes) class(shared_ragged_array_int64_t), intent(inout) :: this integer(int32), intent(in) :: sizes(:) integer(int64) :: n_entries ! Allocate the shared resource call this%data_array%shared_alloc(int(sum(sizes), int64)) ! Assign the pointers n_entries = size(sizes, kind=int64) allocate(this%ptr(n_entries)) ! Keep a local copy of sizes (fortran 2003 automatic allocation) allocate(this%store_sizes(n_entries)) this%store_sizes(1:n_entries) = int(sizes(1:n_entries), int64) ! Set the internal pointers call this%reassign_pointers() end subroutine shared_alloc_int64_int32 subroutine shared_alloc_int64_int64(this, sizes) class(shared_ragged_array_int64_t), intent(inout) :: this integer(int64), intent(in) :: sizes(:) integer(int64) :: n_entries ! Allocate the shared resource call this%data_array%shared_alloc(int(sum(sizes), int64)) ! Assign the pointers n_entries = size(sizes, kind=int64) allocate(this%ptr(n_entries)) ! Keep a local copy of sizes (fortran 2003 automatic allocation) allocate(this%store_sizes(n_entries)) this%store_sizes(1:n_entries) = int(sizes(1:n_entries), int64) ! Set the internal pointers call this%reassign_pointers() end subroutine shared_alloc_int64_int64 !------------------------------------------------------------------------------------------! subroutine shared_dealloc_int64(this) class(shared_ragged_array_int64_t), intent(inout) :: this call this%data_array%shared_dealloc() if (allocated(this%ptr)) deallocate(this%ptr) if (allocated(this%store_sizes)) deallocate(this%store_sizes) end subroutine shared_dealloc_int64 !------------------------------------------------------------------------------------------! subroutine reassign_pointers_int64(this) class(shared_ragged_array_int64_t), intent(inout) :: this integer(int64) :: n_entries integer(int64) :: i, win_start, win_end n_entries = size(this%store_sizes, kind=int64) win_start = 1 do i = 1, n_entries win_end = win_start - 1 + this%store_sizes(i) this%ptr(i)%res => this%data_array%ptr(win_start:win_end) win_start = win_end + 1 end do end subroutine reassign_pointers_int64 !------------------------------------------------------------------------------------------! subroutine set_val_int64_int32(this, i, j, val) class(shared_ragged_array_int64_t), intent(inout) :: this integer(int32), intent(in) :: i, j integer(int64), intent(in) :: val this%ptr(i)%res(j) = val end subroutine set_val_int64_int32 subroutine set_val_int64_int64(this, i, j, val) class(shared_ragged_array_int64_t), intent(inout) :: this integer(int64), intent(in) :: i, j integer(int64), intent(in) :: val this%ptr(i)%res(j) = val end subroutine set_val_int64_int64 !------------------------------------------------------------------------------------------! subroutine sync_int64(this) class(shared_ragged_array_int64_t), intent(inout) :: this call this%data_array%sync() end subroutine sync_int64 !------------------------------------------------------------------------------------------! function pos_2d_int64_int32(this, i, j) result(val) class(shared_ragged_array_int64_t), intent(inout) :: this integer(int32), intent(in) :: i, j integer(int64) :: val val = this%ptr(i)%res(j) end function pos_2d_int64_int32 !------------------------------------------------------------------------------------------! function pos_1d_int64_int32(this, i) result(pt) class(shared_ragged_array_int64_t), intent(inout) :: this integer(int32), intent(in) :: i integer(int64), pointer :: pt(:) pt => this%ptr(i)%res end function pos_1d_int64_int32 function pos_2d_int64_int64(this, i, j) result(val) class(shared_ragged_array_int64_t), intent(inout) :: this integer(int64), intent(in) :: i, j integer(int64) :: val val = this%ptr(i)%res(j) end function pos_2d_int64_int64 !------------------------------------------------------------------------------------------! function pos_1d_int64_int64(this, i) result(pt) class(shared_ragged_array_int64_t), intent(inout) :: this integer(int64), intent(in) :: i integer(int64), pointer :: pt(:) pt => this%ptr(i)%res end function pos_1d_int64_int64 subroutine shared_alloc_int32_int32(this, sizes) class(shared_ragged_array_int32_t), intent(inout) :: this integer(int32), intent(in) :: sizes(:) integer(int64) :: n_entries ! Allocate the shared resource call this%data_array%shared_alloc(int(sum(sizes), int64)) ! Assign the pointers n_entries = size(sizes, kind=int64) allocate(this%ptr(n_entries)) ! Keep a local copy of sizes (fortran 2003 automatic allocation) allocate(this%store_sizes(n_entries)) this%store_sizes(1:n_entries) = int(sizes(1:n_entries), int64) ! Set the internal pointers call this%reassign_pointers() end subroutine shared_alloc_int32_int32 subroutine shared_alloc_int32_int64(this, sizes) class(shared_ragged_array_int32_t), intent(inout) :: this integer(int64), intent(in) :: sizes(:) integer(int64) :: n_entries ! Allocate the shared resource call this%data_array%shared_alloc(int(sum(sizes), int64)) ! Assign the pointers n_entries = size(sizes, kind=int64) allocate(this%ptr(n_entries)) ! Keep a local copy of sizes (fortran 2003 automatic allocation) allocate(this%store_sizes(n_entries)) this%store_sizes(1:n_entries) = int(sizes(1:n_entries), int64) ! Set the internal pointers call this%reassign_pointers() end subroutine shared_alloc_int32_int64 !------------------------------------------------------------------------------------------! subroutine shared_dealloc_int32(this) class(shared_ragged_array_int32_t), intent(inout) :: this call this%data_array%shared_dealloc() if (allocated(this%ptr)) deallocate(this%ptr) if (allocated(this%store_sizes)) deallocate(this%store_sizes) end subroutine shared_dealloc_int32 !------------------------------------------------------------------------------------------! subroutine reassign_pointers_int32(this) class(shared_ragged_array_int32_t), intent(inout) :: this integer(int64) :: n_entries integer(int64) :: i, win_start, win_end n_entries = size(this%store_sizes, kind=int64) win_start = 1 do i = 1, n_entries win_end = win_start - 1 + this%store_sizes(i) this%ptr(i)%res => this%data_array%ptr(win_start:win_end) win_start = win_end + 1 end do end subroutine reassign_pointers_int32 !------------------------------------------------------------------------------------------! subroutine set_val_int32_int32(this, i, j, val) class(shared_ragged_array_int32_t), intent(inout) :: this integer(int32), intent(in) :: i, j integer(int32), intent(in) :: val this%ptr(i)%res(j) = val end subroutine set_val_int32_int32 subroutine set_val_int32_int64(this, i, j, val) class(shared_ragged_array_int32_t), intent(inout) :: this integer(int64), intent(in) :: i, j integer(int32), intent(in) :: val this%ptr(i)%res(j) = val end subroutine set_val_int32_int64 !------------------------------------------------------------------------------------------! subroutine sync_int32(this) class(shared_ragged_array_int32_t), intent(inout) :: this call this%data_array%sync() end subroutine sync_int32 !------------------------------------------------------------------------------------------! function pos_2d_int32_int32(this, i, j) result(val) class(shared_ragged_array_int32_t), intent(inout) :: this integer(int32), intent(in) :: i, j integer(int32) :: val val = this%ptr(i)%res(j) end function pos_2d_int32_int32 !------------------------------------------------------------------------------------------! function pos_1d_int32_int32(this, i) result(pt) class(shared_ragged_array_int32_t), intent(inout) :: this integer(int32), intent(in) :: i integer(int32), pointer :: pt(:) pt => this%ptr(i)%res end function pos_1d_int32_int32 function pos_2d_int32_int64(this, i, j) result(val) class(shared_ragged_array_int32_t), intent(inout) :: this integer(int64), intent(in) :: i, j integer(int32) :: val val = this%ptr(i)%res(j) end function pos_2d_int32_int64 !------------------------------------------------------------------------------------------! function pos_1d_int32_int64(this, i) result(pt) class(shared_ragged_array_int32_t), intent(inout) :: this integer(int64), intent(in) :: i integer(int32), pointer :: pt(:) pt => this%ptr(i)%res end function pos_1d_int32_int64 subroutine shared_alloc_cmplx_int32(this, sizes) class(shared_ragged_array_cmplx_t), intent(inout) :: this integer(int32), intent(in) :: sizes(:) integer(int64) :: n_entries ! Allocate the shared resource call this%data_array%shared_alloc(int(sum(sizes), int64)) ! Assign the pointers n_entries = size(sizes, kind=int64) allocate(this%ptr(n_entries)) ! Keep a local copy of sizes (fortran 2003 automatic allocation) allocate(this%store_sizes(n_entries)) this%store_sizes(1:n_entries) = int(sizes(1:n_entries), int64) ! Set the internal pointers call this%reassign_pointers() end subroutine shared_alloc_cmplx_int32 subroutine shared_alloc_cmplx_int64(this, sizes) class(shared_ragged_array_cmplx_t), intent(inout) :: this integer(int64), intent(in) :: sizes(:) integer(int64) :: n_entries ! Allocate the shared resource call this%data_array%shared_alloc(int(sum(sizes), int64)) ! Assign the pointers n_entries = size(sizes, kind=int64) allocate(this%ptr(n_entries)) ! Keep a local copy of sizes (fortran 2003 automatic allocation) allocate(this%store_sizes(n_entries)) this%store_sizes(1:n_entries) = int(sizes(1:n_entries), int64) ! Set the internal pointers call this%reassign_pointers() end subroutine shared_alloc_cmplx_int64 !------------------------------------------------------------------------------------------! subroutine shared_dealloc_cmplx(this) class(shared_ragged_array_cmplx_t), intent(inout) :: this call this%data_array%shared_dealloc() if (allocated(this%ptr)) deallocate(this%ptr) if (allocated(this%store_sizes)) deallocate(this%store_sizes) end subroutine shared_dealloc_cmplx !------------------------------------------------------------------------------------------! subroutine reassign_pointers_cmplx(this) class(shared_ragged_array_cmplx_t), intent(inout) :: this integer(int64) :: n_entries integer(int64) :: i, win_start, win_end n_entries = size(this%store_sizes, kind=int64) win_start = 1 do i = 1, n_entries win_end = win_start - 1 + this%store_sizes(i) this%ptr(i)%res => this%data_array%ptr(win_start:win_end) win_start = win_end + 1 end do end subroutine reassign_pointers_cmplx !------------------------------------------------------------------------------------------! subroutine set_val_cmplx_int32(this, i, j, val) class(shared_ragged_array_cmplx_t), intent(inout) :: this integer(int32), intent(in) :: i, j complex(dp), intent(in) :: val this%ptr(i)%res(j) = val end subroutine set_val_cmplx_int32 subroutine set_val_cmplx_int64(this, i, j, val) class(shared_ragged_array_cmplx_t), intent(inout) :: this integer(int64), intent(in) :: i, j complex(dp), intent(in) :: val this%ptr(i)%res(j) = val end subroutine set_val_cmplx_int64 !------------------------------------------------------------------------------------------! subroutine sync_cmplx(this) class(shared_ragged_array_cmplx_t), intent(inout) :: this call this%data_array%sync() end subroutine sync_cmplx !------------------------------------------------------------------------------------------! function pos_2d_cmplx_int32(this, i, j) result(val) class(shared_ragged_array_cmplx_t), intent(inout) :: this integer(int32), intent(in) :: i, j complex(dp) :: val val = this%ptr(i)%res(j) end function pos_2d_cmplx_int32 !------------------------------------------------------------------------------------------! function pos_1d_cmplx_int32(this, i) result(pt) class(shared_ragged_array_cmplx_t), intent(inout) :: this integer(int32), intent(in) :: i complex(dp), pointer :: pt(:) pt => this%ptr(i)%res end function pos_1d_cmplx_int32 function pos_2d_cmplx_int64(this, i, j) result(val) class(shared_ragged_array_cmplx_t), intent(inout) :: this integer(int64), intent(in) :: i, j complex(dp) :: val val = this%ptr(i)%res(j) end function pos_2d_cmplx_int64 !------------------------------------------------------------------------------------------! function pos_1d_cmplx_int64(this, i) result(pt) class(shared_ragged_array_cmplx_t), intent(inout) :: this integer(int64), intent(in) :: i complex(dp), pointer :: pt(:) pt => this%ptr(i)%res end function pos_1d_cmplx_int64 subroutine shared_alloc_bool_int32(this, sizes) class(shared_ragged_array_bool_t), intent(inout) :: this integer(int32), intent(in) :: sizes(:) integer(int64) :: n_entries ! Allocate the shared resource call this%data_array%shared_alloc(int(sum(sizes), int64)) ! Assign the pointers n_entries = size(sizes, kind=int64) allocate(this%ptr(n_entries)) ! Keep a local copy of sizes (fortran 2003 automatic allocation) allocate(this%store_sizes(n_entries)) this%store_sizes(1:n_entries) = int(sizes(1:n_entries), int64) ! Set the internal pointers call this%reassign_pointers() end subroutine shared_alloc_bool_int32 subroutine shared_alloc_bool_int64(this, sizes) class(shared_ragged_array_bool_t), intent(inout) :: this integer(int64), intent(in) :: sizes(:) integer(int64) :: n_entries ! Allocate the shared resource call this%data_array%shared_alloc(int(sum(sizes), int64)) ! Assign the pointers n_entries = size(sizes, kind=int64) allocate(this%ptr(n_entries)) ! Keep a local copy of sizes (fortran 2003 automatic allocation) allocate(this%store_sizes(n_entries)) this%store_sizes(1:n_entries) = int(sizes(1:n_entries), int64) ! Set the internal pointers call this%reassign_pointers() end subroutine shared_alloc_bool_int64 !------------------------------------------------------------------------------------------! subroutine shared_dealloc_bool(this) class(shared_ragged_array_bool_t), intent(inout) :: this call this%data_array%shared_dealloc() if (allocated(this%ptr)) deallocate(this%ptr) if (allocated(this%store_sizes)) deallocate(this%store_sizes) end subroutine shared_dealloc_bool !------------------------------------------------------------------------------------------! subroutine reassign_pointers_bool(this) class(shared_ragged_array_bool_t), intent(inout) :: this integer(int64) :: n_entries integer(int64) :: i, win_start, win_end n_entries = size(this%store_sizes, kind=int64) win_start = 1 do i = 1, n_entries win_end = win_start - 1 + this%store_sizes(i) this%ptr(i)%res => this%data_array%ptr(win_start:win_end) win_start = win_end + 1 end do end subroutine reassign_pointers_bool !------------------------------------------------------------------------------------------! subroutine set_val_bool_int32(this, i, j, val) class(shared_ragged_array_bool_t), intent(inout) :: this integer(int32), intent(in) :: i, j logical, intent(in) :: val this%ptr(i)%res(j) = val end subroutine set_val_bool_int32 subroutine set_val_bool_int64(this, i, j, val) class(shared_ragged_array_bool_t), intent(inout) :: this integer(int64), intent(in) :: i, j logical, intent(in) :: val this%ptr(i)%res(j) = val end subroutine set_val_bool_int64 !------------------------------------------------------------------------------------------! subroutine sync_bool(this) class(shared_ragged_array_bool_t), intent(inout) :: this call this%data_array%sync() end subroutine sync_bool !------------------------------------------------------------------------------------------! function pos_2d_bool_int32(this, i, j) result(val) class(shared_ragged_array_bool_t), intent(inout) :: this integer(int32), intent(in) :: i, j logical :: val val = this%ptr(i)%res(j) end function pos_2d_bool_int32 !------------------------------------------------------------------------------------------! function pos_1d_bool_int32(this, i) result(pt) class(shared_ragged_array_bool_t), intent(inout) :: this integer(int32), intent(in) :: i logical, pointer :: pt(:) pt => this%ptr(i)%res end function pos_1d_bool_int32 function pos_2d_bool_int64(this, i, j) result(val) class(shared_ragged_array_bool_t), intent(inout) :: this integer(int64), intent(in) :: i, j logical :: val val = this%ptr(i)%res(j) end function pos_2d_bool_int64 !------------------------------------------------------------------------------------------! function pos_1d_bool_int64(this, i) result(pt) class(shared_ragged_array_bool_t), intent(inout) :: this integer(int64), intent(in) :: i logical, pointer :: pt(:) pt => this%ptr(i)%res end function pos_1d_bool_int64 end module shared_ragged_array