nf_example.f90 6.1 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182
  1. ! StarPU --- Runtime system for heterogeneous multicore architectures.
  2. !
  3. ! Copyright (C) 2015-2020 Université de Bordeaux, CNRS (LaBRI UMR 5800), Inria
  4. ! Copyright (C) 2015 ONERA
  5. !
  6. ! StarPU is free software; you can redistribute it and/or modify
  7. ! it under the terms of the GNU Lesser General Public License as published by
  8. ! the Free Software Foundation; either version 2.1 of the License, or (at
  9. ! your option) any later version.
  10. !
  11. ! StarPU is distributed in the hope that it will be useful, but
  12. ! WITHOUT ANY WARRANTY; without even the implied warranty of
  13. ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
  14. !
  15. ! See the GNU Lesser General Public License in COPYING.LGPL for more details.
  16. !
  17. ! This is an example of Fortran90 program making use of StarPU.
  18. ! It registers a few matrices for each element of a domain, performs
  19. ! update computations on them, and checks the result.
  20. PROGRAM f90_example
  21. USE nf_types
  22. USE fstarpu_mod
  23. USE nf_compute
  24. USE iso_c_binding
  25. IMPLICIT NONE
  26. TYPE(type_mesh) :: mesh
  27. TYPE(type_numpar),TARGET :: numpar
  28. TYPE(type_mesh_elt),POINTER :: elt => NULL()
  29. INTEGER(KIND=C_INT) :: i,Nelt,res,cpus
  30. INTEGER(KIND=C_INT) :: starpu_maj,starpu_min,starpu_rev
  31. INTEGER(KIND=C_INT) :: neq,ng,nb,it,it_tot
  32. REAL(KIND=C_DOUBLE) :: r, coeff2
  33. REAL(KIND=C_DOUBLE),TARGET :: flops
  34. TYPE(C_PTR) :: cl_loop_element = C_NULL_PTR ! loop codelet
  35. TYPE(C_PTR) :: cl_copy_element = C_NULL_PTR ! copy codelet
  36. !Initialization with arbitrary data
  37. Nelt = 2
  38. it_tot = 2
  39. numpar%Neq_max = 5
  40. numpar%coeff = 1.0
  41. ALLOCATE(mesh%elt(Nelt))
  42. DO i = 1,Nelt
  43. elt => mesh%elt(i)
  44. elt%Ng = 4
  45. elt%Np = 2
  46. ALLOCATE(elt%ro(numpar%Neq_max,elt%Np))
  47. ALLOCATE(elt%dro(numpar%Neq_max,elt%Np))
  48. ALLOCATE(elt%basis(elt%Np,elt%Ng))
  49. CALL init_element(elt%ro,elt%dro,elt%basis,numpar%Neq_max,elt%Np,elt%Ng,i)
  50. ENDDO
  51. !Initialization of StarPU
  52. res = fstarpu_init(C_NULL_PTR)
  53. IF (res == -19) THEN
  54. STOP 77
  55. END IF
  56. CALL fstarpu_get_version(starpu_maj,starpu_min,starpu_rev)
  57. WRITE(6,'(a,i4,a,i4,a,i4)') "StarPU version: ", starpu_maj , "." , starpu_min , "." , starpu_rev
  58. cpus = fstarpu_cpu_worker_get_count()
  59. IF (cpus == 0) THEN
  60. CALL fstarpu_shutdown()
  61. STOP 77
  62. END IF
  63. cl_loop_element = fstarpu_codelet_allocate()
  64. CALL fstarpu_codelet_add_cpu_func(cl_loop_element, C_FUNLOC(loop_element_cpu_fortran))
  65. CALL fstarpu_codelet_add_buffer(cl_loop_element, FSTARPU_R)
  66. CALL fstarpu_codelet_add_buffer(cl_loop_element, FSTARPU_RW)
  67. CALL fstarpu_codelet_add_buffer(cl_loop_element, FSTARPU_R)
  68. CALL fstarpu_codelet_set_name(cl_loop_element, C_CHAR_"LOOP_ELEMENT"//C_NULL_CHAR)
  69. cl_copy_element = fstarpu_codelet_allocate()
  70. CALL fstarpu_codelet_add_cpu_func(cl_copy_element, C_FUNLOC(copy_element_cpu_fortran))
  71. CALL fstarpu_codelet_add_buffer(cl_copy_element, FSTARPU_RW)
  72. CALL fstarpu_codelet_add_buffer(cl_copy_element, FSTARPU_R)
  73. CALL fstarpu_codelet_set_name(cl_copy_element, C_CHAR_"COPY_ELEMENT"//C_NULL_CHAR)
  74. !Registration of elements
  75. DO i = 1,Nelt
  76. elt => mesh%elt(i)
  77. call fstarpu_matrix_data_register(elt%ro_h, 0, c_loc(elt%ro), numpar%Neq_max, numpar%Neq_max, elt%Np, c_sizeof(elt%ro(1,1)))
  78. call fstarpu_matrix_data_register(elt%dro_h, 0, c_loc(elt%dro), numpar%Neq_max, numpar%Neq_max, elt%Np, c_sizeof(elt%dro(1,1)))
  79. call fstarpu_matrix_data_register(elt%basis_h, 0, c_loc(elt%basis), elt%Np, elt%Np, elt%Ng, c_sizeof(elt%basis(1,1)))
  80. ENDDO
  81. !Compute
  82. DO it = 1,it_tot
  83. ! compute new dro for each element
  84. DO i = 1,Nelt
  85. elt => mesh%elt(i)
  86. flops = elt%Ng * ( (elt%Np * numpar%Neq_max * 2) + 1 + elt%Np * numpar%Neq_max)
  87. CALL fstarpu_insert_task((/ cl_loop_element, &
  88. FSTARPU_VALUE, c_loc(numpar%coeff), FSTARPU_SZ_C_DOUBLE, &
  89. FSTARPU_R, elt%ro_h, &
  90. FSTARPU_RW, elt%dro_h, &
  91. FSTARPU_R, elt%basis_h, &
  92. FSTARPU_FLOPS, c_loc(flops), &
  93. C_NULL_PTR /))
  94. ENDDO
  95. ! sync (if needed by the algorithm)
  96. CALL fstarpu_task_wait_for_all()
  97. ! - - - - -
  98. ! copy dro to ro for each element
  99. DO i = 1,Nelt
  100. elt => mesh%elt(i)
  101. CALL fstarpu_insert_task((/ cl_copy_element, &
  102. FSTARPU_RW, elt%ro_h, &
  103. FSTARPU_R, elt%dro_h, &
  104. C_NULL_PTR /))
  105. ENDDO
  106. ! sync (if needed by the algorithm)
  107. CALL fstarpu_task_wait_for_all()
  108. ENDDO
  109. !Unregistration of elements
  110. DO i = 1,Nelt
  111. elt => mesh%elt(i)
  112. CALL fstarpu_data_unregister(elt%ro_h)
  113. CALL fstarpu_data_unregister(elt%dro_h)
  114. CALL fstarpu_data_unregister(elt%basis_h)
  115. ENDDO
  116. !Terminate StarPU, no task can be submitted after
  117. CALL fstarpu_shutdown()
  118. !Check data with StarPU
  119. WRITE(6,'(a)') " "
  120. WRITE(6,'(a)') " %%%% RESULTS STARPU %%%% "
  121. WRITE(6,'(a)') " "
  122. DO i = 1,Nelt
  123. WRITE(6,'(a,i4,a)') " elt ", i , " ; elt%ro = "
  124. WRITE(6,'(10(1x,F11.2))') mesh%elt(i)%ro
  125. WRITE(6,'(a)') " ------------------------ "
  126. ENDDO
  127. !Same compute without StarPU
  128. DO i = 1,Nelt
  129. elt => mesh%elt(i)
  130. CALL init_element(elt%ro,elt%dro,elt%basis,numpar%Neq_max,elt%Np,elt%Ng,i)
  131. ENDDO
  132. DO it = 1, it_tot
  133. DO i = 1,Nelt
  134. elt => mesh%elt(i)
  135. CALL loop_element_cpu(elt%ro,elt%dro,elt%basis,numpar%coeff,numpar%Neq_max,elt%Ng,elt%Np)
  136. elt%ro = elt%ro + elt%dro
  137. ENDDO
  138. ENDDO
  139. WRITE(6,'(a)') " "
  140. WRITE(6,'(a)') " %%%% RESULTS VERIFICATION %%%% "
  141. WRITE(6,'(a)') " "
  142. DO i = 1,Nelt
  143. WRITE(6,'(a,i4,a)') " elt ", i , " ; elt%ro = "
  144. WRITE(6,'(10(1x,F11.2))') mesh%elt(i)%ro
  145. WRITE(6,'(a)') " ------------------------ "
  146. ENDDO
  147. WRITE(6,'(a)') " "
  148. !Deallocation
  149. CALL fstarpu_codelet_free(cl_loop_element)
  150. CALL fstarpu_codelet_free(cl_copy_element)
  151. DO i = 1,Nelt
  152. elt => mesh%elt(i)
  153. DEALLOCATE(elt%ro)
  154. DEALLOCATE(elt%dro)
  155. DEALLOCATE(elt%basis)
  156. ENDDO
  157. DEALLOCATE(mesh%elt)
  158. END PROGRAM f90_example