do_write_kpar Subroutine

public subroutine do_write_kpar(write_text)

Write the parallel spectrum of , overwriting existing values

Arguments

Type IntentOptional Attributes Name
logical, intent(in) :: write_text

Write to text file


Contents

Source Code


Source Code

  subroutine do_write_kpar(write_text)
    use mp, only: proc0
    use file_utils, only: open_output_file, close_output_file
    use theta_grid, only: ntgrid, gradpar, nperiod
    use kt_grids, only: naky, ntheta0, aky, akx
    use run_parameters, only: has_phi, has_apar, has_bpar
    use fields_arrays, only: phi, apar, bpar
    implicit none

    !> Write to text file
    logical, intent(in) :: write_text

    complex, dimension (:,:,:), allocatable :: phi2, apar2, bpar2
    real, dimension (2*ntgrid) :: kpar
    integer :: ig, ik, it, unit

    if (.not. proc0) return
    if (.not. write_text) return

    allocate (phi2(-ntgrid:ntgrid,ntheta0,naky))
    allocate (apar2(-ntgrid:ntgrid,ntheta0,naky))
    allocate (bpar2(-ntgrid:ntgrid,ntheta0,naky))

    if (has_phi) then
      call par_spectrum(phi, phi2)
    else
      phi2=0.
    end if
    if (has_apar) then
      call par_spectrum(apar, apar2)
    else
      apar2=0.
    endif
    if (has_bpar) then
      call par_spectrum(bpar, bpar2)
    else
      bpar2=0.
    endif

    call open_output_file (unit, ".kpar")
    do ig = 1, ntgrid
      kpar(ig) = (ig-1)*gradpar(ig)/real(2*nperiod-1)
      kpar(2*ntgrid-ig+1)=-(ig)*gradpar(ig)/real(2*nperiod-1)
    end do
    do ik = 1, naky
      do it = 1, ntheta0
        do ig = ntgrid+1,2*ntgrid
          write (unit, "(9(1x,e12.5))") &
               kpar(ig), aky(ik), akx(it), &
               phi2(ig-ntgrid-1,it,ik), &
               apar2(ig-ntgrid-1,it,ik), &
               bpar2(ig-ntgrid-1,it,ik)
        end do
        do ig = 1, ntgrid
          write (unit, "(9(1x,e12.5))") &
               kpar(ig), aky(ik), akx(it), &
               phi2(ig-ntgrid-1,it,ik), &
               apar2(ig-ntgrid-1,it,ik), &
               bpar2(ig-ntgrid-1,it,ik)
        end do
        write (unit, "()")
      end do
    end do
    call close_output_file (unit)

    deallocate (phi2, apar2, bpar2)
  end subroutine do_write_kpar