nf_sched_ctx.f90 6.1 KB

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