f90_example.f90 3.8 KB

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