nprocs Subroutine

private subroutine nprocs(nmesh, report_unit)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nmesh
integer, intent(in) :: report_unit

Contents

Source Code


Source Code

  subroutine nprocs (nmesh, report_unit)
    use nonlinear_terms, only : nonlin
    use species, only : nspec
    use kt_grids, only: naky, ntheta0, nx, ny
    use le_grids, only: negrid, nlambda
    use theta_grid, only: ntgrid
    use gs2_layouts, only: layout, init_x_transform_layouts, init_y_transform_layouts, factors
    use mp, only: nproc, iproc
    implicit none
    integer, intent (in) :: nmesh, report_unit
    integer, dimension(:,:), allocatable :: facs
    integer, dimension(:), allocatable :: mixed_facs, nfac_list, dim_sizes
    integer :: npe, checknpe, i, j, dim_size, nfacs, previous_blocks, nkxkyfacs
    logical :: onlyxoryfac
    character :: layout_char
    write (report_unit, fmt="('Layout = ',a5,/)") layout
    write (report_unit, fmt="('Recommended #proc up to:',i8)") npmax

    ! Initial setup / print headers
    if (nonlin) then
       call init_x_transform_layouts(ntgrid, naky, ntheta0, nlambda, negrid, nspec, nx, nproc, iproc)
       call init_y_transform_layouts(ntgrid, naky, ntheta0, nlambda, negrid, nspec, nx, ny, nproc, iproc)

       ! First write standard sweetspots
       call write_nonlinear_glo_header(report_unit)
    else
       write (report_unit, *)
       write (report_unit, fmt="('Recommended numbers of processors:')")
    end if

    ! Report standard sweet spots
    allocate (facs(max(nspec,naky,ntheta0,negrid,nlambda)/2+1,5))
    allocate (nfac_list(5), dim_sizes(5))
    previous_blocks = 1
    do i = 1, 5
       ! Loop over layout string in reverse
       layout_char = layout(6-i:6-i)
       select case(layout_char)
       case('x')
          dim_size = ntheta0
       case('y')
          dim_size = naky
       case('l')
          dim_size = nlambda
       case('e')
          dim_size = negrid
       case('s')
          dim_size = nspec
       end select
       dim_sizes(i) = dim_size
       call factors (dim_size, nfacs, facs(:,i))
       nfac_list(i) = nfacs
       ! Note special handling for the first call
       if (nonlin) then
          if (i == 1) call write_nonlinear_sweet_spot(layout_char, report_unit, 2, [1, 1], 1, npmax)
          call write_nonlinear_sweet_spot(layout_char,report_unit, nfacs, facs(:, i), &
               previous_blocks, npmax)
       else
          if (i == 1) call write_linear_sweet_spot(layout_char, report_unit, 2, [1, 1], 1, nmesh,ncut)
          call write_linear_sweet_spot(layout_char,report_unit, nfacs, facs(:, i), &
               previous_blocks, nmesh, ncut)
       end if
       previous_blocks = previous_blocks * dim_size
    end do

    ! Now we might want to write sweetspots based on factors of x*y if NL
    if (nonlin) then
       select case (layout)
       case ('yxels', 'yxles', 'xyles')
          write (report_unit, fmt="('------------------------------------------------------------------------------------------------------------------------------------------------')")
          write (report_unit, fmt="(/,'Mixed kx*ky sweetspots (note these are often not recommended:)')")
          call write_nonlinear_glo_header(report_unit)
          allocate (mixed_facs((ntheta0*naky)/2+1))
          call factors (naky*ntheta0, nkxkyfacs, mixed_facs)
          previous_blocks = nlambda * negrid * nspec
          kxky: do i = 2, nkxkyfacs
             npe = mixed_facs(i) * previous_blocks
             if (npe > npmax) exit
             ! Check whether this process count would have been generated by the
             ! plain x or y factorisation or if it is new from the combined x*y
             ! functionality
             onlyxoryfac = .false.
             do j=2, nfac_list(4)
                checknpe = facs(j, 4) * previous_blocks
                if (npe == checknpe) cycle kxky
             end do
             do j = 2, nfac_list(5)
                checknpe = facs(j,5) * dim_sizes(4) * previous_blocks
                if (npe == checknpe) cycle kxky
             end do
             if (.not. onlyxoryfac) call report_idle_procs(npe, 'x*y', report_unit, onlyxoryfac)
          end do kxky
       end select

       write (report_unit, fmt="('------------------------------------------------------------------------------------------------------------------------------------------------')")
       write (report_unit, *)
       write (report_unit, fmt="('(*) denotes process counts that are from factors of the combined kx*ky index rather than the ordered kx or ky indices separately.')")
       write (report_unit, fmt="('To use the unbalanced functionality set unbalanced_xxf = .true. or unbalanced_yxf = .true. in the &layouts_knobs namelist in your GS2 ')")
       write (report_unit, fmt="('input file. You can also set the max_unbalanced_xxf and max_unbalanced_yxf flags in the same namelist in the input file to specify the')")
       write (report_unit, fmt="('maximum amount of computational imbalance allowed. These flags specify the maximum imbalance as 1 with no imbalance as 0, so to allow')")
       write (report_unit, fmt="('50% imbalanced on the xxf decomposition using the following flags in the input file: ')")
       write (report_unit, fmt="('                                                                                     unbalanced_xxf = .true. ')")
       write (report_unit, fmt="('                                                                                     max_unbalanced_xxf = 0.5 ')")
       write (report_unit, fmt="('And likewise for yxf.')")
    end if
    deallocate (facs)
  end subroutine nprocs