Construct a build schedule from the sorted targets.
The schedule is broken into regions, described by schedule_ptr
,
where targets in each region can be compiled in parallel.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
type(build_target_ptr), | intent(out), | allocatable | :: | queue(:) | ||
integer, | allocatable | :: | schedule_ptr(:) | |||
type(build_target_ptr), | intent(in) | :: | targets(:) |
subroutine schedule_targets(queue, schedule_ptr, targets) type(build_target_ptr), allocatable, intent(out) :: queue(:) integer, allocatable :: schedule_ptr(:) type(build_target_ptr), intent(in) :: targets(:) integer :: i, j integer :: n_schedule, n_sorted n_schedule = 0 ! Number of schedule regions n_sorted = 0 ! Total number of targets to build do i=1,size(targets) if (targets(i)%ptr%sorted) then n_sorted = n_sorted + 1 end if n_schedule = max(n_schedule, targets(i)%ptr%schedule) end do allocate(queue(n_sorted)) allocate(schedule_ptr(n_schedule+1)) ! Construct the target queue and schedule region pointer n_sorted = 1 schedule_ptr(n_sorted) = 1 do i=1,n_schedule do j=1,size(targets) if (targets(j)%ptr%sorted) then if (targets(j)%ptr%schedule == i) then queue(n_sorted)%ptr => targets(j)%ptr n_sorted = n_sorted + 1 end if end if end do schedule_ptr(i+1) = n_sorted end do end subroutine schedule_targets