f90_example.f90 4.2 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151
  1. ! StarPU --- Runtime system for heterogeneous multicore architectures.
  2. !
  3. ! Copyright (C) 2015 ONERA
  4. ! Copyright (C) 2015 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 mod_types
  21. USE starpu_mod
  22. USE mod_interface
  23. USE mod_compute
  24. USE iso_c_binding
  25. IMPLICIT NONE
  26. TYPE(type_mesh) :: mesh
  27. TYPE(type_numpar) :: 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. !Initialization with arbitrary data
  34. Nelt = 2
  35. it_tot = 2
  36. numpar%Neq_max = 5
  37. numpar%coeff = 1.0
  38. ALLOCATE(mesh%elt(Nelt))
  39. DO i = 1,Nelt
  40. elt => mesh%elt(i)
  41. elt%Ng = 4
  42. elt%Np = 2
  43. ALLOCATE(elt%ro(numpar%Neq_max,elt%Np))
  44. ALLOCATE(elt%dro(numpar%Neq_max,elt%Np))
  45. ALLOCATE(elt%basis(elt%Np,elt%Ng))
  46. CALL init_element(elt%ro,elt%dro,elt%basis,numpar%Neq_max,elt%Np,elt%Ng,i)
  47. ENDDO
  48. !Initialization of StarPU
  49. res = starpu_my_init_c()
  50. IF (res == -19) THEN
  51. STOP 77
  52. END IF
  53. call starpu_get_version(starpu_maj,starpu_min,starpu_rev)
  54. WRITE(6,'(a,i4,a,i4,a,i4)') "StarPU version: ", starpu_maj , "." , starpu_min , "." , starpu_rev
  55. cpus = starpu_cpu_worker_get_count()
  56. IF (cpus == 0) THEN
  57. CALL starpu_shutdown()
  58. STOP 77
  59. END IF
  60. !Registration of elements
  61. DO i = 1,Nelt
  62. elt => mesh%elt(i)
  63. CALL starpu_register_element_c(numpar%Neq_max,elt%Np,elt%Ng,elt%ro,elt%dro, &
  64. elt%basis,elt%ro_h,elt%dro_h,elt%basis_h)
  65. ENDDO
  66. !Compute
  67. DO it = 1,it_tot
  68. ! compute new dro for each element
  69. DO i = 1,Nelt
  70. elt => mesh%elt(i)
  71. CALL starpu_loop_element_task_c(numpar%coeff,elt%ro_h,elt%dro_h,elt%basis_h)
  72. ENDDO
  73. ! sync (if needed by the algorithm)
  74. CALL starpu_task_wait_for_all()
  75. ! - - - - -
  76. ! copy dro to ro for each element
  77. DO i = 1,Nelt
  78. elt => mesh%elt(i)
  79. CALL starpu_copy_element_task_c(elt%ro_h,elt%dro_h)
  80. ENDDO
  81. ! sync (if needed by the algorithm)
  82. CALL starpu_task_wait_for_all()
  83. ENDDO
  84. !Unregistration of elements
  85. DO i = 1,Nelt
  86. elt => mesh%elt(i)
  87. CALL starpu_unregister_element_c(elt%ro_h,elt%dro_h,elt%basis_h)
  88. ENDDO
  89. !Terminate StarPU, no task can be submitted after
  90. CALL starpu_shutdown()
  91. !Check data with StarPU
  92. WRITE(6,'(a)') " "
  93. WRITE(6,'(a)') " %%%% RESULTS STARPU %%%% "
  94. WRITE(6,'(a)') " "
  95. DO i = 1,Nelt
  96. WRITE(6,'(a,i4,a)') " elt ", i , " ; elt%ro = "
  97. WRITE(6,'(10(1x,F11.2))') mesh%elt(i)%ro
  98. WRITE(6,'(a)') " ------------------------ "
  99. ENDDO
  100. !Same compute without StarPU
  101. DO i = 1,Nelt
  102. elt => mesh%elt(i)
  103. CALL init_element(elt%ro,elt%dro,elt%basis,numpar%Neq_max,elt%Np,elt%Ng,i)
  104. ENDDO
  105. DO it = 1, it_tot
  106. DO i = 1,Nelt
  107. elt => mesh%elt(i)
  108. CALL loop_element_cpu(elt%ro,elt%dro,elt%basis,numpar%coeff,numpar%Neq_max,elt%Ng,elt%Np)
  109. elt%ro = elt%ro + elt%dro
  110. ENDDO
  111. ENDDO
  112. WRITE(6,'(a)') " "
  113. WRITE(6,'(a)') " %%%% RESULTS VERIFICATION %%%% "
  114. WRITE(6,'(a)') " "
  115. DO i = 1,Nelt
  116. WRITE(6,'(a,i4,a)') " elt ", i , " ; elt%ro = "
  117. WRITE(6,'(10(1x,F11.2))') mesh%elt(i)%ro
  118. WRITE(6,'(a)') " ------------------------ "
  119. ENDDO
  120. WRITE(6,'(a)') " "
  121. !Deallocation
  122. DO i = 1,Nelt
  123. elt => mesh%elt(i)
  124. DEALLOCATE(elt%ro)
  125. DEALLOCATE(elt%dro)
  126. DEALLOCATE(elt%basis)
  127. ENDDO
  128. DEALLOCATE(mesh%elt)
  129. END PROGRAM f90_example