nf_sched_ctx.f90 6.2 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178
  1. ! StarPU --- Runtime system for heterogeneous multicore architectures.
  2. !
  3. ! Copyright (C) 2017 CNRS
  4. ! Copyright (C) 2016 Inria
  5. ! Copyright (C) 2017 Université de Bordeaux
  6. !
  7. ! StarPU is free software; you can redistribute it and/or modify
  8. ! it under the terms of the GNU Lesser General Public License as published by
  9. ! the Free Software Foundation; either version 2.1 of the License, or (at
  10. ! your option) any later version.
  11. !
  12. ! StarPU is distributed in the hope that it will be useful, but
  13. ! WITHOUT ANY WARRANTY; without even the implied warranty of
  14. ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
  15. !
  16. ! See the GNU Lesser General Public License in COPYING.LGPL for more details.
  17. !
  18. program nf_sched_ctx
  19. use iso_c_binding ! C interfacing module
  20. use fstarpu_mod ! StarPU interfacing module
  21. use nf_sched_ctx_cl
  22. implicit none
  23. type(c_ptr) :: cl1 ! a pointer for a codelet structure
  24. type(c_ptr) :: cl2 ! a pointer for another codelet structure
  25. integer(c_int) :: err ! return status for fstarpu_init
  26. integer(c_int) :: ncpu ! number of cpus workers
  27. ! list of cpu worker ids
  28. integer(c_int), dimension(:), allocatable :: procs
  29. ! sub-list of cpu worker ids for sched context 1
  30. integer(c_int) :: nprocs1
  31. integer(c_int), dimension(:), allocatable :: procs1
  32. integer(c_int) :: ctx1
  33. ! sub-list of cpu worker ids for sched context 2
  34. integer(c_int) :: nprocs2
  35. integer(c_int), dimension(:), allocatable :: procs2
  36. integer(c_int) :: ctx2
  37. ! needed to be able to call c_loc on it, to get a ptr to the string
  38. character(kind=c_char,len=6), target :: ctx2_policy = C_CHAR_"eager"//C_NULL_CHAR
  39. integer(c_int),parameter :: n = 20
  40. integer(c_int) :: i
  41. integer(c_int), target :: arg_id
  42. integer(c_int), target :: arg_ctx
  43. ! initialize StarPU with default settings
  44. err = fstarpu_init(C_NULL_PTR)
  45. if (err == -19) then
  46. stop 77
  47. end if
  48. ! stop there if no CPU worker available
  49. ncpu = fstarpu_cpu_worker_get_count()
  50. if (ncpu == 0) then
  51. call fstarpu_shutdown()
  52. stop 77
  53. end if
  54. ! actually we really need at least 2 CPU workers such to allocate 2 non overlapping contexts
  55. if (ncpu < 2) then
  56. call fstarpu_shutdown()
  57. stop 77
  58. end if
  59. ! allocate and fill codelet structs
  60. cl1 = fstarpu_codelet_allocate()
  61. call fstarpu_codelet_set_name(cl1, C_CHAR_"sched_ctx_cl1"//C_NULL_CHAR)
  62. call fstarpu_codelet_add_cpu_func(cl1, C_FUNLOC(cl_cpu_func_sched_ctx))
  63. ! allocate and fill codelet structs
  64. cl2 = fstarpu_codelet_allocate()
  65. call fstarpu_codelet_set_name(cl2, C_CHAR_"sched_ctx_cl2"//C_NULL_CHAR)
  66. call fstarpu_codelet_add_cpu_func(cl2, C_FUNLOC(cl_cpu_func_sched_ctx))
  67. ! get the list of CPU worker ids
  68. allocate(procs(ncpu))
  69. err = fstarpu_worker_get_ids_by_type(FSTARPU_CPU_WORKER, procs, ncpu)
  70. ! split the workers in two sets
  71. nprocs1 = ncpu/2;
  72. allocate(procs1(nprocs1))
  73. write(*,*) "procs1:"
  74. do i=1,nprocs1
  75. procs1(i) = procs(i)
  76. write(*,*) i, procs1(i)
  77. end do
  78. nprocs2 = ncpu - nprocs1
  79. allocate(procs2(nprocs2))
  80. write(*,*) "procs2:"
  81. do i=1,nprocs2
  82. procs2(i) = procs(nprocs1+i)
  83. write(*,*) i, procs2(i)
  84. end do
  85. deallocate(procs)
  86. ! create sched context 1 with default policy, by giving a NULL policy name
  87. ctx1 = fstarpu_sched_ctx_create(procs1, nprocs1, &
  88. C_CHAR_"ctx1"//C_NULL_CHAR, &
  89. (/ FSTARPU_SCHED_CTX_POLICY_NAME, c_null_ptr, c_null_ptr /) &
  90. )
  91. ! create sched context 2 with a user selected policy name
  92. ctx2 = fstarpu_sched_ctx_create(procs2, nprocs2, &
  93. C_CHAR_"ctx2"//C_NULL_CHAR, &
  94. (/ FSTARPU_SCHED_CTX_POLICY_NAME, c_loc(ctx2_policy), c_null_ptr /))
  95. ! set inheritor context
  96. call fstarpu_sched_ctx_set_inheritor(ctx2, ctx1);
  97. call fstarpu_sched_ctx_display_workers(ctx1)
  98. call fstarpu_sched_ctx_display_workers(ctx2)
  99. do i = 1, n
  100. ! submit a task on context 1
  101. arg_id = 1*1000 + i
  102. arg_ctx = ctx1
  103. call fstarpu_insert_task((/ cl1, &
  104. FSTARPU_VALUE, c_loc(arg_id), FSTARPU_SZ_C_INT, &
  105. FSTARPU_SCHED_CTX, c_loc(arg_ctx), &
  106. C_NULL_PTR /))
  107. end do
  108. do i = 1, n
  109. ! now submit a task on context 2
  110. arg_id = 2*1000 + i
  111. arg_ctx = ctx2
  112. call fstarpu_insert_task((/ cl2, &
  113. FSTARPU_VALUE, c_loc(arg_id), FSTARPU_SZ_C_INT, &
  114. FSTARPU_SCHED_CTX, c_loc(arg_ctx), &
  115. C_NULL_PTR /))
  116. end do
  117. ! mark submission process as completed on context 2
  118. call fstarpu_sched_ctx_finished_submit(ctx2)
  119. do i = 1, n
  120. ! now submit a task on context 1 again
  121. arg_id = 1*10000 + i
  122. arg_ctx = ctx1
  123. call fstarpu_insert_task((/ cl1, &
  124. FSTARPU_VALUE, c_loc(arg_id), FSTARPU_SZ_C_INT, &
  125. FSTARPU_SCHED_CTX, c_loc(arg_ctx), &
  126. C_NULL_PTR /))
  127. end do
  128. ! mark submission process as completed on context 1
  129. call fstarpu_sched_ctx_finished_submit(ctx1)
  130. ! wait for completion of all tasks
  131. call fstarpu_task_wait_for_all()
  132. ! show how to add some workers from a context to another
  133. call fstarpu_sched_ctx_add_workers(procs1, nprocs1, ctx2)
  134. ! deallocate both contexts
  135. call fstarpu_sched_ctx_delete(ctx2)
  136. call fstarpu_sched_ctx_delete(ctx1)
  137. deallocate(procs2)
  138. deallocate(procs1)
  139. ! free codelet structure
  140. call fstarpu_codelet_free(cl1)
  141. call fstarpu_codelet_free(cl2)
  142. ! shut StarPU down
  143. call fstarpu_shutdown()
  144. end program nf_sched_ctx