123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106 |
- program nf_vector
- use iso_c_binding
- use fstarpu_mod
- use nf_codelets
- implicit none
- real(8), dimension(:), allocatable, target :: va
- integer, dimension(:), allocatable, target :: vb
- integer :: i
- type(c_ptr) :: cl_vec
- type(c_ptr) :: dh_va
- type(c_ptr) :: dh_vb
- integer(c_int) :: err
- integer(c_int) :: ncpu
- allocate(va(5))
- va = (/ (i,i=1,5) /)
- allocate(vb(7))
- vb = (/ (i,i=1,7) /)
-
- 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
-
- cl_vec = fstarpu_codelet_allocate()
-
- call fstarpu_codelet_set_name(cl_vec, C_CHAR_"my_vec_codelet"//C_NULL_CHAR)
-
- call fstarpu_codelet_add_cpu_func(cl_vec, C_FUNLOC(cl_cpu_func_vec))
-
- call fstarpu_codelet_set_where(cl_vec, FSTARPU_CPU)
-
- call fstarpu_codelet_add_buffer(cl_vec, FSTARPU_R)
-
- call fstarpu_codelet_add_buffer(cl_vec, FSTARPU_RW.ior.FSTARPU_LOCALITY)
-
- call fstarpu_vector_data_register(dh_va, 0, c_loc(va), 1+ubound(va,1)-lbound(va,1), c_sizeof(va(lbound(va,1))))
-
- call fstarpu_vector_data_register(dh_vb, 0, c_loc(vb), 1+ubound(vb,1)-lbound(vb,1), c_sizeof(vb(lbound(vb,1))))
-
-
-
-
-
-
-
-
-
- call fstarpu_insert_task((/ cl_vec, FSTARPU_R, dh_va, FSTARPU_RW.ior.FSTARPU_LOCALITY, dh_vb, C_NULL_PTR /))
-
- call fstarpu_task_wait_for_all()
-
- call fstarpu_data_unregister(dh_va)
-
- call fstarpu_data_unregister(dh_vb)
-
- call fstarpu_codelet_free(cl_vec)
-
- call fstarpu_shutdown()
- deallocate(vb)
- deallocate(va)
- end program nf_vector
|