123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121 |
- program nf_matrix
- use iso_c_binding
- use fstarpu_mod
- use nf_codelets
- implicit none
- real(8), dimension(:,:), allocatable, target :: ma
- integer, dimension(:,:), allocatable, target :: mb
- integer :: i,j
- type(c_ptr) :: cl_mat
- type(c_ptr) :: dh_ma
- type(c_ptr) :: dh_mb
- integer(c_int) :: err
- integer(c_int) :: ncpu
- real(c_double) :: start_time
- real(c_double) :: end_time
- allocate(ma(5,6))
- do i=1,5
- do j=1,6
- ma(i,j) = (i*10)+j
- end do
- end do
- allocate(mb(7,8))
- do i=1,7
- do j=1,8
- mb(i,j) = (i*10)+j
- end do
- end do
-
- err = fstarpu_init(C_NULL_PTR)
- if (err == -19) then
- stop 77
- end if
-
- ncpu = fstarpu_cpu_worker_get_count()
- if (ncpu == 0) then
- call fstarpu_shutdown()
- stop 77
- end if
-
- start_time = fstarpu_timing_now()
-
- cl_mat = fstarpu_codelet_allocate()
-
- call fstarpu_codelet_set_name(cl_mat, C_CHAR_"my_mat_codelet"//C_NULL_CHAR)
-
- call fstarpu_codelet_add_cpu_func(cl_mat, C_FUNLOC(cl_cpu_func_mat))
-
- call fstarpu_codelet_add_buffer(cl_mat, FSTARPU_R)
-
- call fstarpu_codelet_add_buffer(cl_mat, FSTARPU_RW)
-
-
- call fstarpu_matrix_data_register(dh_ma, 0, c_loc(ma), 5, 5, 6, c_sizeof(ma(1,1)))
-
- call fstarpu_matrix_data_register(dh_mb, 0, c_loc(mb), 7, 7, 8, c_sizeof(mb(1,1)))
-
-
-
-
-
-
-
-
-
- call fstarpu_insert_task((/ cl_mat, FSTARPU_R, dh_ma, FSTARPU_RW, dh_mb, C_NULL_PTR /))
-
- call fstarpu_task_wait_for_all()
-
- call fstarpu_data_unregister(dh_ma)
-
- call fstarpu_data_unregister(dh_mb)
-
- call fstarpu_codelet_free(cl_mat)
-
- end_time = fstarpu_timing_now()
-
- call fstarpu_shutdown()
- deallocate(mb)
- deallocate(ma)
- print "(es 10.3)", end_time - start_time
- end program nf_matrix
|