123456789101112131415161718192021222324252627282930313233343536373839404142434445 |
- module nf_partition_cl
- contains
-
- recursive subroutine cl_partition_func (buffers, cl_args) bind(C)
- use iso_c_binding
- use fstarpu_mod
- implicit none
- type(c_ptr), value, intent(in) :: buffers, cl_args
- real(8), dimension(:,:), pointer :: ma
- integer :: ld_ma,nx_ma,ny_ma
- integer :: i,j
- ld_ma = fstarpu_matrix_get_ld(buffers, 0)
- nx_ma = fstarpu_matrix_get_nx(buffers, 0)
- ny_ma = fstarpu_matrix_get_ny(buffers, 0)
- write(*,*) "ld_ma = ", ld_ma, ", nx_ma = ", nx_ma, ", ny_ma = ", ny_ma
- call c_f_pointer(fstarpu_matrix_get_ptr(buffers, 0), ma, shape=[ld_ma,ny_ma])
- write(*,*) "ma"
- do i=1,nx_ma
- do j=1,ny_ma
- write(*,*) i,j,ma(i,j)
- end do
- write(*,*) '-'
- end do
- end subroutine cl_partition_func
- end module nf_partition_cl
|