g_adjust_floats Subroutine

private subroutine g_adjust_floats(g, phi, bpar, facphi, facbpar)

Transform between g_gs2 and g_wesson with direction indicated by passed floats [facphi] and [facbpar].

Arguments

Type IntentOptional Attributes Name
complex, intent(inout), dimension (-ntgrid:,:,g_lo%llim_proc:) :: g
complex, intent(in), dimension (-ntgrid:,:,:) :: phi
complex, intent(in), dimension (-ntgrid:,:,:) :: bpar
real, intent(in) :: facphi
real, intent(in) :: facbpar

Contents

Source Code


Source Code

  subroutine g_adjust_floats (g, phi, bpar, facphi, facbpar)
    use species, only: spec, nonmaxw_corr
    use theta_grid, only: ntgrid
    use le_grids, only: grid_has_trapped_particles, jend
    use gs2_layouts, only: g_lo, ik_idx, it_idx, ie_idx, is_idx, il_idx
    use warning_helpers, only: is_not_zero
    implicit none
    complex, dimension (-ntgrid:,:,g_lo%llim_proc:), intent (in out) :: g
    complex, dimension (-ntgrid:,:,:), intent (in) :: phi, bpar
    real, intent (in) :: facphi, facbpar
    integer :: iglo, ig, ik, it, ie, is, il
    complex :: adj
    logical :: trapped
    logical :: with_bpar, with_phi
    real :: phi_factor, bpar_factor

    trapped = grid_has_trapped_particles()

    with_bpar = is_not_zero(facbpar)
    with_phi = is_not_zero(facphi)

    phi_factor = 0.0

    if (with_bpar) then
       bpar_factor = 2.0*facbpar
    else
       bpar_factor = 0.0
    end if

    !$OMP PARALLEL DO DEFAULT(none) &
    !$OMP PRIVATE(iglo, ig, ik, it, il, ie, is, phi_factor, adj) &
    !$OMP SHARED(g_lo, with_phi, spec, nonmaxw_corr, facphi, ntgrid, trapped, &
    !$OMP jend, bpar_factor, vperp2, aj1, bpar, phi, aj0, g) &
    !$OMP SCHEDULE(static)
    do iglo = g_lo%llim_proc, g_lo%ulim_proc
       ik = ik_idx(g_lo,iglo)
       it = it_idx(g_lo,iglo)
       il = il_idx(g_lo,iglo)

       if (with_phi) then
          ie = ie_idx(g_lo,iglo)
          is = is_idx(g_lo,iglo)
          phi_factor = spec(is)%zt*nonmaxw_corr(ie,is)*facphi
       end if

       ! BD:  bpar == delta B_parallel / B_0(theta) so no extra factor of
       ! 1/bmag is needed here.
       do ig = -ntgrid, ntgrid
          ! Avoid adjusting in the forbidden region
          if ( trapped .and. il > jend(ig)) cycle

          adj = bpar_factor*vperp2(ig,iglo)*aj1(ig,iglo)*bpar(ig,it,ik) &
               + phi_factor*phi(ig,it,ik)*aj0(ig,iglo)

          g(ig,1,iglo) = g(ig,1,iglo) + adj
          g(ig,2,iglo) = g(ig,2,iglo) + adj
       end do
    end do
    !$OMP END PARALLEL DO
  end subroutine g_adjust_floats