nf_example.f90 5.8 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179
  1. ! StarPU --- Runtime system for heterogeneous multicore architectures.
  2. !
  3. ! Copyright (C) 2015 ONERA
  4. ! Copyright (C) 2015-2016 Inria
  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. ! This is an example of Fortran90 program making use of StarPU.
  17. ! It registers a few matrices for each element of a domain, performs
  18. ! update computations on them, and checks the result.
  19. PROGRAM f90_example
  20. USE nf_types
  21. USE fstarpu_mod
  22. USE nf_compute
  23. USE iso_c_binding
  24. IMPLICIT NONE
  25. TYPE(type_mesh) :: mesh
  26. TYPE(type_numpar),TARGET :: numpar
  27. TYPE(type_mesh_elt),POINTER :: elt => NULL()
  28. INTEGER(KIND=C_INT) :: i,Nelt,res,cpus
  29. INTEGER(KIND=C_INT) :: starpu_maj,starpu_min,starpu_rev
  30. INTEGER(KIND=C_INT) :: neq,ng,nb,it,it_tot
  31. REAL(KIND=C_DOUBLE) :: r, coeff2
  32. TYPE(C_PTR) :: cl_loop_element = C_NULL_PTR ! loop codelet
  33. TYPE(C_PTR) :: cl_copy_element = C_NULL_PTR ! copy codelet
  34. !Initialization with arbitrary data
  35. Nelt = 2
  36. it_tot = 2
  37. numpar%Neq_max = 5
  38. numpar%coeff = 1.0
  39. ALLOCATE(mesh%elt(Nelt))
  40. DO i = 1,Nelt
  41. elt => mesh%elt(i)
  42. elt%Ng = 4
  43. elt%Np = 2
  44. ALLOCATE(elt%ro(numpar%Neq_max,elt%Np))
  45. ALLOCATE(elt%dro(numpar%Neq_max,elt%Np))
  46. ALLOCATE(elt%basis(elt%Np,elt%Ng))
  47. CALL init_element(elt%ro,elt%dro,elt%basis,numpar%Neq_max,elt%Np,elt%Ng,i)
  48. ENDDO
  49. !Initialization of StarPU
  50. res = fstarpu_init(C_NULL_PTR)
  51. IF (res == -19) THEN
  52. STOP 77
  53. END IF
  54. CALL fstarpu_get_version(starpu_maj,starpu_min,starpu_rev)
  55. WRITE(6,'(a,i4,a,i4,a,i4)') "StarPU version: ", starpu_maj , "." , starpu_min , "." , starpu_rev
  56. cpus = fstarpu_cpu_worker_get_count()
  57. IF (cpus == 0) THEN
  58. CALL fstarpu_shutdown()
  59. STOP 77
  60. END IF
  61. cl_loop_element = fstarpu_codelet_allocate()
  62. CALL fstarpu_codelet_add_cpu_func(cl_loop_element, C_FUNLOC(loop_element_cpu_fortran))
  63. CALL fstarpu_codelet_add_buffer(cl_loop_element, FSTARPU_R)
  64. CALL fstarpu_codelet_add_buffer(cl_loop_element, FSTARPU_RW)
  65. CALL fstarpu_codelet_add_buffer(cl_loop_element, FSTARPU_R)
  66. CALL fstarpu_codelet_set_name(cl_loop_element, C_CHAR_"LOOP_ELEMENT"//C_NULL_CHAR)
  67. cl_copy_element = fstarpu_codelet_allocate()
  68. CALL fstarpu_codelet_add_cpu_func(cl_copy_element, C_FUNLOC(copy_element_cpu_fortran))
  69. CALL fstarpu_codelet_add_buffer(cl_copy_element, FSTARPU_RW)
  70. CALL fstarpu_codelet_add_buffer(cl_copy_element, FSTARPU_R)
  71. CALL fstarpu_codelet_set_name(cl_copy_element, C_CHAR_"COPY_ELEMENT"//C_NULL_CHAR)
  72. !Registration of elements
  73. DO i = 1,Nelt
  74. elt => mesh%elt(i)
  75. 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)))
  76. 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)))
  77. 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)))
  78. ENDDO
  79. !Compute
  80. DO it = 1,it_tot
  81. ! compute new dro for each element
  82. DO i = 1,Nelt
  83. elt => mesh%elt(i)
  84. CALL fstarpu_insert_task((/ cl_loop_element, &
  85. FSTARPU_VALUE, c_loc(numpar%coeff), FSTARPU_SZ_C_DOUBLE, &
  86. FSTARPU_R, elt%ro_h, &
  87. FSTARPU_RW, elt%dro_h, &
  88. FSTARPU_R, elt%basis_h, &
  89. C_NULL_PTR /))
  90. ENDDO
  91. ! sync (if needed by the algorithm)
  92. CALL fstarpu_task_wait_for_all()
  93. ! - - - - -
  94. ! copy dro to ro for each element
  95. DO i = 1,Nelt
  96. elt => mesh%elt(i)
  97. CALL fstarpu_insert_task((/ cl_copy_element, &
  98. FSTARPU_RW, elt%ro_h, &
  99. FSTARPU_R, elt%dro_h, &
  100. C_NULL_PTR /))
  101. ENDDO
  102. ! sync (if needed by the algorithm)
  103. CALL fstarpu_task_wait_for_all()
  104. ENDDO
  105. !Unregistration of elements
  106. DO i = 1,Nelt
  107. elt => mesh%elt(i)
  108. CALL fstarpu_data_unregister(elt%ro_h)
  109. CALL fstarpu_data_unregister(elt%dro_h)
  110. CALL fstarpu_data_unregister(elt%basis_h)
  111. ENDDO
  112. !Terminate StarPU, no task can be submitted after
  113. CALL fstarpu_shutdown()
  114. !Check data with StarPU
  115. WRITE(6,'(a)') " "
  116. WRITE(6,'(a)') " %%%% RESULTS STARPU %%%% "
  117. WRITE(6,'(a)') " "
  118. DO i = 1,Nelt
  119. WRITE(6,'(a,i4,a)') " elt ", i , " ; elt%ro = "
  120. WRITE(6,'(10(1x,F11.2))') mesh%elt(i)%ro
  121. WRITE(6,'(a)') " ------------------------ "
  122. ENDDO
  123. !Same compute without StarPU
  124. DO i = 1,Nelt
  125. elt => mesh%elt(i)
  126. CALL init_element(elt%ro,elt%dro,elt%basis,numpar%Neq_max,elt%Np,elt%Ng,i)
  127. ENDDO
  128. DO it = 1, it_tot
  129. DO i = 1,Nelt
  130. elt => mesh%elt(i)
  131. CALL loop_element_cpu(elt%ro,elt%dro,elt%basis,numpar%coeff,numpar%Neq_max,elt%Ng,elt%Np)
  132. elt%ro = elt%ro + elt%dro
  133. ENDDO
  134. ENDDO
  135. WRITE(6,'(a)') " "
  136. WRITE(6,'(a)') " %%%% RESULTS VERIFICATION %%%% "
  137. WRITE(6,'(a)') " "
  138. DO i = 1,Nelt
  139. WRITE(6,'(a,i4,a)') " elt ", i , " ; elt%ro = "
  140. WRITE(6,'(10(1x,F11.2))') mesh%elt(i)%ro
  141. WRITE(6,'(a)') " ------------------------ "
  142. ENDDO
  143. WRITE(6,'(a)') " "
  144. !Deallocation
  145. CALL fstarpu_codelet_free(cl_loop_element)
  146. CALL fstarpu_codelet_free(cl_copy_element)
  147. DO i = 1,Nelt
  148. elt => mesh%elt(i)
  149. DEALLOCATE(elt%ro)
  150. DEALLOCATE(elt%dro)
  151. DEALLOCATE(elt%basis)
  152. ENDDO
  153. DEALLOCATE(mesh%elt)
  154. END PROGRAM f90_example