add_nl_gryfx Subroutine

private subroutine add_nl_gryfx(g1)

this subroutine constructs the GK nonlinear term from the 6 GryfX gyrofluid nonlinear terms. we first construct in gryfx units. gryfx uses vt=sqrt(T/m) normalization, so vt_gs2 = sqrt(2T/m) = sqrt(2) vt_gryfx. since vpa and vperp2 are normalized to vt_gs2, below we multiply by factors of sqrt(2) to get vpa and vperp2 in gryfx units, i.e. vpa_gryfx = sqrt(2) vpa vperp2_gryfx = 2 vperp2

the Hermite-Laguerre construction of the distribution from the gyrofluid moments is of the form df/F_M = n + vpar/vt upar + 1/2(vpar^2/vt^2-1) tpar + (vprp^2/2vt^2-1) tprp + 1/6(vpar^3/3vt^3 - 3 vpar/vt) qpar + vpar/vt (vprp^2/2vt^2-1) qprp where vt=vt_gryfx, and moments are normalized in gryfx units

Arguments

Type IntentOptional Attributes Name
complex, intent(out), dimension (-ntgrid:,:,g_lo%llim_proc:) :: g1

Contents

Source Code


Source Code

  subroutine add_nl_gryfx (g1)
    use mp, only: max_allreduce
    use theta_grid, only: ntgrid
    use gs2_layouts, only: g_lo, ik_idx, it_idx, is_idx
    use dist_fn_arrays, only: vpa, vperp2
    use gs2_transforms, only: transform2, inverse2
    use gs2_time, only: save_dt_cfl, check_time_step_too_large
    use mp, only: broadcast
    implicit none
    complex, dimension (-ntgrid:,:,g_lo%llim_proc:), intent (out) :: g1

    integer :: iglo, ik, it, ig, iz, is, isgn, index_gryfx

    do iglo = g_lo%llim_proc, g_lo%ulim_proc
       ik = ik_idx(g_lo,iglo)
       it = it_idx(g_lo,iglo)
       is = is_idx(g_lo,iglo)
       do isgn = 1, 2
          do ig = -ntgrid, ntgrid
             iz = ig + ntgrid + 1
             if(ig==ntgrid) iz = 1 ! periodic point not included in gryfx arrays
             index_gryfx = 1 + (ik-1) + g_lo%naky*((it-1)) + &
                  g_lo%naky*g_lo%ntheta0*(iz-1) + &
                  (2*ntgrid)*g_lo%naky*g_lo%ntheta0*(is-1)
             
             g1(ig,isgn,iglo) =  gryfx_zonal%NLdens_ky0(index_gryfx) + &
                  
                  0.5*(2.*vpa(ig,isgn,iglo)*vpa(ig,isgn,iglo) - 1.)* &
                  gryfx_zonal%NLtpar_ky0(index_gryfx) + &
                  
                  (vperp2(ig,iglo) - 1.0)* &
                  gryfx_zonal%NLtprp_ky0(index_gryfx) + &

                  sqrt(2.)*vpa(ig,isgn,iglo)* &
                     gryfx_zonal%NLupar_ky0(index_gryfx) + &
                     
                     1./6.*( (sqrt(2.)*vpa(ig,isgn,iglo))**3. &
                     - 3*sqrt(2.)*vpa(ig,isgn,iglo) )* &
                     gryfx_zonal%NLqpar_ky0(index_gryfx) + &
                     
                     sqrt(2.)*vpa(ig,isgn,iglo)*(vperp2(ig,iglo) - 1.)* &
                     gryfx_zonal%NLqprp_ky0(index_gryfx) 
             
             ! now we must account for the fact that phi and g are normalized to a/rho_i,
             ! and grad ~ k is normalized to rho_i, and rho_gs2 = sqrt2 rho_gryfx.
             ! we have just calculated the GK nonlinear term in gryfx units:
             ! g1 = z_hat X grad_gryfx phi_gryfx . grad_gryfx g_gryfx =
             ! z_hat X (1/sqrt2 grad_gs2)(sqrt2 phi_gs2) . (1/sqrt2 grad_gs2)(sqrt2 g_gs2)
             ! = z_hat X grad_gs2 phi_gs2 . grad_gs2 g_gs2
             ! so it turns out that the GK nonlinear term is the same in gryfx units
             ! and gs2 units, so we don't need any additional factors.

          end do
       end do
    end do
    g1 = -g1 !left-handed / right-handed conversion    
  end subroutine add_nl_gryfx