potential_root_mpi_curv Module Procedure

module procedure potential_root_mpi_curv module subroutine potential_root_mpi_curv(it, t, dt, sig0, sigP, sigH, incap, vs2, vs3, vn2, vn3, sourcemlat, B1, x, potsolve, flagcap, E1, E2, E3, J1, J2, J3, Phiall, flagE0file, dtE0, E0dir, ymd, UTsec)

ROOT MPI COMM./SOLVE ROUTINE FOR POTENTIAL. THIS VERSION INCLUDES THE POLARIZATION CURRENT TIME DERIVATIVE PART AND CONVECTIVE PARTS IN MATRIX SOLUTION. STATE VARIABLES VS2,3 INCLUDE GHOST CELLS. FOR NOW THE POLARIZATION TERMS ARE PASSED BACK TO MAIN FN, EVEN THOUGH THEY ARE NOT USED (THEY MAY BE IN THE FUTURE)

POPULATE BACKGROUND AND BOUNDARY CONDITION ARRAYS - IDEALLY ROOT ONLY SINCE IT INVOLVES FILE INPUT, ALTHOUGH THE INTERPOLATION MAY BE SLOW... wind x2 current, note that all workers already have a copy of this. wind x3 current wind x2 current wind x3 current !!!!!!

INTEGRATE CONDUCTANCES AND CAPACITANCES FOR SOLVER COEFFICIENTS PRODUCE A FIELD-INTEGRATED SOURCE TERM workers don't have access to boundary conditions, unless root sends

need to pick out the ExB drift here (i.e. the drifts from highest altitudes); but this is only valid for Cartesian, so it's okay for the foreseeable future

note tha this solver is only valid for cartesian meshes, unless the inertial capacitance is set to zero !note that either sigPint2 or 3 will work since this must be cartesian... Dirichlet conditions - since this is field integrated we just copy BCs specified by user to other locations along field line

potential is whatever user specifies, since we assume equipotential field lines, it doesn't really matter whether we use Vmaxx1 or Vminx1. Note however, tha thte boundary conditions subroutines should explicitly set these to be equal with Dirichlet conditions, for consistency. copy the potential across the ix1 direction; past this point there is no real difference with 3D, note that this is still valid in curvilinear form resolved 3D solve ZZZ - conductivities need to be properly scaled here... So does the source term... Maybe leave as broken for now since I don't really plan to use this code in a 2D solve negate this due to it being a cross produce and the fact that we've permuted the 2 and 3 dimensions. ZZZ - NOT JUST THIS WORKS WITH BACKGROUND FIELDS???

EXECUTE THE SOLVE WITH MUMPS AND SCALED TERMS NOTE THE LACK OF A SPECIAL CASE HERE TO CHANGE THE POTENTIAL PROBLEM - ONLY THE HALL TERM CHANGES (SINCE RELATED TO EXB) BUT THAT DOESN'T APPEAR IN THIS EQN! !!!!!!!

STORE PREVIOUS TIME TOTAL FIELDS BEFORE UPDATING THE ELECTRIC FIELDS WITH NEW POTENTIAL (OLD FIELDS USED TO CALCULATE POLARIZATION CURRENT) causes major memory leak. maybe from arithmetic statement argument? Left here as a 'lesson learned' (or is it a gfortran bug...)

ZZZ this is really bad needs to be a global test rather than having each worker test since there is message passing embedded in here and everyone needs to do the same thing!!! !!!!!!

Neumann conditions, this is boundary location-agnostic since both bottom and top FACs are known - they have to be loaded into VVmaxx1 and Vminx1 Dirichlet conditions - we need to integrate from the lowest altitude (where FAC is known to be zero, note this is not necessarilty the logical bottom of the grid), upwards (to where it isn't) !!!!!!!

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: it
real(kind=wp), intent(in) :: t
real(kind=wp), intent(in) :: dt
real(kind=wp), intent(in), dimension(:,:,:):: sig0
real(kind=wp), intent(in), dimension(:,:,:):: sigP
real(kind=wp), intent(in), dimension(:,:,:):: sigH
real(kind=wp), intent(in), dimension(:,:,:):: incap
real(kind=wp), intent(in), dimension(-1:,-1:,-1:,:):: vs2
real(kind=wp), intent(in), dimension(-1:,-1:,-1:,:):: vs3
real(kind=wp), intent(in), dimension(:,:,:):: vn2
real(kind=wp), intent(in), dimension(:,:,:):: vn3
real(kind=wp), intent(in) :: sourcemlat
real(kind=wp), intent(in), dimension(-1:,-1:,-1:):: B1
type(curvmesh), intent(in) :: x
integer, intent(in) :: potsolve
integer, intent(in) :: flagcap
real(kind=wp), intent(out), dimension(:,:,:):: E1
real(kind=wp), intent(out), dimension(:,:,:):: E2
real(kind=wp), intent(out), dimension(:,:,:):: E3
real(kind=wp), intent(out), dimension(:,:,:):: J1
real(kind=wp), intent(out), dimension(:,:,:):: J2
real(kind=wp), intent(out), dimension(:,:,:):: J3
real(kind=wp), intent(inout), dimension(:,:,:):: Phiall
integer, intent(in) :: flagE0file
real(kind=wp), intent(in) :: dtE0
character(len=*), intent(in) :: E0dir
integer, intent(in), dimension(3):: ymd
real(kind=wp), intent(in) :: UTsec

Calls

proc~~potential_root_mpi_curv~~CallsGraph proc~potential_root_mpi_curv potential_root_mpi_curv interface~potential2d_polarization_periodic potential2D_polarization_periodic proc~potential_root_mpi_curv->interface~potential2d_polarization_periodic interface~gather_recv gather_recv proc~potential_root_mpi_curv->interface~gather_recv proc~halo_pot halo_pot proc~potential_root_mpi_curv->proc~halo_pot interface~bcast_send bcast_send proc~potential_root_mpi_curv->interface~bcast_send interface~potential2d_fieldresolved potential2D_fieldresolved proc~potential_root_mpi_curv->interface~potential2d_fieldresolved proc~potentialbcs2d potentialBCs2D proc~potential_root_mpi_curv->proc~potentialbcs2d mpi_send mpi_send proc~potential_root_mpi_curv->mpi_send proc~potentialbcs2d_fileinput potentialBCs2D_fileinput proc~potential_root_mpi_curv->proc~potentialbcs2d_fileinput interface~div3d div3D proc~potential_root_mpi_curv->interface~div3d interface~integral3d1_curv_alt integral3D1_curv_alt proc~potential_root_mpi_curv->interface~integral3d1_curv_alt interface~integral3d1 integral3D1 proc~potential_root_mpi_curv->interface~integral3d1 interface~grad3d2 grad3D2 proc~potential_root_mpi_curv->interface~grad3d2 interface~grad3d1 grad3D1 proc~potential_root_mpi_curv->interface~grad3d1 interface~potential2d_polarization potential2D_polarization proc~potential_root_mpi_curv->interface~potential2d_polarization proc~potential3d_fieldresolved_decimate potential3D_fieldresolved_decimate proc~potential_root_mpi_curv->proc~potential3d_fieldresolved_decimate interface~grad3d3 grad3D3 proc~potential_root_mpi_curv->interface~grad3d3 proc~potential2d_polarization_periodic potential2D_polarization_periodic interface~potential2d_polarization_periodic->proc~potential2d_polarization_periodic interface~gather_recv4d_23 gather_recv4D_23 interface~gather_recv->interface~gather_recv4d_23 interface~gather_recv3d_23 gather_recv3D_23 interface~gather_recv->interface~gather_recv3d_23 interface~gather_recv2d_23 gather_recv2D_23 interface~gather_recv->interface~gather_recv2d_23 interface~halo halo proc~halo_pot->interface~halo interface~bcast_send1d_23 bcast_send1D_23 interface~bcast_send->interface~bcast_send1d_23 interface~bcast_send2d_23 bcast_send2D_23 interface~bcast_send->interface~bcast_send2d_23 interface~bcast_send4d_23 bcast_send4D_23 interface~bcast_send->interface~bcast_send4d_23 interface~bcast_send3d_23 bcast_send3D_23 interface~bcast_send->interface~bcast_send3d_23 proc~potential2d_fieldresolved potential2D_fieldresolved interface~potential2d_fieldresolved->proc~potential2d_fieldresolved interface~interp2 interp2 proc~potentialbcs2d_fileinput->interface~interp2 proc~interp1 interp1 proc~potentialbcs2d_fileinput->proc~interp1 interface~get_grid2 get_grid2 proc~potentialbcs2d_fileinput->interface~get_grid2 interface~get_simsize2 get_simsize2 proc~potentialbcs2d_fileinput->interface~get_simsize2 proc~date_filename date_filename proc~potentialbcs2d_fileinput->proc~date_filename proc~dateinc dateinc proc~potentialbcs2d_fileinput->proc~dateinc interface~div3d_curv_23 div3D_curv_23 interface~div3d->interface~div3d_curv_23 proc~integral3d1_curv_alt integral3D1_curv_alt interface~integral3d1_curv_alt->proc~integral3d1_curv_alt interface~integral3d1_curv integral3D1_curv interface~integral3d1->interface~integral3d1_curv interface~grad3d2_curv_23 grad3D2_curv_23 interface~grad3d2->interface~grad3d2_curv_23 interface~grad3d1_curv_23 grad3D1_curv_23 interface~grad3d1->interface~grad3d1_curv_23 proc~potential2d_polarization potential2D_polarization interface~potential2d_polarization->proc~potential2d_polarization proc~potential3d_fieldresolved_decimate->interface~grad3d2 proc~potential3d_fieldresolved_decimate->interface~grad3d1 proc~potential3d_fieldresolved_decimate->interface~grad3d3 proc~potential3d_fieldresolved_decimate->proc~interp1 interface~elliptic3d_cart elliptic3D_cart proc~potential3d_fieldresolved_decimate->interface~elliptic3d_cart interface~grad3d3_curv_23 grad3D3_curv_23 interface~grad3d3->interface~grad3d3_curv_23 proc~interp2 interp2 interface~interp2->proc~interp2 proc~gather_recv4d_23 gather_recv4D_23 interface~gather_recv4d_23->proc~gather_recv4d_23 interface~elliptic2d_cart elliptic2D_cart proc~potential2d_fieldresolved->interface~elliptic2d_cart proc~gather_recv3d_23 gather_recv3D_23 interface~gather_recv3d_23->proc~gather_recv3d_23 interface~grad2d1_curv_alt grad2D1_curv_alt proc~potential2d_polarization->interface~grad2d1_curv_alt interface~elliptic2d_polarization elliptic2D_polarization proc~potential2d_polarization->interface~elliptic2d_polarization interface~grad2d3 grad2D3 proc~potential2d_polarization->interface~grad2d3 proc~bcast_send2d_23 bcast_send2D_23 interface~bcast_send2d_23->proc~bcast_send2d_23 proc~grad3d3_curv_23 grad3D3_curv_23 interface~grad3d3_curv_23->proc~grad3d3_curv_23 proc~gather_recv2d_23 gather_recv2D_23 interface~gather_recv2d_23->proc~gather_recv2d_23 proc~potential2d_polarization_periodic->interface~grad2d1_curv_alt interface~elliptic2d_polarization_periodic elliptic2D_polarization_periodic proc~potential2d_polarization_periodic->interface~elliptic2d_polarization_periodic proc~grad2d3_curv_periodic grad2D3_curv_periodic proc~potential2d_polarization_periodic->proc~grad2d3_curv_periodic proc~get_grid2 get_grid2 interface~get_grid2->proc~get_grid2 proc~elliptic3d_cart elliptic3D_cart interface~elliptic3d_cart->proc~elliptic3d_cart proc~bcast_send4d_23 bcast_send4D_23 interface~bcast_send4d_23->proc~bcast_send4d_23 proc~grad3d1_curv_23 grad3D1_curv_23 interface~grad3d1_curv_23->proc~grad3d1_curv_23 proc~bcast_send3d_23 bcast_send3D_23 interface~bcast_send3d_23->proc~bcast_send3d_23 proc~integral3d1_curv integral3D1_curv interface~integral3d1_curv->proc~integral3d1_curv proc~get_simsize2 get_simsize2 interface~get_simsize2->proc~get_simsize2 proc~grad3d2_curv_23 grad3D2_curv_23 interface~grad3d2_curv_23->proc~grad3d2_curv_23 proc~utsec2filestem utsec2filestem proc~date_filename->proc~utsec2filestem proc~day_wrap day_wrap proc~dateinc->proc~day_wrap interface~halo_23 halo_23 interface~halo->interface~halo_23 proc~div3d_curv_23 div3D_curv_23 interface~div3d_curv_23->proc~div3d_curv_23 proc~elliptic2d_cart elliptic2D_cart interface~elliptic2d_cart->proc~elliptic2d_cart proc~grad2d1_curv_alt_23 grad2D1_curv_alt_23 interface~grad2d1_curv_alt->proc~grad2d1_curv_alt_23 proc~elliptic2d_polarization elliptic2D_polarization interface~elliptic2d_polarization->proc~elliptic2d_polarization mumps_exec mumps_exec proc~elliptic3d_cart->mumps_exec proc~check_mumps_status check_mumps_status proc~elliptic3d_cart->proc~check_mumps_status mumps_perm mumps_perm proc~elliptic3d_cart->mumps_perm proc~quiet_mumps quiet_mumps proc~elliptic3d_cart->proc~quiet_mumps proc~grad2d3_curv_23 grad2D3_curv_23 interface~grad2d3->proc~grad2d3_curv_23 mpi_recv mpi_recv proc~gather_recv4d_23->mpi_recv proc~slabinds slabinds proc~gather_recv4d_23->proc~slabinds proc~bcast_send2d_23->mpi_send proc~bcast_send2d_23->proc~slabinds proc~elliptic2d_polarization_periodic elliptic2D_polarization_periodic interface~elliptic2d_polarization_periodic->proc~elliptic2d_polarization_periodic proc~gather_recv3d_23->mpi_recv proc~gather_recv3d_23->proc~slabinds proc~day_wrap->proc~day_wrap proc~daysmonth daysmonth proc~day_wrap->proc~daysmonth proc~bcast_send3d_23->mpi_send proc~bcast_send3d_23->proc~slabinds proc~gather_recv2d_23->mpi_recv proc~gather_recv2d_23->proc~slabinds proc~halo_23 halo_23 interface~halo_23->proc~halo_23 proc~bcast_send4d_23->mpi_send proc~bcast_send4d_23->proc~slabinds proc~utsec2filestem->proc~day_wrap proc~elliptic2d_polarization->mumps_exec proc~elliptic2d_polarization->proc~check_mumps_status proc~elliptic2d_polarization->mumps_perm proc~elliptic2d_polarization->proc~quiet_mumps mpi_irecv mpi_irecv proc~halo_23->mpi_irecv proc~grid2id grid2ID proc~halo_23->proc~grid2id mpi_isend mpi_isend proc~halo_23->mpi_isend mpi_waitall mpi_waitall proc~halo_23->mpi_waitall proc~id2grid ID2grid proc~slabinds->proc~id2grid proc~elliptic2d_cart->mumps_exec proc~elliptic2d_cart->proc~check_mumps_status proc~elliptic2d_cart->mumps_perm proc~elliptic2d_cart->proc~quiet_mumps proc~elliptic2d_polarization_periodic->mumps_exec proc~elliptic2d_polarization_periodic->proc~check_mumps_status proc~elliptic2d_polarization_periodic->mumps_perm proc~elliptic2d_polarization_periodic->proc~quiet_mumps

Called by

proc~~potential_root_mpi_curv~~CalledByGraph proc~potential_root_mpi_curv potential_root_mpi_curv interface~potential_root_mpi_curv potential_root_mpi_curv interface~potential_root_mpi_curv->proc~potential_root_mpi_curv interface~potential_root_mpi potential_root_mpi interface~potential_root_mpi->interface~potential_root_mpi_curv proc~electrodynamics_curv electrodynamics_curv proc~electrodynamics_curv->interface~potential_root_mpi interface~electrodynamics electrodynamics interface~electrodynamics->proc~electrodynamics_curv program~gemini3d Gemini3D program~gemini3d->interface~electrodynamics

Contents

None