Skip to content

Commit

Permalink
Merge pull request #112 from BerkeleyLab/update-caffeine-to-reflect-p…
Browse files Browse the repository at this point in the history
…rif-0.3

Update Caffeine to reflect PRIF v0.3
  • Loading branch information
ktras authored Jun 10, 2024
2 parents 7261b36 + 032bfd7 commit 213e3df
Show file tree
Hide file tree
Showing 8 changed files with 75 additions and 70 deletions.
8 changes: 4 additions & 4 deletions src/caffeine/allocation_s.f90
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@

contains

module procedure prif_allocate
module procedure prif_allocate_coarray
! TODO: determining the size of the handle and where the coarray begins
! becomes a bit more complicated if we don't allocate space for
! 15 cobounds
Expand Down Expand Up @@ -54,11 +54,11 @@
allocated_memory = coarray_handle%info%coarray_data
end procedure

module procedure prif_allocate_non_symmetric
module procedure prif_allocate
allocated_memory = caf_allocate(non_symmetric_heap_mspace, size_in_bytes)
end procedure

module procedure prif_deallocate
module procedure prif_deallocate_coarray
! gfortran is yelling that this isn't valid for bind(C)
! https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113338
! abstract interface
Expand Down Expand Up @@ -120,7 +120,7 @@
if (present(stat)) stat = 0
end procedure

module procedure prif_deallocate_non_symmetric
module procedure prif_deallocate
call caf_deallocate(non_symmetric_heap_mspace, mem)
end procedure

Expand Down
12 changes: 6 additions & 6 deletions src/caffeine/coarray_access_s.f90
Original file line number Diff line number Diff line change
Expand Up @@ -11,15 +11,15 @@
integer(c_int) :: image
integer(c_intptr_t) :: remote_base, remote_ptr

call prif_image_index(coarray_handle, coindices, image_index=image)
call prif_image_index(coarray_handle, cosubscripts, image_index=image)
call prif_base_pointer(coarray_handle, image, remote_base)
remote_ptr = &
remote_base &
+ (caf_as_int(first_element_addr) &
- caf_as_int(coarray_handle%info%coarray_data))
call prif_put_raw( &
image_num = image, &
local_buffer = c_loc(value), &
current_image_buffer = c_loc(value), &
remote_ptr = remote_ptr, &
size = size(value) * coarray_handle%info%element_length)
end procedure
Expand All @@ -28,7 +28,7 @@
call caf_put( &
image = image_num, &
dest = remote_ptr, &
src = local_buffer, &
src = current_image_buffer, &
size = size)
end procedure

Expand All @@ -40,23 +40,23 @@
integer(c_int) :: image
integer(c_intptr_t) :: remote_base, remote_ptr

call prif_image_index(coarray_handle, coindices, image_index=image)
call prif_image_index(coarray_handle, cosubscripts, image_index=image)
call prif_base_pointer(coarray_handle, image, remote_base)
remote_ptr = &
remote_base &
+ (caf_as_int(first_element_addr) &
- caf_as_int(coarray_handle%info%coarray_data))
call prif_get_raw( &
image_num = image, &
local_buffer = c_loc(value), &
current_image_buffer = c_loc(value), &
remote_ptr = remote_ptr, &
size = size(value) * coarray_handle%info%element_length)
end procedure

module procedure prif_get_raw
call caf_get( &
image = image_num, &
dest = local_buffer, &
dest = current_image_buffer, &
src = remote_ptr, &
size = size)
end procedure
Expand Down
4 changes: 2 additions & 2 deletions src/caffeine/prif_queries_s.f90
Original file line number Diff line number Diff line change
Expand Up @@ -26,8 +26,8 @@
end if
end procedure

module procedure prif_local_data_size
call unimplemented("prif_local_data_size")
module procedure prif_size_bytes
call unimplemented("prif_size_bytes")
end procedure

end submodule prif_queries_s
49 changes: 27 additions & 22 deletions src/prif.f90
Original file line number Diff line number Diff line change
Expand Up @@ -10,12 +10,12 @@ module prif
private
public :: prif_init
public :: prif_stop, prif_error_stop, prif_fail_image
public :: prif_allocate, prif_allocate_non_symmetric, prif_deallocate, prif_deallocate_non_symmetric
public :: prif_allocate_coarray, prif_allocate, prif_deallocate_coarray, prif_deallocate
public :: prif_put, prif_put_raw, prif_put_raw_strided, prif_get, prif_get_raw, prif_get_raw_strided
public :: prif_alias_create, prif_alias_destroy
public :: prif_lcobound, prif_ucobound, prif_coshape, prif_image_index
public :: prif_this_image, prif_num_images, prif_failed_images, prif_stopped_images, prif_image_status
public :: prif_set_context_data, prif_get_context_data, prif_base_pointer, prif_local_data_size
public :: prif_set_context_data, prif_get_context_data, prif_base_pointer, prif_size_bytes
public :: prif_co_sum, prif_co_max, prif_co_min, prif_co_reduce, prif_co_broadcast
public :: prif_form_team, prif_change_team, prif_end_team, prif_get_team, prif_team_number
public :: prif_sync_all, prif_sync_images, prif_sync_team, prif_sync_memory
Expand Down Expand Up @@ -114,6 +114,7 @@ module subroutine prif_stop(quiet, stop_code_int, stop_code_char)
end subroutine

module pure subroutine prif_error_stop(quiet, stop_code_int, stop_code_char)
implicit none
logical(c_bool), intent(in) :: quiet
integer(c_int), intent(in), optional :: stop_code_int
character(len=*), intent(in), optional :: stop_code_char
Expand All @@ -123,7 +124,7 @@ module subroutine prif_fail_image()
implicit none
end subroutine

module subroutine prif_allocate( &
module subroutine prif_allocate_coarray( &
lcobounds, ucobounds, lbounds, ubounds, element_length, final_func, coarray_handle, &
allocated_memory, stat, errmsg, errmsg_alloc)
implicit none
Expand All @@ -138,7 +139,7 @@ module subroutine prif_allocate( &
character(len=:), intent(inout), allocatable, optional :: errmsg_alloc
end subroutine

module subroutine prif_allocate_non_symmetric(size_in_bytes, allocated_memory, stat, errmsg, errmsg_alloc)
module subroutine prif_allocate(size_in_bytes, allocated_memory, stat, errmsg, errmsg_alloc)
implicit none
integer(kind=c_size_t) :: size_in_bytes
type(c_ptr), intent(out) :: allocated_memory
Expand All @@ -147,15 +148,15 @@ module subroutine prif_allocate_non_symmetric(size_in_bytes, allocated_memory, s
character(len=:), intent(inout), allocatable, optional :: errmsg_alloc
end subroutine

module subroutine prif_deallocate(coarray_handles, stat, errmsg, errmsg_alloc)
module subroutine prif_deallocate_coarray(coarray_handles, stat, errmsg, errmsg_alloc)
implicit none
type(prif_coarray_handle), target, intent(in) :: coarray_handles(:)
integer(c_int), intent(out), optional :: stat
character(len=*), intent(inout), optional :: errmsg
character(len=:), intent(inout), allocatable, optional :: errmsg_alloc
end subroutine

module subroutine prif_deallocate_non_symmetric(mem, stat, errmsg, errmsg_alloc)
module subroutine prif_deallocate(mem, stat, errmsg, errmsg_alloc)
implicit none
type(c_ptr), intent(in) :: mem
integer(c_int), intent(out), optional :: stat
Expand All @@ -164,10 +165,10 @@ module subroutine prif_deallocate_non_symmetric(mem, stat, errmsg, errmsg_alloc)
end subroutine

module subroutine prif_put( &
coarray_handle, coindices, value, first_element_addr, team, team_number, notify_ptr, stat, errmsg, errmsg_alloc)
coarray_handle, cosubscripts, value, first_element_addr, team, team_number, notify_ptr, stat, errmsg, errmsg_alloc)
implicit none
type(prif_coarray_handle), intent(in) :: coarray_handle
integer(c_intmax_t), intent(in) :: coindices(:)
integer(c_intmax_t), intent(in) :: cosubscripts(:)
type(*), intent(in), contiguous, target :: value(..)
type(c_ptr), intent(in) :: first_element_addr
type(prif_team_type), optional, intent(in) :: team
Expand All @@ -178,10 +179,10 @@ module subroutine prif_put( &
character(len=:), intent(inout), allocatable, optional :: errmsg_alloc
end subroutine

module subroutine prif_put_raw(image_num, local_buffer, remote_ptr, notify_ptr, size, stat, errmsg, errmsg_alloc)
module subroutine prif_put_raw(image_num, current_image_buffer, remote_ptr, notify_ptr, size, stat, errmsg, errmsg_alloc)
implicit none
integer(c_int), intent(in) :: image_num
type(c_ptr), intent(in) :: local_buffer
type(c_ptr), intent(in) :: current_image_buffer
integer(c_intptr_t), intent(in) :: remote_ptr
integer(c_intptr_t), optional, intent(in) :: notify_ptr
integer(c_size_t), intent(in) :: size
Expand All @@ -191,27 +192,27 @@ module subroutine prif_put_raw(image_num, local_buffer, remote_ptr, notify_ptr,
end subroutine

module subroutine prif_put_raw_strided( &
image_num, local_buffer, remote_ptr, element_size, extent, remote_ptr_stride, &
local_buffer_stride, notify_ptr, stat, errmsg, errmsg_alloc)
image_num, current_image_buffer, remote_ptr, element_size, extent, remote_ptr_stride, &
current_image_buffer_stride, notify_ptr, stat, errmsg, errmsg_alloc)
implicit none
integer(c_int), intent(in) :: image_num
type(c_ptr), intent(in) :: local_buffer
type(c_ptr), intent(in) :: current_image_buffer
integer(c_intptr_t), intent(in) :: remote_ptr
integer(c_size_t), intent(in) :: element_size
integer(c_size_t), intent(in) :: extent(:)
integer(c_ptrdiff_t), intent(in) :: remote_ptr_stride(:)
integer(c_ptrdiff_t), intent(in) :: local_buffer_stride(:)
integer(c_ptrdiff_t), intent(in) :: current_image_buffer_stride(:)
integer(c_intptr_t), optional, intent(in) :: notify_ptr
integer(c_int), intent(out), optional :: stat
character(len=*), intent(inout), optional :: errmsg
character(len=:), intent(inout), allocatable, optional :: errmsg_alloc
end subroutine

module subroutine prif_get( &
coarray_handle, coindices, first_element_addr, value, team, team_number, stat, errmsg, errmsg_alloc)
coarray_handle, cosubscripts, first_element_addr, value, team, team_number, stat, errmsg, errmsg_alloc)
implicit none
type(prif_coarray_handle), intent(in) :: coarray_handle
integer(c_intmax_t), intent(in) :: coindices(:)
integer(c_intmax_t), intent(in) :: cosubscripts(:)
type(c_ptr), intent(in) :: first_element_addr
type(*), intent(inout), contiguous, target :: value(..)
type(prif_team_type), optional, intent(in) :: team
Expand All @@ -221,10 +222,10 @@ module subroutine prif_get( &
character(len=:), intent(inout), allocatable, optional :: errmsg_alloc
end subroutine

module subroutine prif_get_raw(image_num, local_buffer, remote_ptr, size, stat, errmsg, errmsg_alloc)
module subroutine prif_get_raw(image_num, current_image_buffer, remote_ptr, size, stat, errmsg, errmsg_alloc)
implicit none
integer(c_int), intent(in) :: image_num
type(c_ptr), intent(in) :: local_buffer
type(c_ptr), intent(in) :: current_image_buffer
integer(c_intptr_t), intent(in) :: remote_ptr
integer(c_size_t), intent(in) :: size
integer(c_int), intent(out), optional :: stat
Expand All @@ -233,16 +234,16 @@ module subroutine prif_get_raw(image_num, local_buffer, remote_ptr, size, stat,
end subroutine

module subroutine prif_get_raw_strided( &
image_num, local_buffer, remote_ptr, element_size, extent, remote_ptr_stride, local_buffer_stride, &
image_num, current_image_buffer, remote_ptr, element_size, extent, remote_ptr_stride, current_image_buffer_stride, &
stat, errmsg, errmsg_alloc)
implicit none
integer(c_int), intent(in) :: image_num
type(c_ptr), intent(in) :: local_buffer
type(c_ptr), intent(in) :: current_image_buffer
integer(c_intptr_t), intent(in) :: remote_ptr
integer(c_size_t), intent(in) :: element_size
integer(c_size_t), intent(in) :: extent(:)
integer(c_ptrdiff_t), intent(in) :: remote_ptr_stride(:)
integer(c_ptrdiff_t), intent(in) :: local_buffer_stride(:)
integer(c_ptrdiff_t), intent(in) :: current_image_buffer_stride(:)
integer(c_int), intent(out), optional :: stat
character(len=*), intent(inout), optional :: errmsg
character(len=:), intent(inout), allocatable, optional :: errmsg_alloc
Expand All @@ -262,23 +263,27 @@ module subroutine prif_alias_destroy(alias_handle)
end subroutine

module subroutine prif_lcobound_with_dim(coarray_handle, dim, lcobound)
implicit none
type(prif_coarray_handle), intent(in) :: coarray_handle
integer(kind=c_int), intent(in) :: dim
integer(kind=c_intmax_t), intent(out) :: lcobound
end subroutine

module subroutine prif_lcobound_no_dim(coarray_handle, lcobounds)
implicit none
type(prif_coarray_handle), intent(in) :: coarray_handle
integer(kind=c_intmax_t), intent(out) :: lcobounds(:)
end subroutine

module subroutine prif_ucobound_with_dim(coarray_handle, dim, ucobound)
implicit none
type(prif_coarray_handle), intent(in) :: coarray_handle
integer(kind=c_int), intent(in) :: dim
integer(kind=c_intmax_t), intent(out) :: ucobound
end subroutine

module subroutine prif_ucobound_no_dim(coarray_handle, ucobounds)
implicit none
type(prif_coarray_handle), intent(in) :: coarray_handle
integer(kind=c_intmax_t), intent(out) :: ucobounds(:)
end subroutine
Expand Down Expand Up @@ -343,7 +348,7 @@ module subroutine prif_base_pointer(coarray_handle, image_num, ptr)
integer(c_intptr_t), intent(out) :: ptr
end subroutine

module subroutine prif_local_data_size(coarray_handle, data_size)
module subroutine prif_size_bytes(coarray_handle, data_size)
implicit none
type(prif_coarray_handle), intent(in) :: coarray_handle
integer(c_size_t), intent(out) :: data_size
Expand Down
10 changes: 5 additions & 5 deletions test/caf_allocate_test.f90
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
module caf_allocate_test
use prif, only : &
prif_allocate_coarray, prif_deallocate_coarray, &
prif_allocate, prif_deallocate, &
prif_allocate_non_symmetric, prif_deallocate_non_symmetric, &
prif_coarray_handle, prif_num_images
use veggies, only: result_t, test_item_t, assert_that, assert_equals, describe, it
use iso_c_binding, only: &
Expand Down Expand Up @@ -48,7 +48,7 @@ function check_allocate_integer_scalar_coarray_with_corank1() result(result_)
local_slice => null()
result_ = assert_that(.not.associated(local_slice))

call prif_allocate( &
call prif_allocate_coarray( &
lcobounds, ucobounds, lbounds, ubounds, int(storage_size(dummy_element)/8, c_size_t), c_null_funptr, &
coarray_handle, allocated_memory)

Expand All @@ -58,7 +58,7 @@ function check_allocate_integer_scalar_coarray_with_corank1() result(result_)
local_slice = 42
result_ = result_ .and. assert_equals(42, local_slice)

call prif_deallocate([coarray_handle])
call prif_deallocate_coarray([coarray_handle])

end function

Expand All @@ -68,13 +68,13 @@ function check_allocate_non_symmetric() result(result_)
type(c_ptr) :: allocated_memory
integer(c_int), pointer :: local_slice

call prif_allocate_non_symmetric(sizeof(local_slice), allocated_memory)
call prif_allocate(sizeof(local_slice), allocated_memory)
call c_f_pointer(allocated_memory, local_slice)

local_slice = 42
result_ = assert_equals(42, local_slice)

call prif_deallocate_non_symmetric(c_loc(local_slice))
call prif_deallocate(c_loc(local_slice))
end function

end module caf_allocate_test
Loading

0 comments on commit 213e3df

Please sign in to comment.