MPI-AMRVAC 3.2
The MPI - Adaptive Mesh Refinement - Versatile Advection Code
Loading...
Searching...
No Matches
mod_rmhd_phys.t
Go to the documentation of this file.
1!> Radiation-magneto-hydrodynamics module
3
4#include "amrvac.h"
5
6 use mod_global_parameters, only: std_len, const_c
10 use mod_comm_lib, only: mpistop
12
13 implicit none
14 private
15
16 !> The adiabatic index
17 double precision, public :: rmhd_gamma = 5.d0/3.0d0
18 !> The adiabatic constant
19 double precision, public :: rmhd_adiab = 1.0d0
20 !> The MHD resistivity
21 double precision, public :: rmhd_eta = 0.0d0
22 !> The MHD hyper-resistivity
23 double precision, public :: rmhd_eta_hyper = 0.0d0
24 !> Hall resistivity
25 double precision, public :: rmhd_etah = 0.0d0
26 !> The small_est allowed energy
27 double precision, protected :: small_e
28 !> The smallest allowed radiation energy
29 double precision, public, protected :: small_r_e = 0.d0
30 !> Height of the mask used in the TRAC method
31 double precision, public, protected :: rmhd_trac_mask = 0.d0
32 !> GLM-MHD parameter: ratio of the diffusive and advective time scales for div b
33 !> taking values within [0, 1]
34 double precision, public :: rmhd_glm_alpha = 0.5d0
35 !> The thermal conductivity kappa in hyperbolic thermal conduction
36 double precision, public :: hypertc_kappa
37 !> Coefficient of diffusive divB cleaning
38 double precision :: divbdiff = 0.8d0
39 !> Helium abundance over Hydrogen
40 double precision, public, protected :: he_abundance=0.1d0
41 !> Ionization fraction of H
42 !> H_ion_fr = H+/(H+ + H)
43 double precision, public, protected :: h_ion_fr=1d0
44 !> Ionization fraction of He
45 !> He_ion_fr = (He2+ + He+)/(He2+ + He+ + He)
46 double precision, public, protected :: he_ion_fr=1d0
47 !> Ratio of number He2+ / number He+ + He2+
48 !> He_ion_fr2 = He2+/(He2+ + He+)
49 double precision, public, protected :: he_ion_fr2=1d0
50 ! used for eq of state when it is not defined by units,
51 ! the units do not contain terms related to ionization fraction
52 ! and it is p = RR * rho * T
53 double precision, public, protected :: rr=1d0
54 !> gamma minus one and its inverse
55 double precision :: gamma_1, inv_gamma_1
56 !> inverse of squared speed of light c0 and reduced speed of light c
57 double precision :: inv_squared_c0, inv_squared_c
58 !> equi vars indices in the state%equi_vars array
59 integer, public :: equi_rho0_ = -1
60 integer, public :: equi_pe0_ = -1
61 !> Number of tracer species
62 integer, public, protected :: rmhd_n_tracer = 0
63 !> Index of the density (in the w array)
64 integer, public, protected :: rho_
65 !> Indices of the momentum density
66 integer, allocatable, public, protected :: mom(:)
67 !> Indices of the momentum density for the form of better vectorization
68 integer, public, protected :: ^c&m^C_
69 !> Index of the energy density (-1 if not present)
70 integer, public, protected :: e_
71 !> Index of the radiation energy
72 integer, public, protected :: r_e
73 !> Indices of the magnetic field for the form of better vectorization
74 integer, public, protected :: ^c&b^C_
75 !> Index of the gas pressure (-1 if not present) should equal e_
76 integer, public, protected :: p_
77 !> Index of the heat flux q
78 integer, public, protected :: q_
79 !> Indices of the GLM psi
80 integer, public, protected :: psi_
81 !> Indices of temperature
82 integer, public, protected :: te_
83 !> Index of the cutoff temperature for the TRAC method
84 integer, public, protected :: tcoff_
85 integer, public, protected :: tweight_
86 !> Indices of the tracers
87 integer, allocatable, public, protected :: tracer(:)
88 !> The number of waves
89 integer :: nwwave=8
90 !> Method type in a integer for good performance
91 integer :: type_divb
92 !> To skip * layer of ghost cells during divB=0 fix for boundary
93 integer, public, protected :: boundary_divbfix_skip(2*^nd)=0
94 ! DivB cleaning methods
95 integer, parameter :: divb_none = 0
96 integer, parameter :: divb_multigrid = -1
97 integer, parameter :: divb_glm = 1
98 integer, parameter :: divb_powel = 2
99 integer, parameter :: divb_janhunen = 3
100 integer, parameter :: divb_linde = 4
101 integer, parameter :: divb_lindejanhunen = 5
102 integer, parameter :: divb_lindepowel = 6
103 integer, parameter :: divb_lindeglm = 7
104 integer, parameter :: divb_ct = 8
105 !> Whether an energy equation is used
106 logical, public, protected :: rmhd_energy = .true.
107 !> Whether thermal conduction is used
108 logical, public, protected :: rmhd_thermal_conduction = .false.
109 !> Whether thermal conduction is used
110 logical, public, protected :: rmhd_hyperbolic_thermal_conduction = .false.
111 !> Whether viscosity is added
112 logical, public, protected :: rmhd_viscosity = .false.
113 !> Whether gravity is added
114 logical, public, protected :: rmhd_gravity = .false.
115 !> Whether particles module is added
116 logical, public, protected :: rmhd_particles = .false.
117 !> Whether GLM-MHD is used to control div B
118 logical, public, protected :: rmhd_glm = .false.
119 !> Whether extended GLM-MHD is used with additional sources
120 logical, public, protected :: rmhd_glm_extended = .true.
121 !> Whether TRAC method is used
122 logical, public, protected :: rmhd_trac = .false.
123 !> Which TRAC method is used
124 integer, public, protected :: rmhd_trac_type=1
125 !> Distance between two adjacent traced magnetic field lines (in finest cell size)
126 integer, public, protected :: rmhd_trac_finegrid=4
127 !> Whether divB cleaning sources are added splitting from fluid solver
128 logical, public, protected :: source_split_divb = .false.
129 !> Whether plasma is partially ionized
130 logical, public, protected :: rmhd_partial_ionization = .false.
131 !> Whether CAK radiation line force is activated
132 logical, public, protected :: rmhd_cak_force = .false.
133 !> MHD fourth order
134 logical, public, protected :: rmhd_4th_order = .false.
135 !> whether split off equilibrium density
136 logical, public :: has_equi_rho0 = .false.
137 !> whether split off equilibrium thermal pressure
138 logical, public :: has_equi_pe0 = .false.
139 logical, public :: rmhd_equi_thermal = .false.
140 !> whether dump full variables (when splitting is used) in a separate dat file
141 logical, public, protected :: rmhd_dump_full_vars = .false.
142 !> Whether divB is computed with a fourth order approximation
143 integer, public, protected :: rmhd_divb_nth = 1
144 !> Use a compact way to add resistivity
145 logical :: compactres = .false.
146 !> Add divB wave in Roe solver
147 logical, public :: divbwave = .true.
148 !> clean initial divB
149 logical, public :: clean_initial_divb = .false.
150 !> Formalism to treat radiation
151 character(len=8), public :: rmhd_radiation_formalism = 'fld'
152 !> In the case of no rmhd_energy, how to compute pressure
153 character(len=8), public :: rmhd_pressure = 'Trad'
154 !> Treat radiation fld_Rad_force
155 logical, public, protected :: rmhd_radiation_force = .true.
156 !> Treat radiation-gas energy interaction
157 logical, public, protected :: rmhd_energy_interact = .true.
158 !> Treat radiation energy diffusion
159 logical, public, protected :: rmhd_radiation_diffusion = .true.
160 !> Treat radiation advection
161 logical, public, protected :: rmhd_radiation_advection = .true.
162 !> Do a running mean over the radiation pressure when determining dt
163 logical, protected :: radio_acoustic_filter = .false.
164 integer, protected :: size_ra_filter = 1
165 !> kb/(m_p mu)* 1/a_rad**4,
166 double precision, public :: kbmpmua4
167 !> Use the speed of light to calculate the timestep, usefull for debugging
168 logical :: dt_c = .false.
169 ! remove the below flag and assume default value = .false.
170 ! when eq state properly implemented everywhere
171 ! and not anymore through units
172 logical, public, protected :: eq_state_units = .true.
173 !> To control divB=0 fix for boundary
174 logical, public, protected :: boundary_divbfix(2*^nd)=.true.
175 !> B0 field is force-free
176 logical, public, protected :: b0field_forcefree=.true.
177 !> Whether an total energy equation is used
178 logical :: total_energy = .true.
179 !> Whether an internal or hydrodynamic energy equation is used
180 logical, public :: partial_energy = .false.
181 !> Whether gravity work is included in energy equation
182 logical :: gravity_energy
183 !> gravity work is calculated use density times velocity or conservative momentum
184 logical :: gravity_rhov = .false.
185 !> Method type to clean divergence of B
186 character(len=std_len), public, protected :: typedivbfix = 'linde'
187 !> Method type of constrained transport
188 character(len=std_len), public, protected :: type_ct = 'uct_contact'
189 !> Update all equations due to divB cleaning
190 character(len=std_len) :: typedivbdiff = 'all'
191 !> type of fluid for thermal conduction
192 type(tc_fluid), public, allocatable :: tc_fl
193 !> type of fluid for thermal emission synthesis
194 type(te_fluid), public, allocatable :: te_fl_rmhd
195
196 procedure(sub_convert), pointer :: rmhd_to_primitive => null()
197 procedure(sub_convert), pointer :: rmhd_to_conserved => null()
198 procedure(sub_small_values), pointer :: rmhd_handle_small_values => null()
199 procedure(sub_get_pthermal), pointer :: rmhd_get_pthermal => null()
200 procedure(sub_get_pthermal), pointer :: rmhd_get_rfactor => null()
201 procedure(sub_get_pthermal), pointer :: rmhd_get_temperature=> null()
202 ! Public methods
203 public :: rmhd_phys_init
204 public :: rmhd_get_pthermal
205 public :: rmhd_get_temperature
206 public :: rmhd_get_v
207 public :: rmhd_get_rho
208 public :: rmhd_to_conserved
209 public :: rmhd_to_primitive
210 public :: rmhd_e_to_ei
211 public :: rmhd_ei_to_e
212 public :: rmhd_face_to_center
213 public :: get_divb
214 public :: get_current
215 public :: get_normalized_divb
217 public :: rmhd_mag_en_all
218 {^nooned
220 }
221 public :: rmhd_get_pradiation
223 public :: rmhd_get_tgas
224 public :: rmhd_get_trad
225 public :: rmhd_set_mg_bounds
226
227contains
228
229 !> Read this module"s parameters from a file
230 subroutine rmhd_read_params(files)
232 use mod_particles, only: particles_eta, particles_etah
233 character(len=*), intent(in) :: files(:)
234 integer :: n
235
236 namelist /rmhd_list/ rmhd_energy, rmhd_n_tracer, rmhd_gamma, rmhd_adiab,&
240 typedivbdiff, type_ct, compactres, divbwave, he_abundance,&
243 particles_eta, particles_etah,has_equi_rho0, has_equi_pe0,rmhd_equi_thermal,&
249 rmhd_radiation_advection, radio_acoustic_filter, size_ra_filter, dt_c
250
251 do n = 1, size(files)
252 open(unitpar, file=trim(files(n)), status="old")
253 read(unitpar, rmhd_list, end=111)
254111 close(unitpar)
255 end do
256
257 end subroutine rmhd_read_params
258
259 !> Write this module's parameters to a snapsoht
260 subroutine rmhd_write_info(fh)
262 integer, intent(in) :: fh
263 integer :: er
264 integer, parameter :: n_par = 1
265 double precision :: values(n_par)
266 integer, dimension(MPI_STATUS_SIZE) :: st
267 character(len=name_len) :: names(n_par)
268
269 call mpi_file_write(fh, n_par, 1, mpi_integer, st, er)
270
271 names(1) = "gamma"
272 values(1) = rmhd_gamma
273 call mpi_file_write(fh, values, n_par, mpi_double_precision, st, er)
274 call mpi_file_write(fh, names, n_par * name_len, mpi_character, st, er)
275 end subroutine rmhd_write_info
276
277 subroutine rmhd_phys_init()
281 use mod_gravity, only: gravity_init
282 use mod_particles, only: particles_init, particles_eta, particles_etah
283 use mod_fld
284 use mod_afld
287 use mod_cak_force, only: cak_init
290 {^nooned
292 }
293
294 integer :: itr, idir
295
296 call rmhd_read_params(par_files)
297
298 if(.not.eq_state_units) then
301 if(mype==0) write(*,*) 'WARNING: set rmhd_partial_ionization=F when eq_state_units=F'
302 end if
303 end if
304
307 if(mype==0) write(*,*) 'WARNING: turn off parabolic TC when using hyperbolic TC'
308 end if
309
310 physics_type = "rmhd"
311 phys_energy=rmhd_energy
314 phys_partial_ionization=rmhd_partial_ionization
315
316 phys_gamma = rmhd_gamma
318
319 if(rmhd_energy) then
320 partial_energy=.false.
321 total_energy=.true.
322 else
323 total_energy=.false.
324 end if
325 phys_total_energy=total_energy
326 if(rmhd_energy) then
327 gravity_energy=.true.
328 if(has_equi_rho0) then
329 gravity_rhov=.true.
330 end if
331 else
332 gravity_energy=.false.
333 end if
334
335 {^ifoned
336 if(rmhd_trac .and. rmhd_trac_type .gt. 2) then
338 if(mype==0) write(*,*) 'WARNING: reset rmhd_trac_type=1 for 1D simulation'
339 end if
340 }
341 if(rmhd_trac .and. rmhd_trac_type .le. 4) then
342 rmhd_trac_mask=bigdouble
343 if(mype==0) write(*,*) 'WARNING: set rmhd_trac_mask==bigdouble for global TRAC method'
344 end if
346
347 ! set default gamma for polytropic/isothermal process
349 if(ndim==1) typedivbfix='none'
350 select case (typedivbfix)
351 case ('none')
352 type_divb = divb_none
353 {^nooned
354 case ('multigrid')
355 type_divb = divb_multigrid
356 use_multigrid = .true.
357 mg%operator_type = mg_laplacian
358 phys_global_source_after => rmhd_clean_divb_multigrid
359 }
360 case ('glm')
361 rmhd_glm = .true.
362 need_global_cmax = .true.
363 type_divb = divb_glm
364 case ('powel', 'powell')
365 type_divb = divb_powel
366 case ('janhunen')
367 type_divb = divb_janhunen
368 case ('linde')
369 type_divb = divb_linde
370 case ('lindejanhunen')
371 type_divb = divb_lindejanhunen
372 case ('lindepowel')
373 type_divb = divb_lindepowel
374 case ('lindeglm')
375 rmhd_glm = .true.
376 need_global_cmax = .true.
377 type_divb = divb_lindeglm
378 case ('ct')
379 type_divb = divb_ct
380 stagger_grid = .true.
381 case default
382 call mpistop('Unknown divB fix')
383 end select
384
385 allocate(start_indices(number_species),stop_indices(number_species))
386 ! set the index of the first flux variable for species 1
387 start_indices(1)=1
388 ! Determine flux variables
389 rho_ = var_set_rho()
390
391 allocate(mom(ndir))
392 mom(:) = var_set_momentum(ndir)
393 m^c_=mom(^c);
394
395 ! Set index of energy variable
396 if (rmhd_energy) then
397 nwwave = 8
398 e_ = var_set_energy() ! energy density
399 p_ = e_ ! gas pressure
400 else
401 nwwave = 7
402 e_ = -1
403 p_ = -1
404 end if
405
406 allocate(mag(ndir))
407 mag(:) = var_set_bfield(ndir)
408 b^c_=mag(^c);
409
410 if (rmhd_glm) then
411 psi_ = var_set_fluxvar('psi', 'psi', need_bc=.false.)
412 else
413 psi_ = -1
414 end if
415
416 !> set radiation energy
417 r_e = var_set_radiation_energy()
418
420 ! hyperbolic thermal conduction flux q
421 q_ = var_set_q()
422 need_global_cmax=.true.
423 else
424 q_=-1
425 end if
426
427 allocate(tracer(rmhd_n_tracer))
428 ! Set starting index of tracers
429 do itr = 1, rmhd_n_tracer
430 tracer(itr) = var_set_fluxvar("trc", "trp", itr, need_bc=.false.)
431 end do
432
433 !if(rmhd_hyperbolic_thermal_conduction) then
434 ! ! hyperbolic thermal conduction flux q
435 ! q_ = var_set_auxvar('q','q')
436 ! need_global_cmax=.true.
437 !else
438 ! q_=-1
439 !end if
440
441 ! set temperature as an auxiliary variable to get ionization degree
443 te_ = var_set_auxvar('Te','Te')
444 else
445 te_ = -1
446 end if
447
448 ! set number of variables which need update ghostcells
449 nwgc=nwflux+nwaux
450
451 ! set the index of the last flux variable for species 1
452 stop_indices(1)=nwflux
453
454 ! set cutoff temperature when using the TRAC method, as well as an auxiliary weight
455 tweight_ = -1
456 if(rmhd_trac) then
457 tcoff_ = var_set_wextra()
458 iw_tcoff=tcoff_
459 if(rmhd_trac_type .ge. 3) then
460 tweight_ = var_set_wextra()
461 endif
462 else
463 tcoff_ = -1
464 end if
465
466 ! set indices of equi vars and update number_equi_vars
468 if(has_equi_rho0) then
471 iw_equi_rho = equi_rho0_
472 endif
473 if(has_equi_pe0) then
476 iw_equi_p = equi_pe0_
477 endif
478 ! determine number of stagger variables
479 nws=ndim
480
481 nvector = 2 ! No. vector vars
482 allocate(iw_vector(nvector))
483 iw_vector(1) = mom(1) - 1 ! TODO: why like this?
484 iw_vector(2) = mag(1) - 1 ! TODO: why like this?
485
486 ! Check whether custom flux types have been defined
487 if (.not. allocated(flux_type)) then
488 allocate(flux_type(ndir, nwflux))
489 flux_type = flux_default
490 else if (any(shape(flux_type) /= [ndir, nwflux])) then
491 call mpistop("phys_check error: flux_type has wrong shape")
492 end if
493
494 if(nwflux>mag(ndir)) then
495 ! for flux of tracers, using hll flux
496 flux_type(:,mag(ndir)+1:nwflux)=flux_hll
497 end if
498
499 if(ndim>1) then
500 if(rmhd_glm) then
501 flux_type(:,psi_)=flux_special
502 do idir=1,ndir
503 flux_type(idir,mag(idir))=flux_special
504 end do
505 else
506 do idir=1,ndir
507 flux_type(idir,mag(idir))=flux_tvdlf
508 end do
509 end if
510 end if
511
512 phys_get_rho => rmhd_get_rho
513 phys_get_dt => rmhd_get_dt
514 phys_get_cmax => rmhd_get_cmax_origin
515 phys_get_a2max => rmhd_get_a2max
516 phys_get_tcutoff => rmhd_get_tcutoff
517 phys_get_h_speed => rmhd_get_h_speed
518 if(has_equi_rho0) then
519 phys_get_cbounds => rmhd_get_cbounds_split_rho
520 else
521 phys_get_cbounds => rmhd_get_cbounds
522 end if
523 if(has_equi_rho0) then
524 phys_to_primitive => rmhd_to_primitive_split_rho
525 rmhd_to_primitive => rmhd_to_primitive_split_rho
526 phys_to_conserved => rmhd_to_conserved_split_rho
527 rmhd_to_conserved => rmhd_to_conserved_split_rho
528 else
529 phys_to_primitive => rmhd_to_primitive_origin
530 rmhd_to_primitive => rmhd_to_primitive_origin
531 phys_to_conserved => rmhd_to_conserved_origin
532 rmhd_to_conserved => rmhd_to_conserved_origin
533 end if
534 if(b0field.or.has_equi_rho0.or.has_equi_pe0) then
535 phys_get_flux => rmhd_get_flux_split
536 else
537 phys_get_flux => rmhd_get_flux
538 end if
539 phys_get_v => rmhd_get_v
540 if(b0field.or.has_equi_rho0) then
541 phys_add_source_geom => rmhd_add_source_geom_split
542 else
543 phys_add_source_geom => rmhd_add_source_geom
544 end if
545 phys_add_source => rmhd_add_source
546 phys_check_params => rmhd_check_params
547 phys_write_info => rmhd_write_info
548
549 phys_handle_small_values => rmhd_handle_small_values_origin
550 rmhd_handle_small_values => rmhd_handle_small_values_origin
551 phys_check_w => rmhd_check_w_origin
552
553 phys_set_mg_bounds => rmhd_set_mg_bounds
554 phys_get_trad => rmhd_get_trad
555 phys_get_tgas => rmhd_get_tgas
556
557 phys_get_pthermal => rmhd_get_pthermal_origin
558 rmhd_get_pthermal => rmhd_get_pthermal_origin
559
560 if(number_equi_vars>0) then
561 phys_set_equi_vars => set_equi_vars_grid
562 endif
563
564 if(type_divb==divb_glm) then
565 phys_modify_wlr => rmhd_modify_wlr
566 end if
567
568 ! choose Rfactor in ideal gas law
570 rmhd_get_rfactor=>rfactor_from_temperature_ionization
571 phys_update_temperature => rmhd_update_temperature
572 else if(associated(usr_rfactor)) then
573 rmhd_get_rfactor=>usr_rfactor
574 else
575 rmhd_get_rfactor=>rfactor_from_constant_ionization
576 end if
577
579 rmhd_get_temperature => rmhd_get_temperature_from_te
580 else
581 if(has_equi_pe0 .and. has_equi_rho0) then
582 rmhd_get_temperature => rmhd_get_temperature_from_etot_with_equi
583 else
584 rmhd_get_temperature => rmhd_get_temperature_from_etot
585 end if
586 end if
587
588 ! if using ct stagger grid, boundary divb=0 is not done here
589 if(stagger_grid) then
590 select case(type_ct)
591 case('average')
592 transverse_ghost_cells = 1
593 phys_get_ct_velocity => rmhd_get_ct_velocity_average
594 phys_update_faces => rmhd_update_faces_average
595 case('uct_contact')
596 transverse_ghost_cells = 1
597 phys_get_ct_velocity => rmhd_get_ct_velocity_contact
598 phys_update_faces => rmhd_update_faces_contact
599 case('uct_hll')
600 transverse_ghost_cells = 2
601 phys_get_ct_velocity => rmhd_get_ct_velocity_hll
602 phys_update_faces => rmhd_update_faces_hll
603 case default
604 call mpistop('choose average, uct_contact,or uct_hll for type_ct!')
605 end select
606 phys_face_to_center => rmhd_face_to_center
607 phys_modify_wlr => rmhd_modify_wlr
608 else if(ndim>1) then
609 phys_boundary_adjust => rmhd_boundary_adjust
610 end if
611
612 {^nooned
613 ! clean initial divb
614 if(clean_initial_divb) phys_clean_divb => rmhd_clean_divb_multigrid
615 }
616
617 ! derive units from basic units
618 call rmhd_physical_units()
619
620 !> Initiate radiation-closure module
621 select case(rmhd_radiation_formalism)
622 case('fld')
624 case('afld')
626 case default
627 call mpistop('Radiation formalism unknown')
628 end select
629
632 end if
633 if(.not. rmhd_energy .and. rmhd_thermal_conduction) then
634 call mpistop("thermal conduction needs rmhd_energy=T")
635 end if
637 call mpistop("hyperbolic thermal conduction needs rmhd_energy=T")
638 end if
639
640 ! initialize thermal conduction module
642 call sts_init()
644
645 allocate(tc_fl)
646 call tc_get_mhd_params(tc_fl,tc_params_read_rmhd)
647 call add_sts_method(rmhd_get_tc_dt_rmhd,rmhd_sts_set_source_tc_rmhd,e_,1,e_,1,.false.)
648 if(has_equi_pe0 .and. has_equi_rho0) then
649 tc_fl%get_temperature_from_conserved => rmhd_get_temperature_from_etot_with_equi
650 else
651 tc_fl%get_temperature_from_conserved => rmhd_get_temperature_from_etot
652 end if
653 if(has_equi_pe0 .and. has_equi_rho0) then
654 tc_fl%get_temperature_from_eint => rmhd_get_temperature_from_eint_with_equi
655 if(rmhd_equi_thermal) then
656 tc_fl%has_equi = .true.
657 tc_fl%get_temperature_equi => rmhd_get_temperature_equi
658 tc_fl%get_rho_equi => rmhd_get_rho_equi
659 else
660 tc_fl%has_equi = .false.
661 end if
662 else
663 tc_fl%get_temperature_from_eint => rmhd_get_temperature_from_eint
664 end if
666 call set_error_handling_to_head(rmhd_tc_handle_small_e)
667 tc_fl%get_rho => rmhd_get_rho
668 tc_fl%e_ = e_
669 tc_fl%Tcoff_ = tcoff_
670 end if
671
672 allocate(te_fl_rmhd)
673 te_fl_rmhd%get_rho=> rmhd_get_rho
674 te_fl_rmhd%get_pthermal=> rmhd_get_pthermal
675 te_fl_rmhd%get_var_Rfactor => rmhd_get_rfactor
676{^ifthreed
677 phys_te_images => rmhd_te_images
678}
679 ! Initialize viscosity module
680 if (rmhd_viscosity) call viscosity_init(phys_wider_stencil)
681
682 ! Initialize gravity module
683 if(rmhd_gravity) then
684 call gravity_init()
685 end if
686
687 ! Initialize particles module
688 if(rmhd_particles) then
689 call particles_init()
690 if (particles_eta < zero) particles_eta = rmhd_eta
691 if (particles_etah < zero) particles_eta = rmhd_etah
692 if(mype==0) then
693 write(*,*) '*****Using particles: with rmhd_eta, rmhd_etah :', rmhd_eta, rmhd_etah
694 write(*,*) '*****Using particles: particles_eta, particles_etah :', particles_eta, particles_etah
695 end if
696 end if
697
698 ! initialize ionization degree table
700
701 ! Initialize CAK radiation force module
703 end subroutine rmhd_phys_init
704
705{^ifthreed
706 subroutine rmhd_te_images
709
710 select case(convert_type)
711 case('EIvtiCCmpi','EIvtuCCmpi')
713 case('ESvtiCCmpi','ESvtuCCmpi')
715 case('SIvtiCCmpi','SIvtuCCmpi')
717 case('WIvtiCCmpi','WIvtuCCmpi')
719 case default
720 call mpistop("Error in synthesize emission: Unknown convert_type")
721 end select
722 end subroutine rmhd_te_images
723}
724
725!!start th cond
726 ! wrappers for STS functions in thermal_conductivity module
727 ! which take as argument the tc_fluid (defined in the physics module)
728 subroutine rmhd_sts_set_source_tc_rmhd(ixI^L,ixO^L,w,x,wres,fix_conserve_at_step,my_dt,igrid,nflux)
732 integer, intent(in) :: ixi^l, ixo^l, igrid, nflux
733 double precision, intent(in) :: x(ixi^s,1:ndim)
734 double precision, intent(inout) :: wres(ixi^s,1:nw), w(ixi^s,1:nw)
735 double precision, intent(in) :: my_dt
736 logical, intent(in) :: fix_conserve_at_step
737 call sts_set_source_tc_mhd(ixi^l,ixo^l,w,x,wres,fix_conserve_at_step,my_dt,igrid,nflux,tc_fl)
738 end subroutine rmhd_sts_set_source_tc_rmhd
739
740 function rmhd_get_tc_dt_rmhd(w,ixI^L,ixO^L,dx^D,x) result(dtnew)
741 !Check diffusion time limit dt < dx_i**2/((gamma-1)*tc_k_para_i/rho)
742 !where tc_k_para_i=tc_k_para*B_i**2/B**2
743 !and T=p/rho
746 integer, intent(in) :: ixi^l, ixo^l
747 double precision, intent(in) :: dx^d, x(ixi^s,1:ndim)
748 double precision, intent(in) :: w(ixi^s,1:nw)
749 double precision :: dtnew
750
751 dtnew=get_tc_dt_mhd(w,ixi^l,ixo^l,dx^d,x,tc_fl)
752 end function rmhd_get_tc_dt_rmhd
753
754 subroutine rmhd_tc_handle_small_e(w, x, ixI^L, ixO^L, step)
756 integer, intent(in) :: ixi^l,ixo^l
757 double precision, intent(inout) :: w(ixi^s,1:nw)
758 double precision, intent(in) :: x(ixi^s,1:ndim)
759 integer, intent(in) :: step
760 character(len=140) :: error_msg
761
762 write(error_msg,"(a,i3)") "Thermal conduction step ", step
763 call rmhd_handle_small_ei(w,x,ixi^l,ixo^l,e_,error_msg)
764 end subroutine rmhd_tc_handle_small_e
765
766 ! fill in tc_fluid fields from namelist
767 subroutine tc_params_read_rmhd(fl)
769 type(tc_fluid), intent(inout) :: fl
770 double precision :: tc_k_para=0d0
771 double precision :: tc_k_perp=0d0
772 integer :: n
773 ! list parameters
774 logical :: tc_perpendicular=.false.
775 logical :: tc_saturate=.false.
776 character(len=std_len) :: tc_slope_limiter="MC"
777
778 namelist /tc_list/ tc_perpendicular, tc_saturate, tc_slope_limiter, tc_k_para, tc_k_perp
779
780 do n = 1, size(par_files)
781 open(unitpar, file=trim(par_files(n)), status="old")
782 read(unitpar, tc_list, end=111)
783111 close(unitpar)
784 end do
785
786 fl%tc_perpendicular = tc_perpendicular
787 fl%tc_saturate = tc_saturate
788 fl%tc_k_para = tc_k_para
789 fl%tc_k_perp = tc_k_perp
790 select case(tc_slope_limiter)
791 case ('no','none')
792 fl%tc_slope_limiter = 0
793 case ('MC')
794 ! montonized central limiter Woodward and Collela limiter (eq.3.51h), a factor of 2 is pulled out
795 fl%tc_slope_limiter = 1
796 case('minmod')
797 ! minmod limiter
798 fl%tc_slope_limiter = 2
799 case ('superbee')
800 ! Roes superbee limiter (eq.3.51i)
801 fl%tc_slope_limiter = 3
802 case ('koren')
803 ! Barry Koren Right variant
804 fl%tc_slope_limiter = 4
805 case default
806 call mpistop("Unknown tc_slope_limiter, choose MC, minmod")
807 end select
808 end subroutine tc_params_read_rmhd
809!!end th cond
810
811 !> sets the equilibrium variables
812 subroutine set_equi_vars_grid_faces(igrid,x,ixI^L,ixO^L)
815 integer, intent(in) :: igrid, ixi^l, ixo^l
816 double precision, intent(in) :: x(ixi^s,1:ndim)
817 double precision :: delx(ixi^s,1:ndim)
818 double precision :: xc(ixi^s,1:ndim),xshift^d
819 integer :: idims, ixc^l, hxo^l, ix, idims2
820
821 if(slab_uniform)then
822 ^d&delx(ixi^s,^d)=rnode(rpdx^d_,igrid)\
823 else
824 ! for all non-cartesian and stretched cartesian coordinates
825 delx(ixi^s,1:ndim)=ps(igrid)%dx(ixi^s,1:ndim)
826 endif
827
828 do idims=1,ndim
829 hxo^l=ixo^l-kr(idims,^d);
830 if(stagger_grid) then
831 ! ct needs all transverse cells
832 ixcmax^d=ixomax^d+nghostcells-nghostcells*kr(idims,^d); ixcmin^d=hxomin^d-nghostcells+nghostcells*kr(idims,^d);
833 else
834 ! ixC is centered index in the idims direction from ixOmin-1/2 to ixOmax+1/2
835 ixcmax^d=ixomax^d; ixcmin^d=hxomin^d;
836 end if
837 ! always xshift=0 or 1/2
838 xshift^d=half*(one-kr(^d,idims));
839 do idims2=1,ndim
840 select case(idims2)
841 {case(^d)
842 do ix = ixc^lim^d
843 ! xshift=half: this is the cell center coordinate
844 ! xshift=0: this is the cell edge i+1/2 coordinate
845 xc(ix^d%ixC^s,^d)=x(ix^d%ixC^s,^d)+(half-xshift^d)*delx(ix^d%ixC^s,^d)
846 end do\}
847 end select
848 end do
849 call usr_set_equi_vars(ixi^l,ixc^l,xc,ps(igrid)%equi_vars(ixi^s,1:number_equi_vars,idims))
850 end do
851 end subroutine set_equi_vars_grid_faces
852
853 !> sets the equilibrium variables
854 subroutine set_equi_vars_grid(igrid)
857 integer, intent(in) :: igrid
858
859 !values at the center
860 call usr_set_equi_vars(ixg^ll,ixg^ll,ps(igrid)%x,ps(igrid)%equi_vars(ixg^t,1:number_equi_vars,0))
861
862 !values at the interfaces
863 call set_equi_vars_grid_faces(igrid,ps(igrid)%x,ixg^ll,ixm^ll)
864 end subroutine set_equi_vars_grid
865
866 ! w, wnew conserved, add splitted variables back to wnew
867 function convert_vars_splitting(ixI^L,ixO^L, w, x, nwc) result(wnew)
869 integer, intent(in) :: ixi^l,ixo^l, nwc
870 double precision, intent(in) :: w(ixi^s, 1:nw)
871 double precision, intent(in) :: x(ixi^s,1:ndim)
872 double precision :: wnew(ixo^s, 1:nwc)
873
874 if(has_equi_rho0) then
875 wnew(ixo^s,rho_)=w(ixo^s,rho_)+block%equi_vars(ixo^s,equi_rho0_,0)
876 else
877 wnew(ixo^s,rho_)=w(ixo^s,rho_)
878 endif
879 wnew(ixo^s,mom(:))=w(ixo^s,mom(:))
880
881 if (b0field) then
882 ! add background magnetic field B0 to B
883 wnew(ixo^s,mag(1:ndir))=w(ixo^s,mag(1:ndir))+block%B0(ixo^s,1:ndir,0)
884 else
885 wnew(ixo^s,mag(1:ndir))=w(ixo^s,mag(1:ndir))
886 end if
887
888 if(rmhd_energy) then
889 wnew(ixo^s,e_)=w(ixo^s,e_)
890 if(has_equi_pe0) then
891 wnew(ixo^s,e_)=wnew(ixo^s,e_)+block%equi_vars(ixo^s,equi_pe0_,0)*inv_gamma_1
892 end if
893 if(b0field .and. total_energy) then
894 wnew(ixo^s,e_)=wnew(ixo^s,e_)+0.5d0*sum(block%B0(ixo^s,:,0)**2,dim=ndim+1) &
895 + sum(w(ixo^s,mag(:))*block%B0(ixo^s,:,0),dim=ndim+1)
896 end if
897 end if
898 end function convert_vars_splitting
899
900 subroutine rmhd_check_params
904
905 ! after user parameter setting
906 gamma_1=rmhd_gamma-1.d0
907 if (.not. rmhd_energy) then
908 if (rmhd_gamma <= 0.0d0) call mpistop ("Error: rmhd_gamma <= 0")
909 if (rmhd_adiab < 0.0d0) call mpistop ("Error: rmhd_adiab < 0")
911 else
912 if (rmhd_gamma <= 0.0d0 .or. rmhd_gamma == 1.0d0) &
913 call mpistop ("Error: rmhd_gamma <= 0 or rmhd_gamma == 1")
914 inv_gamma_1=1.d0/gamma_1
915 small_e = small_pressure * inv_gamma_1
916 end if
917
919
920 if (number_equi_vars > 0 .and. .not. associated(usr_set_equi_vars)) then
921 call mpistop("usr_set_equi_vars has to be implemented in the user file")
922 endif
923 if(convert .or. autoconvert) then
924 if(convert_type .eq. 'dat_generic_mpi') then
925 if(rmhd_dump_full_vars) then
926 if(mype .eq. 0) print*, " add conversion method: split -> full "
927 call add_convert_method(convert_vars_splitting, nw, cons_wnames, "new")
928 endif
929 endif
930 endif
931
933 end subroutine rmhd_check_params
934
935 !> Set the boundaries for the diffusion of E
940 integer :: ib
941
942 ! Set boundary conditions for the multigrid solver
943 do ib = 1, 2*ndim
944 select case (typeboundary(r_e, ib))
945 case (bc_symm)
946 ! d/dx u = 0
947 mg%bc(ib, mg_iphi)%bc_type = mg_bc_neumann
948 mg%bc(ib, mg_iphi)%bc_value = 0.0_dp
949 case (bc_asymm)
950 ! u = 0
951 mg%bc(ib, mg_iphi)%bc_type = mg_bc_dirichlet
952 mg%bc(ib, mg_iphi)%bc_value = 0.0_dp
953 case (bc_cont)
954 ! d/dx u = 0
955 ! mg%bc(iB, mg_iphi)%bc_type = mg_bc_continuous
956 mg%bc(ib, mg_iphi)%bc_type = mg_bc_neumann
957 mg%bc(ib, mg_iphi)%bc_value = 0.0_dp
958 case (bc_periodic)
959 ! Nothing to do here
960 case (bc_noinflow)
961 call usr_special_mg_bc(ib)
962 case (bc_special)
963 call usr_special_mg_bc(ib)
964 case default
965 call mpistop("divE_multigrid warning: unknown b.c. ")
966 end select
967 end do
968 end subroutine rmhd_set_mg_bounds
969
970 subroutine rmhd_physical_units()
972 double precision :: mp,kb,miu0,c_lightspeed
973 double precision :: a,b
974
975 ! Derive scaling units
976 if(si_unit) then
977 mp=mp_si
978 kb=kb_si
979 miu0=miu0_si
980 c_lightspeed=c_si
981 else
982 mp=mp_cgs
983 kb=kb_cgs
984 miu0=4.d0*dpi ! G^2 cm^2 dyne^-1
985 c_lightspeed=const_c
986 end if
987 if(eq_state_units) then
988 a=1d0+4d0*he_abundance
991 else
992 b=2d0+3d0*he_abundance
993 end if
994 rr=1d0
995 else
996 a=1d0
997 b=1d0
998 rr=(1d0+h_ion_fr+he_abundance*(he_ion_fr*(he_ion_fr2+1d0)+1d0))/(1d0+4d0*he_abundance)
999 end if
1000 if(unit_density/=1.d0 .or. unit_numberdensity/=1.d0) then
1001 if(unit_density/=1.d0) then
1003 else if(unit_numberdensity/=1.d0) then
1005 end if
1006 if(unit_temperature/=1.d0) then
1010 if(unit_length/=1.d0) then
1012 else if(unit_time/=1.d0) then
1014 end if
1015 else if(unit_magneticfield/=1.d0) then
1019 if(unit_length/=1.d0) then
1021 else if(unit_time/=1.d0) then
1023 end if
1024 else if(unit_pressure/=1.d0) then
1028 if(unit_length/=1.d0) then
1030 else if(unit_time/=1.d0) then
1032 end if
1033 else if(unit_velocity/=1.d0) then
1037 if(unit_length/=1.d0) then
1039 else if(unit_time/=1.d0) then
1041 end if
1042 else if(unit_time/=1.d0) then
1047 end if
1048 else if(unit_temperature/=1.d0) then
1049 ! units of temperature and velocity are dependent
1050 if(unit_magneticfield/=1.d0) then
1055 if(unit_length/=1.d0) then
1057 else if(unit_time/=1.d0) then
1059 end if
1060 else if(unit_pressure/=1.d0) then
1065 if(unit_length/=1.d0) then
1067 else if(unit_time/=1.d0) then
1069 end if
1070 end if
1071 else if(unit_magneticfield/=1.d0) then
1072 ! units of magnetic field and pressure are dependent
1073 if(unit_velocity/=1.d0) then
1078 if(unit_length/=1.d0) then
1080 else if(unit_time/=1.d0) then
1082 end if
1083 else if(unit_time/=0.d0) then
1089 end if
1090 else if(unit_pressure/=1.d0) then
1091 if(unit_velocity/=1.d0) then
1096 if(unit_length/=1.d0) then
1098 else if(unit_time/=1.d0) then
1100 end if
1101 else if(unit_time/=0.d0) then
1107 end if
1108 end if
1109 ! Additional units needed for the particles
1110 c_norm=c_lightspeed/unit_velocity
1112 if (.not. si_unit) unit_charge = unit_charge*const_c
1114
1115 !> Units for radiative flux and opacity
1118 end subroutine rmhd_physical_units
1119
1120 subroutine rmhd_check_w_origin(primitive,ixI^L,ixO^L,w,flag)
1122 logical, intent(in) :: primitive
1123 integer, intent(in) :: ixi^l, ixo^l
1124 double precision, intent(in) :: w(ixi^s,nw)
1125 logical, intent(inout) :: flag(ixi^s,1:nw)
1126 double precision :: tmp
1127 integer :: ix^d
1128
1129 flag=.false.
1130 {do ix^db=ixomin^db,ixomax^db\}
1131 if(has_equi_rho0) then
1132 tmp=w(ix^d,rho_)+block%equi_vars(ix^d,equi_rho0_,0)
1133 else
1134 tmp=w(ix^d,rho_)
1135 end if
1136 if(tmp<small_density) flag(ix^d,rho_) = .true.
1137 if(primitive) then
1138 if(has_equi_pe0) then
1139 if(w(ix^d,p_)+block%equi_vars(ix^d,equi_pe0_,0)<small_pressure) flag(ix^d,e_) = .true.
1140 else
1141 if(w(ix^d,p_)<small_pressure) flag(ix^d,e_) = .true.
1142 end if
1143 else
1144 tmp=w(ix^d,e_)-half*((^c&w(ix^d,m^c_)**2+)/tmp+(^c&w(ix^d,b^c_)**2+))
1145 if(has_equi_pe0) then
1146 if(tmp+block%equi_vars(ix^d,equi_pe0_,0)*inv_gamma_1<small_e) flag(ix^d,e_) = .true.
1147 else
1148 if(tmp<small_e) flag(ix^d,e_) = .true.
1149 end if
1150 end if
1151 if(w(ix^d,r_e)<small_r_e) flag(ix^d,r_e) = .true.
1152 {end do\}
1153 end subroutine rmhd_check_w_origin
1154
1155 !> Transform primitive variables into conservative ones
1156 subroutine rmhd_to_conserved_origin(ixI^L,ixO^L,w,x)
1158 integer, intent(in) :: ixi^l, ixo^l
1159 double precision, intent(inout) :: w(ixi^s, nw)
1160 double precision, intent(in) :: x(ixi^s, 1:ndim)
1161 integer :: ix^d
1162
1163 {do ix^db=ixomin^db,ixomax^db\}
1164 ! Calculate total energy from pressure, kinetic and magnetic energy
1165 w(ix^d,e_)=w(ix^d,p_)*inv_gamma_1&
1166 +half*((^c&w(ix^d,m^c_)**2+)*w(ix^d,rho_)&
1167 +(^c&w(ix^d,b^c_)**2+))
1168 ! Convert velocity to momentum
1169 ^c&w(ix^d,m^c_)=w(ix^d,rho_)*w(ix^d,m^c_)\
1170 {end do\}
1171 end subroutine rmhd_to_conserved_origin
1172
1173 !> Transform primitive variables into conservative ones
1174 subroutine rmhd_to_conserved_split_rho(ixI^L,ixO^L,w,x)
1176 integer, intent(in) :: ixi^l, ixo^l
1177 double precision, intent(inout) :: w(ixi^s, nw)
1178 double precision, intent(in) :: x(ixi^s, 1:ndim)
1179 double precision :: rho
1180 integer :: ix^d
1181
1182 {do ix^db=ixomin^db,ixomax^db\}
1183 rho=w(ix^d,rho_)+block%equi_vars(ix^d,equi_rho0_,b0i)
1184 ! Calculate total energy from pressure, kinetic and magnetic energy
1185 w(ix^d,e_)=w(ix^d,p_)*inv_gamma_1&
1186 +half*((^c&w(ix^d,m^c_)**2+)*rho&
1187 +(^c&w(ix^d,b^c_)**2+))
1188 ! Convert velocity to momentum
1189 ^c&w(ix^d,m^c_)=rho*w(ix^d,m^c_)\
1190 {end do\}
1191 end subroutine rmhd_to_conserved_split_rho
1192
1193 !> Transform conservative variables into primitive ones
1194 subroutine rmhd_to_primitive_origin(ixI^L,ixO^L,w,x)
1196 integer, intent(in) :: ixi^l, ixo^l
1197 double precision, intent(inout) :: w(ixi^s, nw)
1198 double precision, intent(in) :: x(ixi^s, 1:ndim)
1199 double precision :: inv_rho
1200 integer :: ix^d
1201
1202 if (fix_small_values) then
1203 ! fix small values preventing NaN numbers in the following converting
1204 call rmhd_handle_small_values(.false., w, x, ixi^l, ixo^l, 'rmhd_to_primitive_origin')
1205 end if
1206
1207 {do ix^db=ixomin^db,ixomax^db\}
1208 inv_rho = 1.d0/w(ix^d,rho_)
1209 ! Convert momentum to velocity
1210 ^c&w(ix^d,m^c_)=w(ix^d,m^c_)*inv_rho\
1211 ! Calculate pressure = (gamma-1) * (e-ek-eb)
1212 w(ix^d,p_)=gamma_1*(w(ix^d,e_)&
1213 -half*(w(ix^d,rho_)*(^c&w(ix^d,m^c_)**2+)&
1214 +(^c&w(ix^d,b^c_)**2+)))
1215 {end do\}
1216 end subroutine rmhd_to_primitive_origin
1217
1218 !> Transform conservative variables into primitive ones
1219 subroutine rmhd_to_primitive_split_rho(ixI^L,ixO^L,w,x)
1221 integer, intent(in) :: ixi^l, ixo^l
1222 double precision, intent(inout) :: w(ixi^s, nw)
1223 double precision, intent(in) :: x(ixi^s, 1:ndim)
1224 double precision :: inv_rho
1225 integer :: ix^d
1226
1227 if (fix_small_values) then
1228 ! fix small values preventing NaN numbers in the following converting
1229 call rmhd_handle_small_values(.false., w, x, ixi^l, ixo^l, 'rmhd_to_primitive_split_rho')
1230 end if
1231
1232 {do ix^db=ixomin^db,ixomax^db\}
1233 inv_rho=1.d0/(w(ix^d,rho_)+block%equi_vars(ix^d,equi_rho0_,b0i))
1234 ! Convert momentum to velocity
1235 ^c&w(ix^d,m^c_)=w(ix^d,m^c_)*inv_rho\
1236 ! Calculate pressure = (gamma-1) * (e-ek-eb)
1237 w(ix^d,p_)=gamma_1*(w(ix^d,e_)&
1238 -half*((w(ix^d,rho_)+block%equi_vars(ix^d,equi_rho0_,b0i))*&
1239 (^c&w(ix^d,m^c_)**2+)+(^c&w(ix^d,b^c_)**2+)))
1240 {end do\}
1241 end subroutine rmhd_to_primitive_split_rho
1242
1243 !> Transform internal energy to total energy
1244 subroutine rmhd_ei_to_e(ixI^L,ixO^L,w,x)
1246 integer, intent(in) :: ixi^l, ixo^l
1247 double precision, intent(inout) :: w(ixi^s, nw)
1248 double precision, intent(in) :: x(ixi^s, 1:ndim)
1249
1250 integer :: ix^d
1251
1252 if(has_equi_rho0) then
1253 {do ix^db=ixomin^db,ixomax^db\}
1254 ! Calculate e = ei + ek + eb
1255 w(ix^d,e_)=w(ix^d,e_)&
1256 +half*((^c&w(ix^d,m^c_)**2+)/&
1257 (w(ix^d,rho_)+block%equi_vars(ix^d,equi_rho0_,0))&
1258 +(^c&w(ix^d,b^c_)**2+))
1259 {end do\}
1260 else
1261 {do ix^db=ixomin^db,ixomax^db\}
1262 ! Calculate e = ei + ek + eb
1263 w(ix^d,e_)=w(ix^d,e_)&
1264 +half*((^c&w(ix^d,m^c_)**2+)/w(ix^d,rho_)&
1265 +(^c&w(ix^d,b^c_)**2+))
1266 {end do\}
1267 end if
1268 end subroutine rmhd_ei_to_e
1269
1270 !> Transform total energy to internal energy
1271 subroutine rmhd_e_to_ei(ixI^L,ixO^L,w,x)
1273 integer, intent(in) :: ixi^l, ixo^l
1274 double precision, intent(inout) :: w(ixi^s, nw)
1275 double precision, intent(in) :: x(ixi^s, 1:ndim)
1276
1277 integer :: ix^d
1278
1279 if(has_equi_rho0) then
1280 {do ix^db=ixomin^db,ixomax^db\}
1281 ! Calculate ei = e - ek - eb
1282 w(ix^d,e_)=w(ix^d,e_)&
1283 -half*((^c&w(ix^d,m^c_)**2+)/&
1284 (w(ix^d,rho_)+block%equi_vars(ix^d,equi_rho0_,0))&
1285 +(^c&w(ix^d,b^c_)**2+))
1286 {end do\}
1287 else
1288 {do ix^db=ixomin^db,ixomax^db\}
1289 ! Calculate ei = e - ek - eb
1290 w(ix^d,e_)=w(ix^d,e_)&
1291 -half*((^c&w(ix^d,m^c_)**2+)/w(ix^d,rho_)&
1292 +(^c&w(ix^d,b^c_)**2+))
1293 {end do\}
1294 end if
1295
1296 if(fix_small_values) then
1297 call rmhd_handle_small_ei(w,x,ixi^l,ixi^l,e_,'rmhd_e_to_ei')
1298 end if
1299 end subroutine rmhd_e_to_ei
1300
1301 subroutine rmhd_handle_small_values_origin(primitive, w, x, ixI^L, ixO^L, subname)
1304 logical, intent(in) :: primitive
1305 integer, intent(in) :: ixi^l,ixo^l
1306 double precision, intent(inout) :: w(ixi^s,1:nw)
1307 double precision, intent(in) :: x(ixi^s,1:ndim)
1308 character(len=*), intent(in) :: subname
1309 double precision :: rho
1310 integer :: idir, ix^d
1311 logical :: flag(ixi^s,1:nw)
1312
1313 call phys_check_w(primitive, ixi^l, ixi^l, w, flag)
1314 if(any(flag)) then
1315 select case (small_values_method)
1316 case ("replace")
1317 {do ix^db=ixomin^db,ixomax^db\}
1318 if(has_equi_rho0) then
1319 rho=w(ix^d,rho_)+block%equi_vars(ix^d,equi_rho0_,0)
1320 if(flag(ix^d,rho_)) w(ix^d,rho_)=small_density-block%equi_vars(ix^d,equi_rho0_,0)
1321 else
1322 rho=w(ix^d,rho_)
1323 if(flag(ix^d,rho_)) w(ix^d,rho_)=small_density
1324 end if
1325 {
1326 if(small_values_fix_iw(m^c_)) then
1327 if(flag({ix^d},rho_)) w({ix^d},m^c_)=0.0d0
1328 end if
1329 \}
1330 if(primitive) then
1331 if(has_equi_pe0) then
1332 if(flag(ix^d,e_)) w(ix^d,p_)=small_pressure-block%equi_vars(ix^d,equi_pe0_,0)
1333 else
1334 if(flag(ix^d,e_)) w(ix^d,p_)=small_pressure
1335 end if
1336 else
1337 if(has_equi_pe0) then
1338 if(flag(ix^d,e_)) &
1339 w(ix^d,e_)=small_e+half*((^c&w(ix^d,m^c_)**2+)/rho+(^c&w(ix^d,b^c_)**2+))&
1340 -block%equi_vars(ix^d,equi_pe0_,0)*inv_gamma_1
1341 else
1342 if(flag(ix^d,e_)) &
1343 w(ix^d,e_)=small_e+half*((^c&w(ix^d,m^c_)**2+)/rho+(^c&w(ix^d,b^c_)**2+))
1344 end if
1345 end if
1346 if(flag(ix^d,r_e)) w(ix^d,r_e)=small_r_e
1347 {end do\}
1348 case ("average")
1349 ! do averaging of density
1350 call small_values_average(ixi^l, ixo^l, w, x, flag, rho_)
1351 if(primitive)then
1352 call small_values_average(ixi^l, ixo^l, w, x, flag, p_)
1353 else
1354 ! do averaging of internal energy
1355 {do ix^db=iximin^db,iximax^db\}
1356 if(has_equi_rho0) then
1357 rho=w(ix^d,rho_)+block%equi_vars(ix^d,equi_rho0_,0)
1358 else
1359 rho=w(ix^d,rho_)
1360 end if
1361 w(ix^d,e_)=w(ix^d,e_)&
1362 -half*((^c&w(ix^d,m^c_)**2+)/rho+(^c&w(ix^d,b^c_)**2+))
1363 {end do\}
1364 call small_values_average(ixi^l, ixo^l, w, x, flag, e_)
1365 ! convert back
1366 {do ix^db=iximin^db,iximax^db\}
1367 if(has_equi_rho0) then
1368 rho=w(ix^d,rho_)+block%equi_vars(ix^d,equi_rho0_,0)
1369 else
1370 rho=w(ix^d,rho_)
1371 end if
1372 w(ix^d,e_)=w(ix^d,e_)&
1373 +half*((^c&w(ix^d,m^c_)**2+)/rho+(^c&w(ix^d,b^c_)**2+))
1374 {end do\}
1375 end if
1376 call small_values_average(ixi^l, ixo^l, w, x, flag, r_e)
1377 case default
1378 if(.not.primitive) then
1379 !convert w to primitive
1380 ! do averaging of internal energy
1381 {do ix^db=iximin^db,iximax^db\}
1382 if(has_equi_rho0) then
1383 rho=w(ix^d,rho_)+block%equi_vars(ix^d,equi_rho0_,0)
1384 else
1385 rho=w(ix^d,rho_)
1386 end if
1387 ^c&w(ix^d,m^c_)=w(ix^d,m^c_)/rho\
1388 w(ix^d,p_)=gamma_1*(w(ix^d,e_)&
1389 -half*((^c&w(ix^d,m^c_)**2+)/rho+(^c&w(ix^d,b^c_)**2+)))
1390 {end do\}
1391 end if
1392 call small_values_error(w, x, ixi^l, ixo^l, flag, subname)
1393 end select
1394 end if
1395 end subroutine rmhd_handle_small_values_origin
1396
1397 !> Calculate v vector
1398 subroutine rmhd_get_v(w,x,ixI^L,ixO^L,v)
1400 integer, intent(in) :: ixi^l, ixo^l
1401 double precision, intent(in) :: w(ixi^s,nw), x(ixi^s,1:ndim)
1402 double precision, intent(out) :: v(ixi^s,ndir)
1403 double precision :: rho(ixi^s)
1404 integer :: idir
1405
1406 call rmhd_get_rho(w,x,ixi^l,ixo^l,rho)
1407 rho(ixo^s)=1.d0/rho(ixo^s)
1408 ! Convert momentum to velocity
1409 do idir = 1, ndir
1410 v(ixo^s, idir) = w(ixo^s, mom(idir))*rho(ixo^s)
1411 end do
1412 end subroutine rmhd_get_v
1413
1414 !> Calculate cmax_idim=csound+abs(v_idim) within ixO^L
1415 subroutine rmhd_get_cmax_origin(w,x,ixI^L,ixO^L,idim,cmax)
1417 integer, intent(in) :: ixi^l, ixo^l, idim
1418 double precision, intent(in) :: w(ixi^s, nw), x(ixi^s,1:ndim)
1419 double precision, intent(inout) :: cmax(ixi^s)
1420 double precision :: rho, inv_rho, cfast2, avmincs2, b2, kmax
1421 integer :: ix^d
1422
1423 if(b0field) then
1424 {do ix^db=ixomin^db,ixomax^db \}
1425 if(has_equi_rho0) then
1426 rho=(w(ix^d,rho_)+block%equi_vars(ix^d,equi_rho0_,b0i))
1427 else
1428 rho=w(ix^d,rho_)
1429 end if
1430 inv_rho=1.d0/rho
1431 ! sound speed**2
1432 cmax(ix^d)=rmhd_gamma*w(ix^d,p_)*inv_rho
1433 ! store |B|^2 in v
1434 b2=(^c&(w(ix^d,b^c_)+block%B0(ix^d,^c,b0i))**2+)
1435 cfast2=b2*inv_rho+cmax(ix^d)
1436 avmincs2=cfast2**2-4.0d0*cmax(ix^d)*(w(ix^d,mag(idim))+block%B0(ix^d,idim,b0i))**2*inv_rho
1437 if(avmincs2<zero) avmincs2=zero
1438 cmax(ix^d)=sqrt(half*(cfast2+sqrt(avmincs2)))
1439 cmax(ix^d)=abs(w(ix^d,mom(idim)))+cmax(ix^d)
1440 {end do\}
1441 else
1442 {do ix^db=ixomin^db,ixomax^db \}
1443 if(has_equi_rho0) then
1444 rho=(w(ix^d,rho_)+block%equi_vars(ix^d,equi_rho0_,b0i))
1445 else
1446 rho=w(ix^d,rho_)
1447 end if
1448 inv_rho=1.d0/rho
1449 ! sound speed**2
1450 cmax(ix^d)=rmhd_gamma*w(ix^d,p_)*inv_rho
1451 ! store |B|^2 in v
1452 b2=(^c&w(ix^d,b^c_)**2+)
1453 cfast2=b2*inv_rho+cmax(ix^d)
1454 avmincs2=cfast2**2-4.0d0*cmax(ix^d)*w(ix^d,mag(idim))**2*inv_rho
1455 if(avmincs2<zero) avmincs2=zero
1456 cmax(ix^d)=sqrt(half*(cfast2+sqrt(avmincs2)))
1457 cmax(ix^d)=abs(w(ix^d,mom(idim)))+cmax(ix^d)
1458 {end do\}
1459 end if
1460 end subroutine rmhd_get_cmax_origin
1461
1462 subroutine rmhd_get_a2max(w,x,ixI^L,ixO^L,a2max)
1464 integer, intent(in) :: ixi^l, ixo^l
1465 double precision, intent(in) :: w(ixi^s, nw), x(ixi^s,1:ndim)
1466 double precision, intent(inout) :: a2max(ndim)
1467 double precision :: a2(ixi^s,ndim,nw)
1468 integer :: gxo^l,hxo^l,jxo^l,kxo^l,i,j
1469
1470 a2=zero
1471 do i = 1,ndim
1472 !> 4th order
1473 hxo^l=ixo^l-kr(i,^d);
1474 gxo^l=hxo^l-kr(i,^d);
1475 jxo^l=ixo^l+kr(i,^d);
1476 kxo^l=jxo^l+kr(i,^d);
1477 a2(ixo^s,i,1:nw)=abs(-w(kxo^s,1:nw)+16.d0*w(jxo^s,1:nw)&
1478 -30.d0*w(ixo^s,1:nw)+16.d0*w(hxo^s,1:nw)-w(gxo^s,1:nw))
1479 a2max(i)=maxval(a2(ixo^s,i,1:nw))/12.d0/dxlevel(i)**2
1480 end do
1481 end subroutine rmhd_get_a2max
1482
1483 !> get adaptive cutoff temperature for TRAC (Johnston 2019 ApJL, 873, L22)
1484 subroutine rmhd_get_tcutoff(ixI^L,ixO^L,w,x,Tco_local,Tmax_local)
1486 use mod_geometry
1487 integer, intent(in) :: ixi^l,ixo^l
1488 double precision, intent(in) :: x(ixi^s,1:ndim)
1489 double precision, intent(out) :: tco_local,tmax_local
1490 ! in primitive form
1491 double precision, intent(inout) :: w(ixi^s,1:nw)
1492 double precision, parameter :: trac_delta=0.25d0
1493 double precision :: tmp1(ixi^s),te(ixi^s),lts(ixi^s)
1494 double precision, dimension(ixI^S,1:ndir) :: bunitvec
1495 double precision, dimension(ixI^S,1:ndim) :: gradt
1496 double precision :: bdir(ndim)
1497 double precision :: ltrc,ltrp,altr(ixi^s)
1498 integer :: idims,jxo^l,hxo^l,ixa^d,ixb^d,ix^d
1499 integer :: jxp^l,hxp^l,ixp^l,ixq^l
1500 logical :: lrlt(ixi^s)
1501
1503 call rmhd_get_temperature_from_te(w,x,ixi^l,ixi^l,te)
1504 else
1505 call rmhd_get_rfactor(w,x,ixi^l,ixi^l,te)
1506 te(ixi^s)=w(ixi^s,p_)/(te(ixi^s)*w(ixi^s,rho_))
1507 end if
1508 tco_local=zero
1509 tmax_local=maxval(te(ixo^s))
1510
1511 {^ifoned
1512 select case(rmhd_trac_type)
1513 case(0)
1514 !> test case, fixed cutoff temperature
1515 block%wextra(ixi^s,tcoff_)=2.5d5/unit_temperature
1516 case(1)
1517 hxo^l=ixo^l-1;
1518 jxo^l=ixo^l+1;
1519 lts(ixo^s)=0.5d0*abs(te(jxo^s)-te(hxo^s))/te(ixo^s)
1520 lrlt=.false.
1521 where(lts(ixo^s) > trac_delta)
1522 lrlt(ixo^s)=.true.
1523 end where
1524 if(any(lrlt(ixo^s))) then
1525 tco_local=maxval(te(ixo^s), mask=lrlt(ixo^s))
1526 end if
1527 case(2)
1528 !> iijima et al. 2021, LTRAC method
1529 ltrc=1.5d0
1530 ltrp=4.d0
1531 ixp^l=ixo^l^ladd1;
1532 hxo^l=ixo^l-1;
1533 jxo^l=ixo^l+1;
1534 hxp^l=ixp^l-1;
1535 jxp^l=ixp^l+1;
1536 lts(ixp^s)=0.5d0*abs(te(jxp^s)-te(hxp^s))/te(ixp^s)
1537 lts(ixp^s)=max(one, (exp(lts(ixp^s))/ltrc)**ltrp)
1538 lts(ixo^s)=0.25d0*(lts(jxo^s)+two*lts(ixo^s)+lts(hxo^s))
1539 block%wextra(ixo^s,tcoff_)=te(ixo^s)*lts(ixo^s)**0.4d0
1540 case default
1541 call mpistop("rmhd_trac_type not allowed for 1D simulation")
1542 end select
1543 }
1544 {^nooned
1545 select case(rmhd_trac_type)
1546 case(0)
1547 !> test case, fixed cutoff temperature
1548 block%wextra(ixi^s,tcoff_)=2.5d5/unit_temperature
1549 case(1,4,6)
1550 ! temperature gradient at cell centers
1551 do idims=1,ndim
1552 call gradient(te,ixi^l,ixo^l,idims,tmp1)
1553 gradt(ixo^s,idims)=tmp1(ixo^s)
1554 end do
1555 ! B vector
1556 if(b0field) then
1557 bunitvec(ixo^s,:)=w(ixo^s,iw_mag(:))+block%B0(ixo^s,:,0)
1558 else
1559 bunitvec(ixo^s,:)=w(ixo^s,iw_mag(:))
1560 end if
1561 if(rmhd_trac_type .gt. 1) then
1562 ! B direction at cell center
1563 bdir=zero
1564 {do ixa^d=0,1\}
1565 ixb^d=(ixomin^d+ixomax^d-1)/2+ixa^d;
1566 bdir(1:ndim)=bdir(1:ndim)+bunitvec(ixb^d,1:ndim)
1567 {end do\}
1568 if(sum(bdir(:)**2) .gt. zero) then
1569 bdir(1:ndim)=bdir(1:ndim)/dsqrt(sum(bdir(:)**2))
1570 end if
1571 block%special_values(3:ndim+2)=bdir(1:ndim)
1572 end if
1573 tmp1(ixo^s)=dsqrt(sum(bunitvec(ixo^s,:)**2,dim=ndim+1))
1574 where(tmp1(ixo^s)/=0.d0)
1575 tmp1(ixo^s)=1.d0/tmp1(ixo^s)
1576 elsewhere
1577 tmp1(ixo^s)=bigdouble
1578 end where
1579 ! b unit vector: magnetic field direction vector
1580 do idims=1,ndim
1581 bunitvec(ixo^s,idims)=bunitvec(ixo^s,idims)*tmp1(ixo^s)
1582 end do
1583 ! temperature length scale inversed
1584 lts(ixo^s)=abs(sum(gradt(ixo^s,1:ndim)*bunitvec(ixo^s,1:ndim),dim=ndim+1))/te(ixo^s)
1585 ! fraction of cells size to temperature length scale
1586 if(slab_uniform) then
1587 lts(ixo^s)=minval(dxlevel)*lts(ixo^s)
1588 else
1589 lts(ixo^s)=minval(block%ds(ixo^s,:),dim=ndim+1)*lts(ixo^s)
1590 end if
1591 lrlt=.false.
1592 where(lts(ixo^s) > trac_delta)
1593 lrlt(ixo^s)=.true.
1594 end where
1595 if(any(lrlt(ixo^s))) then
1596 block%special_values(1)=maxval(te(ixo^s), mask=lrlt(ixo^s))
1597 else
1598 block%special_values(1)=zero
1599 end if
1600 block%special_values(2)=tmax_local
1601 case(2)
1602 !> iijima et al. 2021, LTRAC method
1603 ltrc=1.5d0
1604 ltrp=4.d0
1605 ixp^l=ixo^l^ladd2;
1606 ! temperature gradient at cell centers
1607 do idims=1,ndim
1608 ixq^l=ixp^l;
1609 hxp^l=ixp^l;
1610 jxp^l=ixp^l;
1611 select case(idims)
1612 {case(^d)
1613 ixqmin^d=ixqmin^d+1
1614 ixqmax^d=ixqmax^d-1
1615 hxpmax^d=ixpmin^d
1616 jxpmin^d=ixpmax^d
1617 \}
1618 end select
1619 call gradient(te,ixi^l,ixq^l,idims,gradt(ixi^s,idims))
1620 call gradientf(te,x,ixi^l,hxp^l,idims,gradt(ixi^s,idims),nghostcells,.true.)
1621 call gradientf(te,x,ixi^l,jxp^l,idims,gradt(ixi^s,idims),nghostcells,.false.)
1622 end do
1623 ! B vector
1624 {do ix^db=ixpmin^db,ixpmax^db\}
1625 if(b0field) then
1626 ^c&bunitvec(ix^d,^c)=w(ix^d,iw_mag(^c))+block%B0(ix^d,^c,0)\
1627 else
1628 ^c&bunitvec(ix^d,^c)=w(ix^d,iw_mag(^c))\
1629 end if
1630 tmp1(ix^d)=1.d0/(dsqrt(^c&bunitvec(ix^d,^c)**2+)+smalldouble)
1631 ! b unit vector: magnetic field direction vector
1632 ^d&bunitvec({ix^d},^d)=bunitvec({ix^d},^d)*tmp1({ix^d})\
1633 ! temperature length scale inversed
1634 lts(ix^d)=abs(^d&gradt({ix^d},^d)*bunitvec({ix^d},^d)+)/te(ix^d)
1635 ! fraction of cells size to temperature length scale
1636 if(slab_uniform) then
1637 lts(ix^d)=min(^d&dxlevel(^d))*lts(ix^d)
1638 else
1639 lts(ix^d)=min(^d&block%ds({ix^d},^d))*lts(ix^d)
1640 end if
1641 lts(ix^d)=max(one,(exp(lts(ix^d))/ltrc)**ltrp)
1642 {end do\}
1643 ! need one ghost layer for thermal conductivity
1644 ixp^l=ixo^l^ladd1;
1645 do idims=1,ndim
1646 hxo^l=ixp^l-kr(idims,^d);
1647 jxo^l=ixp^l+kr(idims,^d);
1648 if(idims==1) then
1649 altr(ixp^s)=0.25d0*(lts(hxo^s)+two*lts(ixp^s)+lts(jxo^s))*bunitvec(ixp^s,idims)**2
1650 else
1651 altr(ixp^s)=altr(ixp^s)+0.25d0*(lts(hxo^s)+two*lts(ixp^s)+lts(jxo^s))*bunitvec(ixp^s,idims)**2
1652 end if
1653 end do
1654 block%wextra(ixp^s,tcoff_)=te(ixp^s)*altr(ixp^s)**0.4d0
1655 case(3,5)
1656 !> do nothing here
1657 case default
1658 call mpistop("unknown rmhd_trac_type")
1659 end select
1660 }
1661 end subroutine rmhd_get_tcutoff
1662
1663 !> get H speed for H-correction to fix the carbuncle problem at grid-aligned shock front
1664 subroutine rmhd_get_h_speed(wprim,x,ixI^L,ixO^L,idim,Hspeed)
1666
1667 integer, intent(in) :: ixi^l, ixo^l, idim
1668 double precision, intent(in) :: wprim(ixi^s, nw)
1669 double precision, intent(in) :: x(ixi^s,1:ndim)
1670 double precision, intent(out) :: hspeed(ixi^s,1:number_species)
1671
1672 double precision :: csound(ixi^s,ndim)
1673 double precision, allocatable :: tmp(:^d&)
1674 integer :: jxc^l, ixc^l, ixa^l, id, ix^d
1675
1676 hspeed=0.d0
1677 ixa^l=ixo^l^ladd1;
1678 allocate(tmp(ixa^s))
1679 do id=1,ndim
1680 call rmhd_get_csound_prim(wprim,x,ixi^l,ixa^l,id,tmp)
1681 csound(ixa^s,id)=tmp(ixa^s)
1682 end do
1683 ixcmax^d=ixomax^d;
1684 ixcmin^d=ixomin^d+kr(idim,^d)-1;
1685 jxcmax^d=ixcmax^d+kr(idim,^d);
1686 jxcmin^d=ixcmin^d+kr(idim,^d);
1687 hspeed(ixc^s,1)=0.5d0*abs(wprim(jxc^s,mom(idim))+csound(jxc^s,idim)-wprim(ixc^s,mom(idim))+csound(ixc^s,idim))
1688
1689 do id=1,ndim
1690 if(id==idim) cycle
1691 ixamax^d=ixcmax^d+kr(id,^d);
1692 ixamin^d=ixcmin^d+kr(id,^d);
1693 hspeed(ixc^s,1)=max(hspeed(ixc^s,1),0.5d0*abs(wprim(ixa^s,mom(id))+csound(ixa^s,id)-wprim(ixc^s,mom(id))+csound(ixc^s,id)))
1694 ixamax^d=ixcmax^d-kr(id,^d);
1695 ixamin^d=ixcmin^d-kr(id,^d);
1696 hspeed(ixc^s,1)=max(hspeed(ixc^s,1),0.5d0*abs(wprim(ixc^s,mom(id))+csound(ixc^s,id)-wprim(ixa^s,mom(id))+csound(ixa^s,id)))
1697 end do
1698
1699 do id=1,ndim
1700 if(id==idim) cycle
1701 ixamax^d=jxcmax^d+kr(id,^d);
1702 ixamin^d=jxcmin^d+kr(id,^d);
1703 hspeed(ixc^s,1)=max(hspeed(ixc^s,1),0.5d0*abs(wprim(ixa^s,mom(id))+csound(ixa^s,id)-wprim(jxc^s,mom(id))+csound(jxc^s,id)))
1704 ixamax^d=jxcmax^d-kr(id,^d);
1705 ixamin^d=jxcmin^d-kr(id,^d);
1706 hspeed(ixc^s,1)=max(hspeed(ixc^s,1),0.5d0*abs(wprim(jxc^s,mom(id))+csound(jxc^s,id)-wprim(ixa^s,mom(id))+csound(ixa^s,id)))
1707 end do
1708 deallocate(tmp)
1709
1710 end subroutine rmhd_get_h_speed
1711
1712 !> Estimating bounds for the minimum and maximum signal velocities without split
1713 subroutine rmhd_get_cbounds(wLC,wRC,wLp,wRp,x,ixI^L,ixO^L,idim,Hspeed,cmax,cmin)
1715 integer, intent(in) :: ixi^l, ixo^l, idim
1716 double precision, intent(in) :: wlc(ixi^s, nw), wrc(ixi^s, nw)
1717 double precision, intent(in) :: wlp(ixi^s, nw), wrp(ixi^s, nw)
1718 double precision, intent(in) :: x(ixi^s,1:ndim)
1719 double precision, intent(inout) :: cmax(ixi^s,1:number_species)
1720 double precision, intent(inout), optional :: cmin(ixi^s,1:number_species)
1721 double precision, intent(in) :: hspeed(ixi^s,1:number_species)
1722
1723 double precision :: wmean(ixi^s,nw), csoundl(ixo^s), csoundr(ixo^s)
1724 double precision :: umean, dmean, tmp1, tmp2, tmp3
1725 integer :: ix^d
1726
1727 select case (boundspeed)
1728 case (1)
1729 ! This implements formula (10.52) from "Riemann Solvers and Numerical
1730 ! Methods for Fluid Dynamics" by Toro.
1731 call rmhd_get_csound_prim(wlp,x,ixi^l,ixo^l,idim,csoundl)
1732 call rmhd_get_csound_prim(wrp,x,ixi^l,ixo^l,idim,csoundr)
1733 if(present(cmin)) then
1734 {do ix^db=ixomin^db,ixomax^db\}
1735 tmp1=sqrt(wlp(ix^d,rho_))
1736 tmp2=sqrt(wrp(ix^d,rho_))
1737 tmp3=1.d0/(tmp1+tmp2)
1738 umean=(wlp(ix^d,mom(idim))*tmp1+wrp(ix^d,mom(idim))*tmp2)*tmp3
1739 dmean=sqrt((tmp1*csoundl(ix^d)**2+tmp2*csoundr(ix^d)**2)*tmp3+&
1740 half*tmp1*tmp2*tmp3**2*(wrp(ix^d,mom(idim))-wlp(ix^d,mom(idim)))**2)
1741 cmin(ix^d,1)=umean-dmean
1742 cmax(ix^d,1)=umean+dmean
1743 {end do\}
1744 if(h_correction) then
1745 {do ix^db=ixomin^db,ixomax^db\}
1746 cmin(ix^d,1)=sign(one,cmin(ix^d,1))*max(abs(cmin(ix^d,1)),hspeed(ix^d,1))
1747 cmax(ix^d,1)=sign(one,cmax(ix^d,1))*max(abs(cmax(ix^d,1)),hspeed(ix^d,1))
1748 {end do\}
1749 end if
1750 else
1751 {do ix^db=ixomin^db,ixomax^db\}
1752 tmp1=sqrt(wlp(ix^d,rho_))
1753 tmp2=sqrt(wrp(ix^d,rho_))
1754 tmp3=1.d0/(tmp1+tmp2)
1755 umean=(wlp(ix^d,mom(idim))*tmp1+wrp(ix^d,mom(idim))*tmp2)*tmp3
1756 dmean=sqrt((tmp1*csoundl(ix^d)**2+tmp2*csoundr(ix^d)**2)*tmp3+&
1757 half*tmp1*tmp2*tmp3**2*(wrp(ix^d,mom(idim))-wlp(ix^d,mom(idim)))**2)
1758 cmax(ix^d,1)=abs(umean)+dmean
1759 {end do\}
1760 end if
1761 case (2)
1762 wmean(ixo^s,1:nwflux)=0.5d0*(wlp(ixo^s,1:nwflux)+wrp(ixo^s,1:nwflux))
1763 call rmhd_get_csound_prim(wmean,x,ixi^l,ixo^l,idim,csoundr)
1764 if(present(cmin)) then
1765 {do ix^db=ixomin^db,ixomax^db\}
1766 cmax(ix^d,1)=max(wmean(ix^d,mom(idim))+csoundr(ix^d),zero)
1767 cmin(ix^d,1)=min(wmean(ix^d,mom(idim))-csoundr(ix^d),zero)
1768 {end do\}
1769 if(h_correction) then
1770 {do ix^db=ixomin^db,ixomax^db\}
1771 cmin(ix^d,1)=sign(one,cmin(ix^d,1))*max(abs(cmin(ix^d,1)),hspeed(ix^d,1))
1772 cmax(ix^d,1)=sign(one,cmax(ix^d,1))*max(abs(cmax(ix^d,1)),hspeed(ix^d,1))
1773 {end do\}
1774 end if
1775 else
1776 cmax(ixo^s,1)=abs(wmean(ixo^s,mom(idim)))+csoundr(ixo^s)
1777 end if
1778 case (3)
1779 ! Miyoshi 2005 JCP 208, 315 equation (67)
1780 call rmhd_get_csound_prim(wlp,x,ixi^l,ixo^l,idim,csoundl)
1781 call rmhd_get_csound_prim(wrp,x,ixi^l,ixo^l,idim,csoundr)
1782 if(present(cmin)) then
1783 {do ix^db=ixomin^db,ixomax^db\}
1784 csoundl(ix^d)=max(csoundl(ix^d),csoundr(ix^d))
1785 cmin(ix^d,1)=min(wlp(ix^d,mom(idim)),wrp(ix^d,mom(idim)))-csoundl(ix^d)
1786 cmax(ix^d,1)=max(wlp(ix^d,mom(idim)),wrp(ix^d,mom(idim)))+csoundl(ix^d)
1787 {end do\}
1788 if(h_correction) then
1789 {do ix^db=ixomin^db,ixomax^db\}
1790 cmin(ix^d,1)=sign(one,cmin(ix^d,1))*max(abs(cmin(ix^d,1)),hspeed(ix^d,1))
1791 cmax(ix^d,1)=sign(one,cmax(ix^d,1))*max(abs(cmax(ix^d,1)),hspeed(ix^d,1))
1792 {end do\}
1793 end if
1794 else
1795 {do ix^db=ixomin^db,ixomax^db\}
1796 csoundl(ix^d)=max(csoundl(ix^d),csoundr(ix^d))
1797 cmax(ix^d,1)=max(wlp(ix^d,mom(idim)),wrp(ix^d,mom(idim)))+csoundl(ix^d)
1798 {end do\}
1799 end if
1800 end select
1801 end subroutine rmhd_get_cbounds
1802
1803 !> Estimating bounds for the minimum and maximum signal velocities with rho split
1804 subroutine rmhd_get_cbounds_split_rho(wLC,wRC,wLp,wRp,x,ixI^L,ixO^L,idim,Hspeed,cmax,cmin)
1806 integer, intent(in) :: ixi^l, ixo^l, idim
1807 double precision, intent(in) :: wlc(ixi^s, nw), wrc(ixi^s, nw)
1808 double precision, intent(in) :: wlp(ixi^s, nw), wrp(ixi^s, nw)
1809 double precision, intent(in) :: x(ixi^s,1:ndim)
1810 double precision, intent(inout) :: cmax(ixi^s,1:number_species)
1811 double precision, intent(inout), optional :: cmin(ixi^s,1:number_species)
1812 double precision, intent(in) :: hspeed(ixi^s,1:number_species)
1813 double precision :: wmean(ixi^s,nw), csoundl(ixo^s), csoundr(ixo^s)
1814 double precision :: umean, dmean, tmp1, tmp2, tmp3
1815 integer :: ix^d
1816
1817 select case (boundspeed)
1818 case (1)
1819 ! This implements formula (10.52) from "Riemann Solvers and Numerical
1820 ! Methods for Fluid Dynamics" by Toro.
1821 call rmhd_get_csound_prim_split(wlp,x,ixi^l,ixo^l,idim,csoundl)
1822 call rmhd_get_csound_prim_split(wrp,x,ixi^l,ixo^l,idim,csoundr)
1823 if(present(cmin)) then
1824 {do ix^db=ixomin^db,ixomax^db\}
1825 tmp1=sqrt(wlp(ix^d,rho_)+block%equi_vars(ix^d,equi_rho0_,b0i))
1826 tmp2=sqrt(wrp(ix^d,rho_)+block%equi_vars(ix^d,equi_rho0_,b0i))
1827 tmp3=1.d0/(tmp1+tmp2)
1828 umean=(wlp(ix^d,mom(idim))*tmp1+wrp(ix^d,mom(idim))*tmp2)*tmp3
1829 dmean=sqrt((tmp1*csoundl(ix^d)**2+tmp2*csoundr(ix^d)**2)*tmp3+&
1830 half*tmp1*tmp2*tmp3**2*(wrp(ix^d,mom(idim))-wlp(ix^d,mom(idim)))**2)
1831 cmin(ix^d,1)=umean-dmean
1832 cmax(ix^d,1)=umean+dmean
1833 {end do\}
1834 if(h_correction) then
1835 {do ix^db=ixomin^db,ixomax^db\}
1836 cmin(ix^d,1)=sign(one,cmin(ix^d,1))*max(abs(cmin(ix^d,1)),hspeed(ix^d,1))
1837 cmax(ix^d,1)=sign(one,cmax(ix^d,1))*max(abs(cmax(ix^d,1)),hspeed(ix^d,1))
1838 {end do\}
1839 end if
1840 else
1841 {do ix^db=ixomin^db,ixomax^db\}
1842 tmp1=sqrt(wlp(ix^d,rho_)+block%equi_vars(ix^d,equi_rho0_,b0i))
1843 tmp2=sqrt(wrp(ix^d,rho_)+block%equi_vars(ix^d,equi_rho0_,b0i))
1844 tmp3=1.d0/(tmp1+tmp2)
1845 umean=(wlp(ix^d,mom(idim))*tmp1+wrp(ix^d,mom(idim))*tmp2)*tmp3
1846 dmean=sqrt((tmp1*csoundl(ix^d)**2+tmp2*csoundr(ix^d)**2)*tmp3+&
1847 half*tmp1*tmp2*tmp3**2*(wrp(ix^d,mom(idim))-wlp(ix^d,mom(idim)))**2)
1848 cmax(ix^d,1)=abs(umean)+dmean
1849 {end do\}
1850 end if
1851 case (2)
1852 wmean(ixo^s,1:nwflux)=0.5d0*(wlp(ixo^s,1:nwflux)+wrp(ixo^s,1:nwflux))
1853 call rmhd_get_csound_prim_split(wmean,x,ixi^l,ixo^l,idim,csoundr)
1854 if(present(cmin)) then
1855 {do ix^db=ixomin^db,ixomax^db\}
1856 cmax(ix^d,1)=max(wmean(ix^d,mom(idim))+csoundr(ix^d),zero)
1857 cmin(ix^d,1)=min(wmean(ix^d,mom(idim))-csoundr(ix^d),zero)
1858 {end do\}
1859 if(h_correction) then
1860 {do ix^db=ixomin^db,ixomax^db\}
1861 cmin(ix^d,1)=sign(one,cmin(ix^d,1))*max(abs(cmin(ix^d,1)),hspeed(ix^d,1))
1862 cmax(ix^d,1)=sign(one,cmax(ix^d,1))*max(abs(cmax(ix^d,1)),hspeed(ix^d,1))
1863 {end do\}
1864 end if
1865 else
1866 cmax(ixo^s,1)=abs(wmean(ixo^s,mom(idim)))+csoundr(ixo^s)
1867 end if
1868 case (3)
1869 ! Miyoshi 2005 JCP 208, 315 equation (67)
1870 call rmhd_get_csound_prim_split(wlp,x,ixi^l,ixo^l,idim,csoundl)
1871 call rmhd_get_csound_prim_split(wrp,x,ixi^l,ixo^l,idim,csoundr)
1872 if(present(cmin)) then
1873 {do ix^db=ixomin^db,ixomax^db\}
1874 csoundl(ix^d)=max(csoundl(ix^d),csoundr(ix^d))
1875 cmin(ix^d,1)=min(wlp(ix^d,mom(idim)),wrp(ix^d,mom(idim)))-csoundl(ix^d)
1876 cmax(ix^d,1)=max(wlp(ix^d,mom(idim)),wrp(ix^d,mom(idim)))+csoundl(ix^d)
1877 {end do\}
1878 if(h_correction) then
1879 {do ix^db=ixomin^db,ixomax^db\}
1880 cmin(ix^d,1)=sign(one,cmin(ix^d,1))*max(abs(cmin(ix^d,1)),hspeed(ix^d,1))
1881 cmax(ix^d,1)=sign(one,cmax(ix^d,1))*max(abs(cmax(ix^d,1)),hspeed(ix^d,1))
1882 {end do\}
1883 end if
1884 else
1885 {do ix^db=ixomin^db,ixomax^db\}
1886 csoundl(ix^d)=max(csoundl(ix^d),csoundr(ix^d))
1887 cmax(ix^d,1)=max(wlp(ix^d,mom(idim)),wrp(ix^d,mom(idim)))+csoundl(ix^d)
1888 {end do\}
1889 end if
1890 end select
1891 end subroutine rmhd_get_cbounds_split_rho
1892
1893 !> prepare velocities for ct methods
1894 subroutine rmhd_get_ct_velocity_average(vcts,wLp,wRp,ixI^L,ixO^L,idim,cmax,cmin)
1896
1897 integer, intent(in) :: ixi^l, ixo^l, idim
1898 double precision, intent(in) :: wlp(ixi^s, nw), wrp(ixi^s, nw)
1899 double precision, intent(in) :: cmax(ixi^s)
1900 double precision, intent(in), optional :: cmin(ixi^s)
1901 type(ct_velocity), intent(inout):: vcts
1902
1903 end subroutine rmhd_get_ct_velocity_average
1904
1905 subroutine rmhd_get_ct_velocity_contact(vcts,wLp,wRp,ixI^L,ixO^L,idim,cmax,cmin)
1907
1908 integer, intent(in) :: ixi^l, ixo^l, idim
1909 double precision, intent(in) :: wlp(ixi^s, nw), wrp(ixi^s, nw)
1910 double precision, intent(in) :: cmax(ixi^s)
1911 double precision, intent(in), optional :: cmin(ixi^s)
1912 type(ct_velocity), intent(inout):: vcts
1913
1914 ! calculate velocities related to different UCT schemes
1915 if(.not.allocated(vcts%vnorm)) allocate(vcts%vnorm(ixi^s,1:ndim))
1916 ! get average normal velocity at cell faces
1917 vcts%vnorm(ixo^s,idim)=0.5d0*(wlp(ixo^s,mom(idim))+wrp(ixo^s,mom(idim)))
1918
1919 end subroutine rmhd_get_ct_velocity_contact
1920
1921 subroutine rmhd_get_ct_velocity_hll(vcts,wLp,wRp,ixI^L,ixO^L,idim,cmax,cmin)
1923
1924 integer, intent(in) :: ixi^l, ixo^l, idim
1925 double precision, intent(in) :: wlp(ixi^s, nw), wrp(ixi^s, nw)
1926 double precision, intent(in) :: cmax(ixi^s)
1927 double precision, intent(in), optional :: cmin(ixi^s)
1928 type(ct_velocity), intent(inout):: vcts
1929
1930 integer :: idime,idimn
1931
1932 if(.not.allocated(vcts%vbarC)) then
1933 allocate(vcts%vbarC(ixi^s,1:ndir,2),vcts%vbarLC(ixi^s,1:ndir,2),vcts%vbarRC(ixi^s,1:ndir,2))
1934 allocate(vcts%cbarmin(ixi^s,1:ndim),vcts%cbarmax(ixi^s,1:ndim))
1935 end if
1936 ! Store magnitude of characteristics
1937 if(present(cmin)) then
1938 vcts%cbarmin(ixo^s,idim)=max(-cmin(ixo^s),zero)
1939 vcts%cbarmax(ixo^s,idim)=max( cmax(ixo^s),zero)
1940 else
1941 vcts%cbarmax(ixo^s,idim)=max( cmax(ixo^s),zero)
1942 vcts%cbarmin(ixo^s,idim)=vcts%cbarmax(ixo^s,idim)
1943 end if
1944
1945 idimn=mod(idim,ndir)+1 ! 'Next' direction
1946 idime=mod(idim+1,ndir)+1 ! Electric field direction
1947 ! Store velocities
1948 vcts%vbarLC(ixo^s,idim,1)=wlp(ixo^s,mom(idimn))
1949 vcts%vbarRC(ixo^s,idim,1)=wrp(ixo^s,mom(idimn))
1950 vcts%vbarC(ixo^s,idim,1)=(vcts%cbarmax(ixo^s,idim)*vcts%vbarLC(ixo^s,idim,1) &
1951 +vcts%cbarmin(ixo^s,idim)*vcts%vbarRC(ixo^s,idim,1))&
1952 /(vcts%cbarmax(ixo^s,idim)+vcts%cbarmin(ixo^s,idim))
1953
1954 vcts%vbarLC(ixo^s,idim,2)=wlp(ixo^s,mom(idime))
1955 vcts%vbarRC(ixo^s,idim,2)=wrp(ixo^s,mom(idime))
1956 vcts%vbarC(ixo^s,idim,2)=(vcts%cbarmax(ixo^s,idim)*vcts%vbarLC(ixo^s,idim,2) &
1957 +vcts%cbarmin(ixo^s,idim)*vcts%vbarRC(ixo^s,idim,1))&
1958 /(vcts%cbarmax(ixo^s,idim)+vcts%cbarmin(ixo^s,idim))
1959
1960 end subroutine rmhd_get_ct_velocity_hll
1961
1962 !> Calculate fast magnetosonic wave speed
1963 subroutine rmhd_get_csound_prim(w,x,ixI^L,ixO^L,idim,csound)
1965 integer, intent(in) :: ixi^l, ixo^l, idim
1966 double precision, intent(in) :: w(ixi^s, nw), x(ixi^s,1:ndim)
1967 double precision, intent(out):: csound(ixo^s)
1968 double precision :: inv_rho, cfast2, avmincs2, b2, kmax
1969 double precision :: prad_tensor(ixo^s, 1:ndim, 1:ndim)
1970 double precision :: prad_max(ixo^s)
1971 integer :: ix^d
1972
1973 call rmhd_get_pradiation(w, x, ixi^l, ixo^l, prad_tensor, nghostcells-1)
1974 !> filter cmax
1975 if(radio_acoustic_filter) then
1976 call rmhd_radio_acoustic_filter(x, ixi^l, ixo^l, prad_max)
1977 endif
1978 ! store |B|^2 in v
1979 if(b0field) then
1980 {do ix^db=ixomin^db,ixomax^db \}
1981 inv_rho=1.d0/w(ix^d,rho_)
1982 prad_max(ix^d) = maxval(prad_tensor(ix^d,:,:))
1983 if(rmhd_energy) then
1984 csound(ix^d)=max(rmhd_gamma,4.d0/3.d0)*(w(ix^d,p_)+prad_max(ix^d))*inv_rho
1985 else
1986 csound(ix^d)=rmhd_gamma*rmhd_adiab*w(ix^d,rho_)**gamma_1
1987 end if
1988 b2=(^c&(w(ix^d,b^c_)+block%B0(ix^d,^c,b0i))**2+)
1989 cfast2=b2*inv_rho+csound(ix^d)
1990 avmincs2=cfast2**2-4.0d0*csound(ix^d)*(w(ix^d,mag(idim))+&
1991 block%B0(ix^d,idim,b0i))**2*inv_rho
1992 if(avmincs2<zero) avmincs2=zero
1993 csound(ix^d)=sqrt(half*(cfast2+sqrt(avmincs2)))
1994 {end do\}
1995 else
1996 {do ix^db=ixomin^db,ixomax^db \}
1997 inv_rho=1.d0/w(ix^d,rho_)
1998 prad_max(ix^d)=maxval(prad_tensor(ix^d,:,:))
1999 if(rmhd_energy) then
2000 csound(ix^d)=max(rmhd_gamma,4.d0/3.d0)*(w(ix^d,p_)+prad_max(ix^d))*inv_rho
2001 else
2002 csound(ix^d)=rmhd_gamma*rmhd_adiab*w(ix^d,rho_)**gamma_1
2003 end if
2004 b2=(^c&w(ix^d,b^c_)**2+)
2005 cfast2=b2*inv_rho+csound(ix^d)
2006 avmincs2=cfast2**2-4.0d0*csound(ix^d)*w(ix^d,mag(idim))**2*inv_rho
2007 if(avmincs2<zero) avmincs2=zero
2008 csound(ix^d)=sqrt(half*(cfast2+sqrt(avmincs2)))
2009 {end do\}
2010 end if
2011 end subroutine rmhd_get_csound_prim
2012
2013 !> Calculate fast magnetosonic wave speed
2014 subroutine rmhd_get_csound_prim_split(w,x,ixI^L,ixO^L,idim,csound)
2016 integer, intent(in) :: ixi^l, ixo^l, idim
2017 double precision, intent(in) :: w(ixi^s, nw), x(ixi^s,1:ndim)
2018 double precision, intent(out):: csound(ixo^s)
2019 double precision :: rho, inv_rho, cfast2, avmincs2, b2, kmax
2020 double precision :: prad_tensor(ixo^s, 1:ndim, 1:ndim)
2021 double precision :: prad_max(ixo^s)
2022 integer :: ix^d
2023
2024 call rmhd_get_pradiation(w, x, ixi^l, ixo^l, prad_tensor, nghostcells-1)
2025 !> filter cmax
2026 if (radio_acoustic_filter) then
2027 call rmhd_radio_acoustic_filter(x, ixi^l, ixo^l, prad_max)
2028 endif
2029
2030 ! store |B|^2 in v
2031 if(b0field) then
2032 {do ix^db=ixomin^db,ixomax^db \}
2033 rho=(w(ix^d,rho_)+block%equi_vars(ix^d,equi_rho0_,b0i))
2034 inv_rho=1.d0/rho
2035 prad_max(ix^d) = maxval(prad_tensor(ix^d,:,:))
2036 if(has_equi_pe0) then
2037 csound(ix^d)=max(rmhd_gamma,4.d0/3.d0)*(w(ix^d,p_)+block%equi_vars(ix^d,equi_pe0_,b0i)+prad_max(ix^d))*inv_rho
2038 end if
2039 b2=(^c&(w(ix^d,b^c_)+block%B0(ix^d,^c,b0i))**2+)
2040 cfast2=b2*inv_rho+csound(ix^d)
2041 avmincs2=cfast2**2-4.0d0*csound(ix^d)*(w(ix^d,mag(idim))+&
2042 block%B0(ix^d,idim,b0i))**2*inv_rho
2043 if(avmincs2<zero) avmincs2=zero
2044 csound(ix^d)=sqrt(half*(cfast2+sqrt(avmincs2)))
2045 {end do\}
2046 else
2047 {do ix^db=ixomin^db,ixomax^db \}
2048 rho=(w(ix^d,rho_)+block%equi_vars(ix^d,equi_rho0_,b0i))
2049 inv_rho=1.d0/rho
2050 prad_max(ix^d) = maxval(prad_tensor(ix^d,:,:))
2051 if(has_equi_pe0) then
2052 csound(ix^d)=max(rmhd_gamma,4.d0/3.d0)*(w(ix^d,p_)+block%equi_vars(ix^d,equi_pe0_,b0i)+prad_max(ix^d))*inv_rho
2053 end if
2054 b2=(^c&w(ix^d,b^c_)**2+)
2055 cfast2=b2*inv_rho+csound(ix^d)
2056 avmincs2=cfast2**2-4.0d0*csound(ix^d)*w(ix^d,mag(idim))**2*inv_rho
2057 if(avmincs2<zero) avmincs2=zero
2058 csound(ix^d)=sqrt(half*(cfast2+sqrt(avmincs2)))
2059 {end do\}
2060 end if
2061 end subroutine rmhd_get_csound_prim_split
2062
2063 !> Calculate thermal pressure=(gamma-1)*(e-0.5*m**2/rho-b**2/2) within ixO^L
2064 subroutine rmhd_get_pthermal_origin(w,x,ixI^L,ixO^L,pth)
2067
2068 integer, intent(in) :: ixi^l, ixo^l
2069 double precision, intent(in) :: w(ixi^s,nw)
2070 double precision, intent(in) :: x(ixi^s,1:ndim)
2071 double precision, intent(out):: pth(ixi^s)
2072
2073 integer :: iw, ix^d
2074
2075 {do ix^db=ixomin^db,ixomax^db\}
2076 if(has_equi_rho0) then
2077 pth(ix^d)=gamma_1*(w(ix^d,e_)-half*((^c&w(ix^d,m^c_)**2+)/(w(ix^d,rho_)+block%equi_vars(ix^d,equi_rho0_,0))&
2078 +(^c&w(ix^d,b^c_)**2+)))+block%equi_vars(ix^d,equi_pe0_,0)
2079 else
2080 pth(ix^d)=gamma_1*(w(ix^d,e_)-half*((^c&w(ix^d,m^c_)**2+)/w(ix^d,rho_)&
2081 +(^c&w(ix^d,b^c_)**2+)))
2082 end if
2083 if(fix_small_values.and.pth(ix^d)<small_pressure) pth(ix^d)=small_pressure
2084 {end do\}
2085
2086 if(check_small_values.and..not.fix_small_values) then
2087 {do ix^db=ixomin^db,ixomax^db\}
2088 if(pth(ix^d)<small_pressure) then
2089 write(*,*) "Error: small value of gas pressure",pth(ix^d),&
2090 " encountered when call rmhd_get_pthermal"
2091 write(*,*) "Iteration: ", it, " Time: ", global_time
2092 write(*,*) "Location: ", x(ix^d,:)
2093 write(*,*) "Cell number: ", ix^d
2094 do iw=1,nw
2095 write(*,*) trim(cons_wnames(iw)),": ",w(ix^d,iw)
2096 end do
2097 ! use erroneous arithmetic operation to crash the run
2098 if(trace_small_values) write(*,*) sqrt(pth(ix^d)-bigdouble)
2099 write(*,*) "Saving status at the previous time step"
2100 crash=.true.
2101 end if
2102 {end do\}
2103 end if
2104 end subroutine rmhd_get_pthermal_origin
2105
2106 !> copy temperature from stored Te variable
2107 subroutine rmhd_get_temperature_from_te(w, x, ixI^L, ixO^L, res)
2109 integer, intent(in) :: ixi^l, ixo^l
2110 double precision, intent(in) :: w(ixi^s, 1:nw)
2111 double precision, intent(in) :: x(ixi^s, 1:ndim)
2112 double precision, intent(out):: res(ixi^s)
2113 res(ixo^s) = w(ixo^s, te_)
2114 end subroutine rmhd_get_temperature_from_te
2115
2116 !> Calculate temperature=p/rho when in e_ the internal energy is stored
2117 subroutine rmhd_get_temperature_from_eint(w, x, ixI^L, ixO^L, res)
2119 integer, intent(in) :: ixi^l, ixo^l
2120 double precision, intent(in) :: w(ixi^s, 1:nw)
2121 double precision, intent(in) :: x(ixi^s, 1:ndim)
2122 double precision, intent(out):: res(ixi^s)
2123 double precision :: r(ixi^s)
2124
2125 call rmhd_get_rfactor(w,x,ixi^l,ixo^l,r)
2126 res(ixo^s) = gamma_1 * w(ixo^s, e_)/(w(ixo^s,rho_)*r(ixo^s))
2127 end subroutine rmhd_get_temperature_from_eint
2128
2129 !> Calculate temperature=p/rho when in e_ the total energy is stored
2130 subroutine rmhd_get_temperature_from_etot(w, x, ixI^L, ixO^L, res)
2132 integer, intent(in) :: ixi^l, ixo^l
2133 double precision, intent(in) :: w(ixi^s, 1:nw)
2134 double precision, intent(in) :: x(ixi^s, 1:ndim)
2135 double precision, intent(out):: res(ixi^s)
2136 double precision :: r(ixi^s)
2137
2138 call rmhd_get_rfactor(w,x,ixi^l,ixo^l,r)
2139 call rmhd_get_pthermal(w,x,ixi^l,ixo^l,res)
2140 res(ixo^s)=res(ixo^s)/(r(ixo^s)*w(ixo^s,rho_))
2141 end subroutine rmhd_get_temperature_from_etot
2142
2143 subroutine rmhd_get_temperature_from_etot_with_equi(w, x, ixI^L, ixO^L, res)
2145 integer, intent(in) :: ixi^l, ixo^l
2146 double precision, intent(in) :: w(ixi^s, 1:nw)
2147 double precision, intent(in) :: x(ixi^s, 1:ndim)
2148 double precision, intent(out):: res(ixi^s)
2149 double precision :: r(ixi^s)
2150
2151 call rmhd_get_rfactor(w,x,ixi^l,ixo^l,r)
2152 call rmhd_get_pthermal(w,x,ixi^l,ixo^l,res)
2153 res(ixo^s)=res(ixo^s)/(r(ixo^s)*(w(ixo^s,rho_)+block%equi_vars(ixo^s,equi_rho0_,b0i)))
2154 end subroutine rmhd_get_temperature_from_etot_with_equi
2155
2156 subroutine rmhd_get_temperature_from_eint_with_equi(w, x, ixI^L, ixO^L, res)
2158 integer, intent(in) :: ixi^l, ixo^l
2159 double precision, intent(in) :: w(ixi^s, 1:nw)
2160 double precision, intent(in) :: x(ixi^s, 1:ndim)
2161 double precision, intent(out):: res(ixi^s)
2162 double precision :: r(ixi^s)
2163
2164 call rmhd_get_rfactor(w,x,ixi^l,ixo^l,r)
2165 res(ixo^s) = (gamma_1 * w(ixo^s, e_) + block%equi_vars(ixo^s,equi_pe0_,b0i)) /&
2166 ((w(ixo^s,rho_) +block%equi_vars(ixo^s,equi_rho0_,b0i))*r(ixo^s))
2167 end subroutine rmhd_get_temperature_from_eint_with_equi
2168
2169 subroutine rmhd_get_temperature_equi(w,x, ixI^L, ixO^L, res)
2171 integer, intent(in) :: ixi^l, ixo^l
2172 double precision, intent(in) :: w(ixi^s, 1:nw)
2173 double precision, intent(in) :: x(ixi^s, 1:ndim)
2174 double precision, intent(out):: res(ixi^s)
2175 double precision :: r(ixi^s)
2176
2177 call rmhd_get_rfactor(w,x,ixi^l,ixo^l,r)
2178 res(ixo^s)= block%equi_vars(ixo^s,equi_pe0_,b0i)/(block%equi_vars(ixo^s,equi_rho0_,b0i)*r(ixo^s))
2179 end subroutine rmhd_get_temperature_equi
2180
2181 subroutine rmhd_get_rho_equi(w, x, ixI^L, ixO^L, res)
2183 integer, intent(in) :: ixi^l, ixo^l
2184 double precision, intent(in) :: w(ixi^s, 1:nw)
2185 double precision, intent(in) :: x(ixi^s, 1:ndim)
2186 double precision, intent(out):: res(ixi^s)
2187 res(ixo^s) = block%equi_vars(ixo^s,equi_rho0_,b0i)
2188 end subroutine rmhd_get_rho_equi
2189
2190 subroutine rmhd_get_pe_equi(w,x, ixI^L, ixO^L, res)
2192 integer, intent(in) :: ixi^l, ixo^l
2193 double precision, intent(in) :: w(ixi^s, 1:nw)
2194 double precision, intent(in) :: x(ixi^s, 1:ndim)
2195 double precision, intent(out):: res(ixi^s)
2196 res(ixo^s) = block%equi_vars(ixo^s,equi_pe0_,b0i)
2197 end subroutine rmhd_get_pe_equi
2198
2199 !> Calculate total pressure within ixO^L including magnetic pressure
2200 subroutine rmhd_get_p_total(w,x,ixI^L,ixO^L,p)
2202 integer, intent(in) :: ixi^l, ixo^l
2203 double precision, intent(in) :: w(ixi^s,nw)
2204 double precision, intent(in) :: x(ixi^s,1:ndim)
2205 double precision, intent(out) :: p(ixi^s)
2206
2207 call rmhd_get_pthermal(w,x,ixi^l,ixo^l,p)
2208 p(ixo^s) = p(ixo^s) + 0.5d0 * sum(w(ixo^s, mag(:))**2, dim=ndim+1)
2209 end subroutine rmhd_get_p_total
2210
2211 !> Calculate radiation pressure within ixO^L
2212 subroutine rmhd_get_pradiation(w, x, ixI^L, ixO^L, prad, nth)
2214 use mod_fld
2215 use mod_afld
2216 integer, intent(in) :: ixi^l, ixo^l, nth
2217 double precision, intent(in) :: w(ixi^s, 1:nw)
2218 double precision, intent(in) :: x(ixi^s, 1:ndim)
2219 double precision, intent(out):: prad(ixo^s, 1:ndim, 1:ndim)
2220
2221 select case (rmhd_radiation_formalism)
2222 case('fld')
2223 call fld_get_radpress(w, x, ixi^l, ixo^l, prad, nth)
2224 case('afld')
2225 call afld_get_radpress(w, x, ixi^l, ixo^l, prad, nth)
2226 case default
2227 call mpistop('Radiation formalism unknown')
2228 end select
2229 end subroutine rmhd_get_pradiation
2230
2231 !> Calculates the sum of the gas pressure and the max Prad tensor element
2232 subroutine rmhd_get_pthermal_plus_pradiation(w, x, ixI^L, ixO^L, pth_plus_prad)
2234 integer, intent(in) :: ixi^l, ixo^l
2235 double precision, intent(in) :: w(ixi^s, 1:nw)
2236 double precision, intent(in) :: x(ixi^s, 1:ndim)
2237 double precision :: pth(ixi^s)
2238 double precision :: prad_tensor(ixo^s, 1:ndim, 1:ndim)
2239 double precision :: prad_max(ixo^s)
2240 double precision, intent(out) :: pth_plus_prad(ixi^s)
2241 integer :: ix^d
2242
2243 call rmhd_get_pthermal(w, x, ixi^l, ixo^l, pth)
2244 call rmhd_get_pradiation(w, x, ixi^l, ixo^l, prad_tensor, nghostcells)
2245 {do ix^d = ixomin^d,ixomax^d\}
2246 prad_max(ix^d) = maxval(prad_tensor(ix^d,:,:))
2247 {enddo\}
2248 !> filter cmax
2249 if (radio_acoustic_filter) then
2250 call rmhd_radio_acoustic_filter(x, ixi^l, ixo^l, prad_max)
2251 endif
2252 pth_plus_prad(ixo^s) = pth(ixo^s) + prad_max(ixo^s)
2254
2255 !> Filter peaks in cmax due to radiation energy density, used for debugging
2256 subroutine rmhd_radio_acoustic_filter(x, ixI^L, ixO^L, prad_max)
2258 integer, intent(in) :: ixi^l, ixo^l
2259 double precision, intent(in) :: x(ixi^s, 1:ndim)
2260 double precision, intent(inout) :: prad_max(ixo^s)
2261 double precision :: tmp_prad(ixi^s)
2262 integer :: ix^d, filter, idim
2263
2264 if (size_ra_filter .lt. 1) call mpistop("ra filter of size < 1 makes no sense")
2265 if (size_ra_filter .gt. nghostcells) call mpistop("ra filter of size < nghostcells makes no sense")
2266
2267 tmp_prad(ixi^s) = zero
2268 tmp_prad(ixo^s) = prad_max(ixo^s)
2269 do filter = 1,size_ra_filter
2270 do idim = 1,ndim
2271 ! {do ix^D = ixOmin^D+filter,ixOmax^D-filter\}
2272 {do ix^d = ixomin^d,ixomax^d\}
2273 prad_max(ix^d) = min(tmp_prad(ix^d),tmp_prad(ix^d+filter*kr(idim,^d)))
2274 prad_max(ix^d) = min(tmp_prad(ix^d),tmp_prad(ix^d-filter*kr(idim,^d)))
2275 {enddo\}
2276 enddo
2277 enddo
2278 end subroutine rmhd_radio_acoustic_filter
2279
2280 !> Calculates gas temperature
2281 subroutine rmhd_get_tgas(w, x, ixI^L, ixO^L, tgas)
2283 integer, intent(in) :: ixi^l, ixo^l
2284 double precision, intent(in) :: w(ixi^s, 1:nw)
2285 double precision, intent(in) :: x(ixi^s, 1:ndim)
2286 double precision :: pth(ixi^s)
2287 double precision, intent(out):: tgas(ixi^s)
2288
2289 call rmhd_get_pthermal(w, x, ixi^l, ixo^l, pth)
2290 tgas(ixi^s) = pth(ixi^s)/w(ixi^s,rho_)
2291 end subroutine rmhd_get_tgas
2292
2293 !> Calculates radiation temperature
2294 subroutine rmhd_get_trad(w, x, ixI^L, ixO^L, trad)
2296 use mod_constants
2297
2298 integer, intent(in) :: ixi^l, ixo^l
2299 double precision, intent(in) :: w(ixi^s, 1:nw)
2300 double precision, intent(in) :: x(ixi^s, 1:ndim)
2301 double precision, intent(out):: trad(ixi^s)
2302
2303 trad(ixi^s) = (w(ixi^s,r_e)*unit_pressure&
2304 /const_rad_a)**(1.d0/4.d0)/unit_temperature
2305 end subroutine rmhd_get_trad
2306
2307 !> Calculate fluxes within ixO^L without any splitting
2308 subroutine rmhd_get_flux(wC,w,x,ixI^L,ixO^L,idim,f)
2310 use mod_geometry
2311
2312 integer, intent(in) :: ixi^l, ixo^l, idim
2313 ! conservative w
2314 double precision, intent(in) :: wc(ixi^s,nw)
2315 ! primitive w
2316 double precision, intent(in) :: w(ixi^s,nw)
2317 double precision, intent(in) :: x(ixi^s,1:ndim)
2318 double precision,intent(out) :: f(ixi^s,nwflux)
2319 double precision :: vhall(ixi^s,1:ndir)
2320 double precision :: ptotal
2321 integer :: iw, ix^d
2322
2323 {do ix^db=ixomin^db,ixomax^db\}
2324 ! Get flux of density
2325 f(ix^d,rho_)=w(ix^d,mom(idim))*w(ix^d,rho_)
2326 ! f_i[m_k]=v_i*m_k-b_k*b_i
2327 ^c&f(ix^d,m^c_)=wc(ix^d,mom(idim))*w(ix^d,m^c_)-w(ix^d,mag(idim))*w(ix^d,b^c_)\
2328 ptotal=w(ix^d,p_)+half*(^c&w(ix^d,b^c_)**2+)
2329 ! normal one includes total pressure
2330 f(ix^d,mom(idim))=f(ix^d,mom(idim))+ptotal
2331 ! Get flux of total energy
2332 ! f_i[e]=v_i*e+v_i*ptotal-b_i*(b_k*v_k)
2333 f(ix^d,e_)=w(ix^d,mom(idim))*(wc(ix^d,e_)+ptotal)&
2334 -w(ix^d,mag(idim))*(^c&w(ix^d,b^c_)*w(ix^d,m^c_)+)
2335 ! f_i[b_k]=v_i*b_k-v_k*b_i
2336 ^c&f(ix^d,b^c_)=w(ix^d,mom(idim))*w(ix^d,b^c_)-w(ix^d,mag(idim))*w(ix^d,m^c_)\
2337 {end do\}
2338 if(rmhd_glm) then
2339 {do ix^db=ixomin^db,ixomax^db\}
2340 f(ix^d,mag(idim))=w(ix^d,psi_)
2341 !f_i[psi]=Ch^2*b_{i} Eq. 24e and Eq. 38c Dedner et al 2002 JCP, 175, 645
2342 f(ix^d,psi_)=cmax_global**2*w(ix^d,mag(idim))
2343 {end do\}
2344 end if
2346 {do ix^db=ixomin^db,ixomax^db\}
2347 f(ix^d,r_e)=w(ix^d,mom(idim))*wc(ix^d,r_e)
2348 {end do\}
2349 else
2350 f(ixo^s,r_e)=zero
2351 endif
2352 ! Get flux of tracer
2353 do iw=1,rmhd_n_tracer
2354 {do ix^db=ixomin^db,ixomax^db\}
2355 f(ix^d,tracer(iw))=w(ix^d,mom(idim))*w(ix^d,tracer(iw))
2356 {end do\}
2357 end do
2359 {do ix^db=ixomin^db,ixomax^db\}
2360 f(ix^d,e_)=f(ix^d,e_)+w(ix^d,q_)*w(ix^d,mag(idim))/(dsqrt(^d&w({ix^d},b^d_)**2+)+smalldouble)
2361 f(ix^d,q_)=zero
2362 {end do\}
2363 end if
2364 end subroutine rmhd_get_flux
2365
2366 !> Calculate fluxes within ixO^L with possible splitting
2367 subroutine rmhd_get_flux_split(wC,w,x,ixI^L,ixO^L,idim,f)
2369 use mod_geometry
2370 integer, intent(in) :: ixi^l, ixo^l, idim
2371 ! conservative w
2372 double precision, intent(in) :: wc(ixi^s,nw)
2373 ! primitive w
2374 double precision, intent(in) :: w(ixi^s,nw)
2375 double precision, intent(in) :: x(ixi^s,1:ndim)
2376 double precision,intent(out) :: f(ixi^s,nwflux)
2377 double precision :: vhall(ixi^s,1:ndir)
2378 double precision :: ptotal, btotal(ixo^s,1:ndir)
2379 integer :: iw, ix^d
2380
2381 {do ix^db=ixomin^db,ixomax^db\}
2382 ! Get flux of density
2383 if(has_equi_rho0) then
2384 f(ix^d,rho_)=w(ix^d,mom(idim))*(w(ix^d,rho_)+block%equi_vars(ix^d,equi_rho0_,b0i))
2385 else
2386 f(ix^d,rho_)=w(ix^d,mom(idim))*w(ix^d,rho_)
2387 endif
2388 if(rmhd_energy) then
2389 ptotal=w(ix^d,p_)+half*(^c&w(ix^d,b^c_)**2+)
2390 else
2391 ptotal=rmhd_adiab*w(ix^d,rho_)**rmhd_gamma+half*(^c&w(ix^d,b^c_)**2+)
2392 if(has_equi_pe0) then
2393 ptotal=ptotal-block%equi_vars(ix^d,equi_pe0_,b0i)
2394 end if
2395 end if
2396 if(b0field) then
2397 ^c&btotal(ix^d,^c)=w(ix^d,b^c_)+block%B0(ix^d,^c,idim)\
2398 ptotal=ptotal+(^c&w(ix^d,b^c_)*block%B0(ix^d,^c,idim)+)
2399 ! Get flux of momentum and magnetic field
2400 ! f_i[m_k]=v_i*m_k-b_k*b_i
2401 ^c&f(ix^d,m^c_)=wc(ix^d,mom(idim))*w(ix^d,m^c_)-&
2402 btotal(ix^d,idim)*w(ix^d,b^c_)-w(ix^d,mag(idim))*block%B0(ix^d,^c,idim)\
2403 f(ix^d,mom(idim))=f(ix^d,mom(idim))+ptotal
2404 else
2405 ^c&btotal(ix^d,^c)=w(ix^d,b^c_)\
2406 ! Get flux of momentum and magnetic field
2407 ! f_i[m_k]=v_i*m_k-b_k*b_i
2408 ^c&f(ix^d,m^c_)=wc(ix^d,mom(idim))*w(ix^d,m^c_)-w(ix^d,mag(idim))*w(ix^d,b^c_)\
2409 f(ix^d,mom(idim))=f(ix^d,mom(idim))+ptotal
2410 end if
2411 ! f_i[b_k]=v_i*b_k-v_k*b_i
2412 ^c&f(ix^d,b^c_)=w(ix^d,mom(idim))*btotal(ix^d,^c)-btotal(ix^d,idim)*w(ix^d,m^c_)\
2413 ! Get flux of energy
2414 ! f_i[e]=v_i*e+v_i*ptotal-b_i*(b_k*v_k)
2415 if(rmhd_energy) then
2416 f(ix^d,e_)=w(ix^d,mom(idim))*(wc(ix^d,e_)+ptotal)&
2417 -btotal(ix^d,idim)*(^c&w(ix^d,b^c_)*w(ix^d,m^c_)+)
2418 end if
2419 {end do\}
2420 if(rmhd_glm) then
2421 {do ix^db=ixomin^db,ixomax^db\}
2422 f(ix^d,mag(idim))=w(ix^d,psi_)
2423 !f_i[psi]=Ch^2*b_{i} Eq. 24e and Eq. 38c Dedner et al 2002 JCP, 175, 645
2424 f(ix^d,psi_) = cmax_global**2*w(ix^d,mag(idim))
2425 {end do\}
2426 end if
2428 {do ix^db=ixomin^db,ixomax^db\}
2429 f(ix^d,r_e)=w(ix^d,mom(idim))*wc(ix^d,r_e)
2430 {end do\}
2431 else
2432 f(ixo^s,r_e)=zero
2433 endif
2434 ! Get flux of tracer
2435 do iw=1,rmhd_n_tracer
2436 {do ix^db=ixomin^db,ixomax^db\}
2437 f(ix^d,tracer(iw))=w(ix^d,mom(idim))*w(ix^d,tracer(iw))
2438 {end do\}
2439 end do
2441 {do ix^db=ixomin^db,ixomax^db\}
2442 f(ix^d,e_)=f(ix^d,e_)+w(ix^d,q_)*btotal(ix^d,idim)/(dsqrt(^c&btotal(ix^d,^c)**2+)+smalldouble)
2443 f(ix^d,q_)=zero
2444 {end do\}
2445 end if
2446 end subroutine rmhd_get_flux_split
2447
2448 !> use cell-center flux to get cell-face flux
2449 !> and get the source term as the divergence of the flux
2450 subroutine get_flux_on_cell_face(ixI^L,ixO^L,ff,src)
2452
2453 integer, intent(in) :: ixi^l, ixo^l
2454 double precision, dimension(:^D&,:), intent(inout) :: ff
2455 double precision, intent(out) :: src(ixi^s)
2456
2457 double precision :: ffc(ixi^s,1:ndim)
2458 double precision :: dxinv(ndim)
2459 integer :: idims, ix^d, ixa^l, ixb^l, ixc^l
2460
2461 ixa^l=ixo^l^ladd1;
2462 dxinv=1.d0/dxlevel
2463 ! cell corner flux in ffc
2464 ffc=0.d0
2465 ixcmax^d=ixomax^d; ixcmin^d=ixomin^d-1;
2466 {do ix^db=0,1\}
2467 ixbmin^d=ixcmin^d+ix^d;
2468 ixbmax^d=ixcmax^d+ix^d;
2469 ffc(ixc^s,1:ndim)=ffc(ixc^s,1:ndim)+ff(ixb^s,1:ndim)
2470 {end do\}
2471 ffc(ixc^s,1:ndim)=0.5d0**ndim*ffc(ixc^s,1:ndim)
2472 ! flux at cell face
2473 ff(ixi^s,1:ndim)=0.d0
2474 do idims=1,ndim
2475 ixb^l=ixo^l-kr(idims,^d);
2476 ixcmax^d=ixomax^d; ixcmin^d=ixbmin^d;
2477 {do ix^db=0,1 \}
2478 if({ ix^d==0 .and. ^d==idims | .or.}) then
2479 ixbmin^d=ixcmin^d-ix^d;
2480 ixbmax^d=ixcmax^d-ix^d;
2481 ff(ixc^s,idims)=ff(ixc^s,idims)+ffc(ixb^s,idims)
2482 end if
2483 {end do\}
2484 ff(ixc^s,idims)=ff(ixc^s,idims)*0.5d0**(ndim-1)
2485 end do
2486 src=0.d0
2487 if(slab_uniform) then
2488 do idims=1,ndim
2489 ff(ixa^s,idims)=dxinv(idims)*ff(ixa^s,idims)
2490 ixb^l=ixo^l-kr(idims,^d);
2491 src(ixo^s)=src(ixo^s)+ff(ixo^s,idims)-ff(ixb^s,idims)
2492 end do
2493 else
2494 do idims=1,ndim
2495 ff(ixa^s,idims)=ff(ixa^s,idims)*block%surfaceC(ixa^s,idims)
2496 ixb^l=ixo^l-kr(idims,^d);
2497 src(ixo^s)=src(ixo^s)+ff(ixo^s,idims)-ff(ixb^s,idims)
2498 end do
2499 src(ixo^s)=src(ixo^s)/block%dvolume(ixo^s)
2500 end if
2501 end subroutine get_flux_on_cell_face
2502
2503 !> w[iws]=w[iws]+qdt*S[iws,wCT] where S is the source based on wCT within ixO
2504 subroutine rmhd_add_source(qdt,dtfactor,ixI^L,ixO^L,wCT,wCTprim,w,x,qsourcesplit,active)
2508 use mod_cak_force, only: cak_add_source
2509
2510 integer, intent(in) :: ixi^l, ixo^l
2511 double precision, intent(in) :: qdt,dtfactor
2512 double precision, intent(in) :: wct(ixi^s,1:nw),wctprim(ixi^s,1:nw), x(ixi^s,1:ndim)
2513 double precision, intent(inout) :: w(ixi^s,1:nw)
2514 logical, intent(in) :: qsourcesplit
2515 logical, intent(inout) :: active
2516
2517 ! TODO local_timestep support is only added for splitting
2518 ! but not for other nonideal terms such gravity, RC, viscosity,..
2519 ! it will also only work for divbfix 'linde', which does not require
2520 ! modification as it does not use dt in the update
2521 if (.not. qsourcesplit) then
2522 if(has_equi_pe0) then
2523 active = .true.
2524 call add_pe0_divv(qdt,dtfactor,ixi^l,ixo^l,wctprim,w,x)
2525 end if
2527 call add_hypertc_source(qdt,ixi^l,ixo^l,wct,w,x,wctprim)
2528 end if
2529 ! Source for B0 splitting
2530 if (b0field) then
2531 active = .true.
2532 call add_source_b0split(qdt,dtfactor,ixi^l,ixo^l,wctprim,w,x)
2533 end if
2534 ! Sources for resistivity in eqs. for e, B1, B2 and B3
2535 if (abs(rmhd_eta)>smalldouble)then
2536 active = .true.
2537 call add_source_res2(qdt,ixi^l,ixo^l,wct,w,x)
2538 end if
2539 if (rmhd_eta_hyper>0.d0)then
2540 active = .true.
2541 call add_source_hyperres(qdt,ixi^l,ixo^l,wct,w,x)
2542 end if
2543 end if
2544 {^nooned
2545 if(source_split_divb .eqv. qsourcesplit) then
2546 ! Sources related to div B
2547 select case (type_divb)
2548 case (divb_ct)
2549 continue ! Do nothing
2550 case (divb_linde)
2551 active = .true.
2552 call add_source_linde(qdt,ixi^l,ixo^l,wct,w,x)
2553 case (divb_glm)
2554 active = .true.
2555 call add_source_glm(qdt,ixi^l,ixo^l,wct,w,x)
2556 case (divb_powel)
2557 active = .true.
2558 call add_source_powel(qdt,ixi^l,ixo^l,wctprim,w,x)
2559 case (divb_janhunen)
2560 active = .true.
2561 call add_source_janhunen(qdt,ixi^l,ixo^l,wctprim,w,x)
2562 case (divb_lindejanhunen)
2563 active = .true.
2564 call add_source_linde(qdt,ixi^l,ixo^l,wct,w,x)
2565 call add_source_janhunen(qdt,ixi^l,ixo^l,wctprim,w,x)
2566 case (divb_lindepowel)
2567 active = .true.
2568 call add_source_linde(qdt,ixi^l,ixo^l,wct,w,x)
2569 call add_source_powel(qdt,ixi^l,ixo^l,wctprim,w,x)
2570 case (divb_lindeglm)
2571 active = .true.
2572 call add_source_linde(qdt,ixi^l,ixo^l,wct,w,x)
2573 call add_source_glm(qdt,ixi^l,ixo^l,wct,w,x)
2574 case (divb_multigrid)
2575 continue ! Do nothing
2576 case (divb_none)
2577 ! Do nothing
2578 case default
2579 call mpistop('Unknown divB fix')
2580 end select
2581 end if
2582 }
2583 if(rmhd_viscosity) then
2584 call viscosity_add_source(qdt,ixi^l,ixo^l,wct,&
2585 w,x,rmhd_energy,qsourcesplit,active)
2586 end if
2587 if(rmhd_gravity) then
2588 call gravity_add_source(qdt,ixi^l,ixo^l,wct,wctprim,&
2589 w,x,gravity_energy,gravity_rhov,qsourcesplit,active)
2590 end if
2591 if (rmhd_cak_force) then
2592 call cak_add_source(qdt,ixi^l,ixo^l,wct,w,x,rmhd_energy,qsourcesplit,active)
2593 end if
2594 !> This is where the radiation force and heating/cooling are added
2595 call rmhd_add_radiation_source(qdt,ixi^l,ixo^l,wct,w,x,qsourcesplit,active)
2596 ! update temperature from new pressure, density, and old ionization degree
2598 if(.not.qsourcesplit) then
2599 active = .true.
2600 call rmhd_update_temperature(ixi^l,ixo^l,wct,w,x)
2601 end if
2602 end if
2603 end subroutine rmhd_add_source
2604
2605 subroutine rmhd_add_radiation_source(qdt,ixI^L,ixO^L,wCT,w,x,qsourcesplit,active)
2606 use mod_constants
2608 use mod_usr_methods
2609 use mod_fld
2610 use mod_afld
2611 integer, intent(in) :: ixi^l, ixo^l
2612 double precision, intent(in) :: qdt, x(ixi^s,1:ndim)
2613 double precision, intent(in) :: wct(ixi^s,1:nw)
2614 double precision, intent(inout) :: w(ixi^s,1:nw)
2615 logical, intent(in) :: qsourcesplit
2616 logical, intent(inout) :: active
2617 double precision :: cmax(ixi^s)
2618
2619 select case(rmhd_radiation_formalism)
2620 case('fld')
2621 if(fld_diff_scheme .eq. 'mg') call fld_get_diffcoef_central(w, wct, x, ixi^l, ixo^l)
2622 !> radiation force
2623 if(rmhd_radiation_force) call get_fld_rad_force(qdt,ixi^l,ixo^l,wct,w,x,rmhd_energy,qsourcesplit,active)
2624 call rmhd_handle_small_values(.true., w, x, ixi^l, ixo^l, 'fld_e_interact')
2625 case('afld')
2626 if(fld_diff_scheme .eq. 'mg') call afld_get_diffcoef_central(w, wct, x, ixi^l, ixo^l)
2627 !> radiation force
2628 if(rmhd_radiation_force) call get_afld_rad_force(qdt,ixi^l,ixo^l,wct,w,x,rmhd_energy,qsourcesplit,active)
2629 call rmhd_handle_small_values(.true., w, x, ixi^l, ixo^l, 'fld_e_interact')
2630 !> photon tiring, heating and cooling
2631 if(rmhd_energy) then
2632 if (rmhd_energy_interact) call get_afld_energy_interact(qdt,ixi^l,ixo^l,wct,w,x,rmhd_energy,qsourcesplit,active)
2633 endif
2634 case default
2635 call mpistop('Radiation formalism unknown')
2636 end select
2637 end subroutine rmhd_add_radiation_source
2638
2639 subroutine add_pe0_divv(qdt,dtfactor,ixI^L,ixO^L,wCT,w,x)
2641 use mod_geometry
2642 integer, intent(in) :: ixi^l, ixo^l
2643 double precision, intent(in) :: qdt,dtfactor
2644 double precision, intent(in) :: wct(ixi^s,1:nw), x(ixi^s,1:ndim)
2645 double precision, intent(inout) :: w(ixi^s,1:nw)
2646 double precision :: divv(ixi^s)
2647
2648 if(slab_uniform) then
2649 if(nghostcells .gt. 2) then
2650 call divvector(wct(ixi^s,mom(1:ndir)),ixi^l,ixo^l,divv,3)
2651 else
2652 call divvector(wct(ixi^s,mom(1:ndir)),ixi^l,ixo^l,divv,2)
2653 end if
2654 else
2655 call divvector(wct(ixi^s,mom(1:ndir)),ixi^l,ixo^l,divv)
2656 end if
2657 if(local_timestep) then
2658 w(ixo^s,e_)=w(ixo^s,e_)-dtfactor*block%dt(ixo^s)*block%equi_vars(ixo^s,equi_pe0_,0)*divv(ixo^s)
2659 else
2660 w(ixo^s,e_)=w(ixo^s,e_)-qdt*block%equi_vars(ixo^s,equi_pe0_,0)*divv(ixo^s)
2661 end if
2662 end subroutine add_pe0_divv
2663
2664 subroutine get_tau(ixI^L,ixO^L,w,Te,tau,sigT5)
2666 integer, intent(in) :: ixi^l, ixo^l
2667 double precision, dimension(ixI^S,1:nw), intent(in) :: w
2668 double precision, dimension(ixI^S), intent(in) :: te
2669 double precision, dimension(ixI^S), intent(out) :: tau,sigt5
2670 double precision :: dxmin,taumin
2671 double precision, dimension(ixI^S) :: sigt7,eint
2672 integer :: ix^d
2673
2674 taumin=4.d0
2675 !> w supposed to be wCTprim here
2676 if(rmhd_trac) then
2677 where(te(ixo^s) .lt. block%wextra(ixo^s,tcoff_))
2678 sigt5(ixo^s)=hypertc_kappa*sqrt(block%wextra(ixo^s,tcoff_)**5)
2679 sigt7(ixo^s)=sigt5(ixo^s)*block%wextra(ixo^s,tcoff_)
2680 else where
2681 sigt5(ixo^s)=hypertc_kappa*sqrt(te(ixo^s)**5)
2682 sigt7(ixo^s)=sigt5(ixo^s)*te(ixo^s)
2683 end where
2684 else
2685 sigt5(ixo^s)=hypertc_kappa*sqrt(te(ixo^s)**5)
2686 sigt7(ixo^s)=sigt5(ixo^s)*te(ixo^s)
2687 end if
2688 eint(ixo^s)=w(ixo^s,p_)/(rmhd_gamma-one)
2689 tau(ixo^s)=max(taumin*dt,sigt7(ixo^s)/eint(ixo^s)/cmax_global**2)
2690 end subroutine get_tau
2691
2692 subroutine add_hypertc_source(qdt,ixI^L,ixO^L,wCT,w,x,wCTprim)
2694 integer, intent(in) :: ixi^l,ixo^l
2695 double precision, intent(in) :: qdt
2696 double precision, dimension(ixI^S,1:ndim), intent(in) :: x
2697 double precision, dimension(ixI^S,1:nw), intent(in) :: wct,wctprim
2698 double precision, dimension(ixI^S,1:nw), intent(inout) :: w
2699 double precision :: invdx
2700 double precision, dimension(ixI^S) :: te,tau,sigt,htc_qsrc,tface,r
2701 double precision, dimension(ixI^S) :: htc_esrc,bsum,bunit
2702 double precision, dimension(ixI^S,1:ndim) :: btot
2703 integer :: idims
2704 integer :: hxc^l,hxo^l,ixc^l,jxc^l,jxo^l,kxc^l
2705
2706 call rmhd_get_rfactor(wctprim,x,ixi^l,ixi^l,r)
2707 !Te(ixI^S)=wCTprim(ixI^S,p_)/wCT(ixI^S,rho_)
2708 te(ixi^s)=wctprim(ixi^s,p_)/(r(ixi^s)*w(ixi^s,rho_))
2709 call get_tau(ixi^l,ixo^l,wctprim,te,tau,sigt)
2710 htc_qsrc=zero
2711 do idims=1,ndim
2712 if(b0field) then
2713 btot(ixo^s,idims)=wct(ixo^s,mag(idims))+block%B0(ixo^s,idims,0)
2714 else
2715 btot(ixo^s,idims)=wct(ixo^s,mag(idims))
2716 endif
2717 enddo
2718 bsum(ixo^s)=sqrt(sum(btot(ixo^s,:)**2,dim=ndim+1))+smalldouble
2719 do idims=1,ndim
2720 invdx=1.d0/dxlevel(idims)
2721 ixc^l=ixo^l;
2722 ixcmin^d=ixomin^d-kr(idims,^d);ixcmax^d=ixomax^d;
2723 jxc^l=ixc^l+kr(idims,^d);
2724 kxc^l=jxc^l+kr(idims,^d);
2725 hxc^l=ixc^l-kr(idims,^d);
2726 hxo^l=ixo^l-kr(idims,^d);
2727 tface(ixc^s)=(7.d0*(te(ixc^s)+te(jxc^s))-(te(hxc^s)+te(kxc^s)))/12.d0
2728 bunit(ixo^s)=btot(ixo^s,idims)/bsum(ixo^s)
2729 htc_qsrc(ixo^s)=htc_qsrc(ixo^s)+sigt(ixo^s)*bunit(ixo^s)*(tface(ixo^s)-tface(hxo^s))*invdx
2730 end do
2731 htc_qsrc(ixo^s)=(htc_qsrc(ixo^s)+wct(ixo^s,q_))/tau(ixo^s)
2732 w(ixo^s,q_)=w(ixo^s,q_)-qdt*htc_qsrc(ixo^s)
2733 end subroutine add_hypertc_source
2734
2735 !> Compute the Lorentz force (JxB)
2736 subroutine get_lorentz_force(ixI^L,ixO^L,w,JxB)
2738 integer, intent(in) :: ixi^l, ixo^l
2739 double precision, intent(in) :: w(ixi^s,1:nw)
2740 double precision, intent(inout) :: jxb(ixi^s,3)
2741 double precision :: a(ixi^s,3), b(ixi^s,3)
2742 ! For ndir=2 only 3rd component of J can exist, ndir=1 is impossible for MHD
2743 double precision :: current(ixi^s,7-2*ndir:3)
2744 integer :: idir, idirmin
2745
2746 b=0.0d0
2747 if(b0field) then
2748 do idir = 1, ndir
2749 b(ixo^s, idir) = w(ixo^s,mag(idir))+block%B0(ixo^s,idir,0)
2750 end do
2751 else
2752 do idir = 1, ndir
2753 b(ixo^s, idir) = w(ixo^s,mag(idir))
2754 end do
2755 end if
2756 ! store J current in a
2757 call get_current(w,ixi^l,ixo^l,idirmin,current)
2758 a=0.0d0
2759 do idir=7-2*ndir,3
2760 a(ixo^s,idir)=current(ixo^s,idir)
2761 end do
2762 call cross_product(ixi^l,ixo^l,a,b,jxb)
2763 end subroutine get_lorentz_force
2764
2765 !> Compute 1/(1+v_A^2/c^2) for semirelativistic MHD, where v_A is the Alfven
2766 !> velocity
2767 subroutine rmhd_gamma2_alfven(ixI^L, ixO^L, w, gamma_A2)
2769 integer, intent(in) :: ixi^l, ixo^l
2770 double precision, intent(in) :: w(ixi^s, nw)
2771 double precision, intent(out) :: gamma_a2(ixo^s)
2772 double precision :: rho(ixi^s)
2773
2774 ! rmhd_get_rho cannot be used as x is not a param
2775 if(has_equi_rho0) then
2776 rho(ixo^s) = w(ixo^s,rho_) + block%equi_vars(ixo^s,equi_rho0_,b0i)
2777 else
2778 rho(ixo^s) = w(ixo^s,rho_)
2779 endif
2780 ! Compute the inverse of 1 + B^2/(rho * c^2)
2781 gamma_a2(ixo^s) = 1.0d0/(1.0d0+rmhd_mag_en_all(w, ixi^l, ixo^l)/rho(ixo^s)*inv_squared_c)
2782 end subroutine rmhd_gamma2_alfven
2783
2784 !> Compute 1/sqrt(1+v_A^2/c^2) for semirelativisitic MHD, where v_A is the
2785 !> Alfven velocity
2786 function rmhd_gamma_alfven(w, ixI^L, ixO^L) result(gamma_A)
2788 integer, intent(in) :: ixi^l, ixo^l
2789 double precision, intent(in) :: w(ixi^s, nw)
2790 double precision :: gamma_a(ixo^s)
2791
2792 call rmhd_gamma2_alfven(ixi^l, ixo^l, w, gamma_a)
2793 gamma_a = sqrt(gamma_a)
2794 end function rmhd_gamma_alfven
2795
2796 subroutine rmhd_get_rho(w,x,ixI^L,ixO^L,rho)
2798 integer, intent(in) :: ixi^l, ixo^l
2799 double precision, intent(in) :: w(ixi^s,1:nw),x(ixi^s,1:ndim)
2800 double precision, intent(out) :: rho(ixi^s)
2801
2802 if(has_equi_rho0) then
2803 rho(ixo^s) = w(ixo^s,rho_) + block%equi_vars(ixo^s,equi_rho0_,b0i)
2804 else
2805 rho(ixo^s) = w(ixo^s,rho_)
2806 endif
2807 end subroutine rmhd_get_rho
2808
2809 !> handle small or negative internal energy
2810 subroutine rmhd_handle_small_ei(w, x, ixI^L, ixO^L, ie, subname)
2813 integer, intent(in) :: ixi^l,ixo^l, ie
2814 double precision, intent(inout) :: w(ixi^s,1:nw)
2815 double precision, intent(in) :: x(ixi^s,1:ndim)
2816 character(len=*), intent(in) :: subname
2817 double precision :: rho(ixi^s)
2818 integer :: idir
2819 logical :: flag(ixi^s,1:nw)
2820
2821 flag=.false.
2822 if(has_equi_pe0) then
2823 where(w(ixo^s,ie)+block%equi_vars(ixo^s,equi_pe0_,0)*inv_gamma_1<small_e)&
2824 flag(ixo^s,ie)=.true.
2825 else
2826 where(w(ixo^s,ie)<small_e) flag(ixo^s,ie)=.true.
2827 endif
2828 if(any(flag(ixo^s,ie))) then
2829 select case (small_values_method)
2830 case ("replace")
2831 if(has_equi_pe0) then
2832 where(flag(ixo^s,ie)) w(ixo^s,ie)=small_e - &
2833 block%equi_vars(ixo^s,equi_pe0_,0)*inv_gamma_1
2834 else
2835 where(flag(ixo^s,ie)) w(ixo^s,ie)=small_e
2836 endif
2837 case ("average")
2838 call small_values_average(ixi^l, ixo^l, w, x, flag, ie)
2839 case default
2840 ! small values error shows primitive variables
2841 w(ixo^s,e_)=w(ixo^s,e_)*gamma_1
2842 call rmhd_get_rho(w,x,ixi^l,ixo^l,rho)
2843 do idir = 1, ndir
2844 w(ixo^s, mom(idir)) = w(ixo^s, mom(idir))/rho(ixo^s)
2845 end do
2846 call small_values_error(w, x, ixi^l, ixo^l, flag, subname)
2847 end select
2848 end if
2849 end subroutine rmhd_handle_small_ei
2850
2851 subroutine rmhd_update_temperature(ixI^L,ixO^L,wCT,w,x)
2854
2855 integer, intent(in) :: ixi^l, ixo^l
2856 double precision, intent(in) :: wct(ixi^s,1:nw), x(ixi^s,1:ndim)
2857 double precision, intent(inout) :: w(ixi^s,1:nw)
2858
2859 double precision :: iz_h(ixo^s),iz_he(ixo^s), pth(ixi^s)
2860
2861 call ionization_degree_from_temperature(ixi^l,ixo^l,wct(ixi^s,te_),iz_h,iz_he)
2862
2863 call rmhd_get_pthermal(w,x,ixi^l,ixo^l,pth)
2864
2865 w(ixo^s,te_)=(2.d0+3.d0*he_abundance)*pth(ixo^s)/(w(ixo^s,rho_)*(1.d0+iz_h(ixo^s)+&
2866 he_abundance*(iz_he(ixo^s)*(iz_he(ixo^s)+1.d0)+1.d0)))
2867 end subroutine rmhd_update_temperature
2868
2869 !> Source terms after split off time-independent magnetic field
2870 subroutine add_source_b0split(qdt,dtfactor,ixI^L,ixO^L,wCT,w,x)
2872 integer, intent(in) :: ixi^l, ixo^l
2873 double precision, intent(in) :: qdt, dtfactor,wct(ixi^s,1:nw), x(ixi^s,1:ndim)
2874 double precision, intent(inout) :: w(ixi^s,1:nw)
2875 double precision :: a(ixi^s,3), b(ixi^s,3), axb(ixi^s,3)
2876 integer :: idir
2877
2878 a=0.d0
2879 b=0.d0
2880 ! for force-free field J0xB0 =0
2881 if(.not.b0field_forcefree) then
2882 ! store B0 magnetic field in b
2883 b(ixo^s,1:ndir)=block%B0(ixo^s,1:ndir,0)
2884 ! store J0 current in a
2885 do idir=7-2*ndir,3
2886 a(ixo^s,idir)=block%J0(ixo^s,idir)
2887 end do
2888 call cross_product(ixi^l,ixo^l,a,b,axb)
2889 if(local_timestep) then
2890 do idir=1,3
2891 axb(ixo^s,idir)=axb(ixo^s,idir)*block%dt(ixo^s)*dtfactor
2892 enddo
2893 else
2894 axb(ixo^s,:)=axb(ixo^s,:)*qdt
2895 endif
2896 ! add J0xB0 source term in momentum equations
2897 w(ixo^s,mom(1:ndir))=w(ixo^s,mom(1:ndir))+axb(ixo^s,1:ndir)
2898 end if
2899 if(total_energy) then
2900 a=0.d0
2901 ! for free-free field -(vxB0) dot J0 =0
2902 b(ixo^s,:)=wct(ixo^s,mag(:))
2903 ! store full magnetic field B0+B1 in b
2904 if(.not.b0field_forcefree) b(ixo^s,:)=b(ixo^s,:)+block%B0(ixo^s,:,0)
2905 ! store velocity in a
2906 a(ixi^s,1:ndir)=wct(ixi^s,mom(1:ndir))
2907 ! -E = a x b
2908 call cross_product(ixi^l,ixo^l,a,b,axb)
2909 if(local_timestep) then
2910 do idir=1,3
2911 axb(ixo^s,idir)=axb(ixo^s,idir)*block%dt(ixo^s)*dtfactor
2912 enddo
2913 else
2914 axb(ixo^s,:)=axb(ixo^s,:)*qdt
2915 endif
2916 ! add -(vxB) dot J0 source term in energy equation
2917 do idir=7-2*ndir,3
2918 w(ixo^s,e_)=w(ixo^s,e_)-axb(ixo^s,idir)*block%J0(ixo^s,idir)
2919 end do
2920 end if
2921 if (fix_small_values) call rmhd_handle_small_values(.false.,w,x,ixi^l,ixo^l,'add_source_B0')
2922 end subroutine add_source_b0split
2923
2924 !> Add resistive source to w within ixO Uses 3 point stencil (1 neighbour) in
2925 !> each direction, non-conservative. If the fourthorder precompiler flag is
2926 !> set, uses fourth order central difference for the laplacian. Then the
2927 !> stencil is 5 (2 neighbours).
2928 subroutine add_source_res1(qdt,ixI^L,ixO^L,wCT,w,x)
2930 use mod_usr_methods
2931 use mod_geometry
2932 integer, intent(in) :: ixi^l, ixo^l
2933 double precision, intent(in) :: qdt
2934 double precision, intent(in) :: wct(ixi^s,1:nw), x(ixi^s,1:ndim)
2935 double precision, intent(inout) :: w(ixi^s,1:nw)
2936 integer :: ixa^l,idir,jdir,kdir,idirmin,idim,jxo^l,hxo^l,ix
2937 integer :: lxo^l, kxo^l
2938 double precision :: tmp(ixi^s),tmp2(ixi^s)
2939 ! For ndir=2 only 3rd component of J can exist, ndir=1 is impossible for MHD
2940 double precision :: current(ixi^s,7-2*ndir:3),eta(ixi^s)
2941 double precision :: gradeta(ixi^s,1:ndim), bf(ixi^s,1:ndir)
2942
2943 ! Calculating resistive sources involve one extra layer
2944 if (rmhd_4th_order) then
2945 ixa^l=ixo^l^ladd2;
2946 else
2947 ixa^l=ixo^l^ladd1;
2948 end if
2949 if (iximin^d>ixamin^d.or.iximax^d<ixamax^d|.or.) &
2950 call mpistop("Error in add_source_res1: Non-conforming input limits")
2951 ! Calculate current density and idirmin
2952 call get_current(wct,ixi^l,ixo^l,idirmin,current)
2953 if (rmhd_eta>zero)then
2954 eta(ixa^s)=rmhd_eta
2955 gradeta(ixo^s,1:ndim)=zero
2956 else
2957 call usr_special_resistivity(wct,ixi^l,ixa^l,idirmin,x,current,eta)
2958 ! assumes that eta is not function of current?
2959 do idim=1,ndim
2960 call gradient(eta,ixi^l,ixo^l,idim,tmp)
2961 gradeta(ixo^s,idim)=tmp(ixo^s)
2962 end do
2963 end if
2964 if(b0field) then
2965 bf(ixi^s,1:ndir)=wct(ixi^s,mag(1:ndir))+block%B0(ixi^s,1:ndir,0)
2966 else
2967 bf(ixi^s,1:ndir)=wct(ixi^s,mag(1:ndir))
2968 end if
2969 do idir=1,ndir
2970 ! Put B_idir into tmp2 and eta*Laplace B_idir into tmp
2971 if (rmhd_4th_order) then
2972 tmp(ixo^s)=zero
2973 tmp2(ixi^s)=bf(ixi^s,idir)
2974 do idim=1,ndim
2975 lxo^l=ixo^l+2*kr(idim,^d);
2976 jxo^l=ixo^l+kr(idim,^d);
2977 hxo^l=ixo^l-kr(idim,^d);
2978 kxo^l=ixo^l-2*kr(idim,^d);
2979 tmp(ixo^s)=tmp(ixo^s)+&
2980 (-tmp2(lxo^s)+16.0d0*tmp2(jxo^s)-30.0d0*tmp2(ixo^s)+16.0d0*tmp2(hxo^s)-tmp2(kxo^s)) &
2981 /(12.0d0 * dxlevel(idim)**2)
2982 end do
2983 else
2984 tmp(ixo^s)=zero
2985 tmp2(ixi^s)=bf(ixi^s,idir)
2986 do idim=1,ndim
2987 jxo^l=ixo^l+kr(idim,^d);
2988 hxo^l=ixo^l-kr(idim,^d);
2989 tmp(ixo^s)=tmp(ixo^s)+&
2990 (tmp2(jxo^s)-2.0d0*tmp2(ixo^s)+tmp2(hxo^s))/dxlevel(idim)**2
2991 end do
2992 end if
2993 ! Multiply by eta
2994 tmp(ixo^s)=tmp(ixo^s)*eta(ixo^s)
2995 ! Subtract grad(eta) x J = eps_ijk d_j eta J_k if eta is non-constant
2996 if (rmhd_eta<zero)then
2997 do jdir=1,ndim; do kdir=idirmin,3
2998 if (lvc(idir,jdir,kdir)/=0)then
2999 if (lvc(idir,jdir,kdir)==1)then
3000 tmp(ixo^s)=tmp(ixo^s)-gradeta(ixo^s,jdir)*current(ixo^s,kdir)
3001 else
3002 tmp(ixo^s)=tmp(ixo^s)+gradeta(ixo^s,jdir)*current(ixo^s,kdir)
3003 end if
3004 end if
3005 end do; end do
3006 end if
3007 ! Add sources related to eta*laplB-grad(eta) x J to B and e
3008 w(ixo^s,mag(idir))=w(ixo^s,mag(idir))+qdt*tmp(ixo^s)
3009 if(total_energy) then
3010 w(ixo^s,e_)=w(ixo^s,e_)+qdt*tmp(ixo^s)*bf(ixo^s,idir)
3011 end if
3012 end do ! idir
3013 if(rmhd_energy) then
3014 ! de/dt+=eta*J**2
3015 w(ixo^s,e_)=w(ixo^s,e_)+qdt*eta(ixo^s)*sum(current(ixo^s,:)**2,dim=ndim+1)
3016 end if
3017 if (fix_small_values) call rmhd_handle_small_values(.false.,w,x,ixi^l,ixo^l,'add_source_res1')
3018 end subroutine add_source_res1
3019
3020 !> Add resistive source to w within ixO
3021 !> Uses 5 point stencil (2 neighbours) in each direction, conservative
3022 subroutine add_source_res2(qdt,ixI^L,ixO^L,wCT,w,x)
3024 use mod_usr_methods
3025 use mod_geometry
3026 integer, intent(in) :: ixi^l, ixo^l
3027 double precision, intent(in) :: qdt
3028 double precision, intent(in) :: wct(ixi^s,1:nw), x(ixi^s,1:ndim)
3029 double precision, intent(inout) :: w(ixi^s,1:nw)
3030 ! For ndir=2 only 3rd component of J can exist, ndir=1 is impossible for MHD
3031 double precision :: current(ixi^s,7-2*ndir:3),eta(ixi^s),curlj(ixi^s,1:3)
3032 double precision :: tmpvec(ixi^s,1:3),tmp(ixo^s)
3033 integer :: ixa^l,idir,idirmin,idirmin1
3034
3035 ixa^l=ixo^l^ladd2;
3036 if (iximin^d>ixamin^d.or.iximax^d<ixamax^d|.or.) &
3037 call mpistop("Error in add_source_res2: Non-conforming input limits")
3038 ixa^l=ixo^l^ladd1;
3039 ! Calculate current density within ixL: J=curl B, thus J_i=eps_ijk*d_j B_k
3040 ! Determine exact value of idirmin while doing the loop.
3041 call get_current(wct,ixi^l,ixa^l,idirmin,current)
3042 tmpvec=zero
3043 if(rmhd_eta>zero)then
3044 do idir=idirmin,3
3045 tmpvec(ixa^s,idir)=current(ixa^s,idir)*rmhd_eta
3046 end do
3047 else
3048 call usr_special_resistivity(wct,ixi^l,ixa^l,idirmin,x,current,eta)
3049 do idir=idirmin,3
3050 tmpvec(ixa^s,idir)=current(ixa^s,idir)*eta(ixa^s)
3051 end do
3052 end if
3053 ! dB/dt= -curl(J*eta), thus B_i=B_i-eps_ijk d_j Jeta_k
3054 call curlvector(tmpvec,ixi^l,ixo^l,curlj,idirmin1,1,3)
3055 if(stagger_grid) then
3056 if(ndim==2.and.ndir==3) then
3057 ! if 2.5D
3058 w(ixo^s,mag(ndir)) = w(ixo^s,mag(ndir))-qdt*curlj(ixo^s,ndir)
3059 end if
3060 else
3061 w(ixo^s,mag(1:ndir)) = w(ixo^s,mag(1:ndir))-qdt*curlj(ixo^s,1:ndir)
3062 end if
3063 if(rmhd_energy) then
3064 if(rmhd_eta>zero)then
3065 tmp(ixo^s)=qdt*rmhd_eta*sum(current(ixo^s,:)**2,dim=ndim+1)
3066 else
3067 tmp(ixo^s)=qdt*eta(ixo^s)*sum(current(ixo^s,:)**2,dim=ndim+1)
3068 end if
3069 if(total_energy) then
3070 ! de/dt= +div(B x Jeta) = eta J^2 - B dot curl(eta J)
3071 ! de1/dt= eta J^2 - B1 dot curl(eta J)
3072 w(ixo^s,e_)=w(ixo^s,e_)+tmp(ixo^s)-&
3073 qdt*sum(wct(ixo^s,mag(1:ndir))*curlj(ixo^s,1:ndir),dim=ndim+1)
3074 else
3075 ! add eta*J**2 source term in the internal energy equation
3076 w(ixo^s,e_)=w(ixo^s,e_)+tmp(ixo^s)
3077 end if
3078 end if
3079 if (fix_small_values) call rmhd_handle_small_values(.false.,w,x,ixi^l,ixo^l,'add_source_res2')
3080 end subroutine add_source_res2
3081
3082 !> Add Hyper-resistive source to w within ixO
3083 !> Uses 9 point stencil (4 neighbours) in each direction.
3084 subroutine add_source_hyperres(qdt,ixI^L,ixO^L,wCT,w,x)
3086 use mod_geometry
3087 integer, intent(in) :: ixi^l, ixo^l
3088 double precision, intent(in) :: qdt
3089 double precision, intent(in) :: wct(ixi^s,1:nw), x(ixi^s,1:ndim)
3090 double precision, intent(inout) :: w(ixi^s,1:nw)
3091 !.. local ..
3092 double precision :: current(ixi^s,7-2*ndir:3)
3093 double precision :: tmpvec(ixi^s,1:3),tmpvec2(ixi^s,1:3),tmp(ixi^s),ehyper(ixi^s,1:3)
3094 integer :: ixa^l,idir,jdir,kdir,idirmin,idirmin1
3095
3096 ixa^l=ixo^l^ladd3;
3097 if (iximin^d>ixamin^d.or.iximax^d<ixamax^d|.or.) &
3098 call mpistop("Error in add_source_hyperres: Non-conforming input limits")
3099 call get_current(wct,ixi^l,ixa^l,idirmin,current)
3100 tmpvec(ixa^s,1:ndir)=zero
3101 do jdir=idirmin,3
3102 tmpvec(ixa^s,jdir)=current(ixa^s,jdir)
3103 end do
3104 ixa^l=ixo^l^ladd2;
3105 call curlvector(tmpvec,ixi^l,ixa^l,tmpvec2,idirmin1,1,3)
3106 ixa^l=ixo^l^ladd1;
3107 tmpvec(ixa^s,1:ndir)=zero
3108 call curlvector(tmpvec2,ixi^l,ixa^l,tmpvec,idirmin1,1,3)
3109 ehyper(ixa^s,1:ndir) = - tmpvec(ixa^s,1:ndir)*rmhd_eta_hyper
3110 ixa^l=ixo^l;
3111 tmpvec2(ixa^s,1:ndir)=zero
3112 call curlvector(ehyper,ixi^l,ixa^l,tmpvec2,idirmin1,1,3)
3113 do idir=1,ndir
3114 w(ixo^s,mag(idir)) = w(ixo^s,mag(idir))-tmpvec2(ixo^s,idir)*qdt
3115 end do
3116 if(total_energy) then
3117 ! de/dt= +div(B x Ehyper)
3118 ixa^l=ixo^l^ladd1;
3119 tmpvec2(ixa^s,1:ndir)=zero
3120 do idir=1,ndir; do jdir=1,ndir; do kdir=idirmin,3
3121 tmpvec2(ixa^s,idir) = tmpvec(ixa^s,idir)&
3122 + lvc(idir,jdir,kdir)*wct(ixa^s,mag(jdir))*ehyper(ixa^s,kdir)
3123 end do; end do; end do
3124 tmp(ixo^s)=zero
3125 call divvector(tmpvec2,ixi^l,ixo^l,tmp)
3126 w(ixo^s,e_)=w(ixo^s,e_)+tmp(ixo^s)*qdt
3127 end if
3128 if (fix_small_values) call rmhd_handle_small_values(.false.,w,x,ixi^l,ixo^l,'add_source_hyperres')
3129 end subroutine add_source_hyperres
3130
3131 subroutine add_source_glm(qdt,ixI^L,ixO^L,wCT,w,x)
3132 ! Add divB related sources to w within ixO
3133 ! corresponding to Dedner JCP 2002, 175, 645 _equation 24_
3134 ! giving the EGLM-MHD scheme or GLM-MHD scheme
3136 use mod_geometry
3137 integer, intent(in) :: ixi^l, ixo^l
3138 double precision, intent(in) :: qdt, wct(ixi^s,1:nw), x(ixi^s,1:ndim)
3139 double precision, intent(inout) :: w(ixi^s,1:nw)
3140 double precision:: divb(ixi^s), gradpsi(ixi^s), ba(ixo^s,1:ndir)
3141 integer :: idir
3142
3143 ! dPsi/dt = - Ch^2/Cp^2 Psi
3144 if (rmhd_glm_alpha < zero) then
3145 w(ixo^s,psi_) = abs(rmhd_glm_alpha)*wct(ixo^s,psi_)
3146 else
3147 ! implicit update of Psi variable
3148 ! equation (27) in Mignone 2010 J. Com. Phys. 229, 2117
3149 if(slab_uniform) then
3150 w(ixo^s,psi_) = dexp(-qdt*cmax_global*rmhd_glm_alpha/minval(dxlevel(:)))*w(ixo^s,psi_)
3151 else
3152 w(ixo^s,psi_) = dexp(-qdt*cmax_global*rmhd_glm_alpha/minval(block%ds(ixo^s,:),dim=ndim+1))*w(ixo^s,psi_)
3153 end if
3154 end if
3155 if(rmhd_glm_extended) then
3156 if(b0field) then
3157 ba(ixo^s,1:ndir)=wct(ixo^s,mag(1:ndir))+block%B0(ixo^s,1:ndir,0)
3158 else
3159 ba(ixo^s,1:ndir)=wct(ixo^s,mag(1:ndir))
3160 end if
3161 ! gradient of Psi
3162 if(total_energy) then
3163 do idir=1,ndim
3164 select case(typegrad)
3165 case("central")
3166 call gradient(wct(ixi^s,psi_),ixi^l,ixo^l,idir,gradpsi)
3167 case("limited")
3168 call gradientl(wct(ixi^s,psi_),ixi^l,ixo^l,idir,gradpsi)
3169 end select
3170 ! e = e -qdt (b . grad(Psi))
3171 w(ixo^s,e_) = w(ixo^s,e_)-qdt*ba(ixo^s,idir)*gradpsi(ixo^s)
3172 end do
3173 end if
3174 ! We calculate now div B
3175 call get_divb(wct,ixi^l,ixo^l,divb,rmhd_divb_nth)
3176 ! m = m - qdt b div b
3177 do idir=1,ndir
3178 w(ixo^s,mom(idir))=w(ixo^s,mom(idir))-qdt*ba(ixo^s,idir)*divb(ixo^s)
3179 end do
3180 end if
3181 if (fix_small_values) call rmhd_handle_small_values(.false.,w,x,ixi^l,ixo^l,'add_source_glm')
3182 end subroutine add_source_glm
3183
3184 !> Add divB related sources to w within ixO corresponding to Powel
3185 subroutine add_source_powel(qdt,ixI^L,ixO^L,wCT,w,x)
3187 integer, intent(in) :: ixi^l, ixo^l
3188 double precision, intent(in) :: qdt, wct(ixi^s,1:nw), x(ixi^s,1:ndim)
3189 double precision, intent(inout) :: w(ixi^s,1:nw)
3190 double precision :: divb(ixi^s), ba(1:ndir)
3191 integer :: idir, ix^d
3192
3193 ! calculate div B
3194 call get_divb(wct,ixi^l,ixo^l,divb,rmhd_divb_nth)
3195 if(b0field) then
3196 {do ix^db=ixomin^db,ixomax^db\}
3197 ! b = b - qdt v * div b
3198 ^c&w(ix^d,b^c_)=w(ix^d,b^c_)-qdt*wct(ix^d,m^c_)*divb(ix^d)\
3199 ! m = m - qdt b div b
3200 ^c&w(ix^d,m^c_)=w(ix^d,m^c_)-qdt*(wct(ix^d,b^c_)+block%B0(ix^d,^c,0))*divb(ix^d)\
3201 if (total_energy) then
3202 ! e = e - qdt (v . b) * div b
3203 w(ix^d,e_)=w(ix^d,e_)-qdt*(^c&wct(ix^d,m^c_)*(wct(ix^d,b^c_)+block%B0(ix^d,^c,0))+)*divb(ix^d)
3204 end if
3205 {end do\}
3206 else
3207 {do ix^db=ixomin^db,ixomax^db\}
3208 ! b = b - qdt v * div b
3209 ^c&w(ix^d,b^c_)=w(ix^d,b^c_)-qdt*wct(ix^d,m^c_)*divb(ix^d)\
3210 ! m = m - qdt b div b
3211 ^c&w(ix^d,m^c_)=w(ix^d,m^c_)-qdt*wct(ix^d,b^c_)*divb(ix^d)\
3212 if (total_energy) then
3213 ! e = e - qdt (v . b) * div b
3214 w(ix^d,e_)=w(ix^d,e_)-qdt*(^c&wct(ix^d,m^c_)*wct(ix^d,b^c_)+)*divb(ix^d)
3215 end if
3216 {end do\}
3217 end if
3218 if (fix_small_values) call rmhd_handle_small_values(.false.,w,x,ixi^l,ixo^l,'add_source_powel')
3219 end subroutine add_source_powel
3220
3221 subroutine add_source_janhunen(qdt,ixI^L,ixO^L,wCT,w,x)
3222 ! Add divB related sources to w within ixO
3223 ! corresponding to Janhunen, just the term in the induction equation.
3225 integer, intent(in) :: ixi^l, ixo^l
3226 double precision, intent(in) :: qdt, wct(ixi^s,1:nw), x(ixi^s,1:ndim)
3227 double precision, intent(inout) :: w(ixi^s,1:nw)
3228 double precision :: divb(ixi^s)
3229 integer :: idir, ix^d
3230
3231 ! calculate div B
3232 call get_divb(wct,ixi^l,ixo^l,divb,rmhd_divb_nth)
3233 {do ix^db=ixomin^db,ixomax^db\}
3234 ! b = b - qdt v * div b
3235 ^c&w(ix^d,b^c_)=w(ix^d,b^c_)-qdt*wct(ix^d,m^c_)*divb(ix^d)\
3236 {end do\}
3237 if (fix_small_values) call rmhd_handle_small_values(.false.,w,x,ixi^l,ixo^l,'add_source_janhunen')
3238 end subroutine add_source_janhunen
3239
3240 subroutine add_source_linde(qdt,ixI^L,ixO^L,wCT,w,x)
3241 ! Add Linde's divB related sources to wnew within ixO
3243 use mod_geometry
3244 integer, intent(in) :: ixi^l, ixo^l
3245 double precision, intent(in) :: qdt, wct(ixi^s,1:nw), x(ixi^s,1:ndim)
3246 double precision, intent(inout) :: w(ixi^s,1:nw)
3247 double precision :: divb(ixi^s),graddivb(ixi^s)
3248 integer :: idim, idir, ixp^l, i^d, iside
3249 logical, dimension(-1:1^D&) :: leveljump
3250
3251 ! Calculate div B
3252 ixp^l=ixo^l^ladd1;
3253 call get_divb(wct,ixi^l,ixp^l,divb,rmhd_divb_nth)
3254 ! for AMR stability, retreat one cell layer from the boarders of level jump
3255 {do i^db=-1,1\}
3256 if(i^d==0|.and.) cycle
3257 if(neighbor_type(i^d,block%igrid)==2 .or. neighbor_type(i^d,block%igrid)==4) then
3258 leveljump(i^d)=.true.
3259 else
3260 leveljump(i^d)=.false.
3261 end if
3262 {end do\}
3263 ixp^l=ixo^l;
3264 do idim=1,ndim
3265 select case(idim)
3266 {case(^d)
3267 do iside=1,2
3268 i^dd=kr(^dd,^d)*(2*iside-3);
3269 if (leveljump(i^dd)) then
3270 if (iside==1) then
3271 ixpmin^d=ixomin^d-i^d
3272 else
3273 ixpmax^d=ixomax^d-i^d
3274 end if
3275 end if
3276 end do
3277 \}
3278 end select
3279 end do
3280 ! Add Linde's diffusive terms
3281 do idim=1,ndim
3282 ! Calculate grad_idim(divb)
3283 select case(typegrad)
3284 case("central")
3285 call gradient(divb,ixi^l,ixp^l,idim,graddivb)
3286 case("limited")
3287 call gradientl(divb,ixi^l,ixp^l,idim,graddivb)
3288 end select
3289 ! Multiply by Linde's eta*dt = divbdiff*(c_max*dx)*dt = divbdiff*dx**2
3290 if (slab_uniform) then
3291 graddivb(ixp^s)=graddivb(ixp^s)*divbdiff/(^d&1.0d0/dxlevel(^d)**2+)
3292 else
3293 graddivb(ixp^s)=graddivb(ixp^s)*divbdiff &
3294 /(^d&1.0d0/block%ds(ixp^s,^d)**2+)
3295 end if
3296 w(ixp^s,mag(idim))=w(ixp^s,mag(idim))+graddivb(ixp^s)
3297
3298 if (typedivbdiff=='all' .and. total_energy) then
3299 ! e += B_idim*eta*grad_idim(divb)
3300 w(ixp^s,e_)=w(ixp^s,e_)+wct(ixp^s,mag(idim))*graddivb(ixp^s)
3301 end if
3302 end do
3303 if (fix_small_values) call rmhd_handle_small_values(.false.,w,x,ixi^l,ixo^l,'add_source_linde')
3304 end subroutine add_source_linde
3305
3306 !> get dimensionless div B = |divB| * volume / area / |B|
3307 subroutine get_normalized_divb(w,ixI^L,ixO^L,divb)
3309 integer, intent(in) :: ixi^l, ixo^l
3310 double precision, intent(in) :: w(ixi^s,1:nw)
3311 double precision :: divb(ixi^s), dsurface(ixi^s)
3312 double precision :: invb(ixo^s)
3313 integer :: ixa^l,idims
3314
3315 call get_divb(w,ixi^l,ixo^l,divb)
3316 invb(ixo^s)=sqrt(rmhd_mag_en_all(w,ixi^l,ixo^l))
3317 where(invb(ixo^s)/=0.d0)
3318 invb(ixo^s)=1.d0/invb(ixo^s)
3319 end where
3320 if(slab_uniform) then
3321 divb(ixo^s)=0.5d0*abs(divb(ixo^s))*invb(ixo^s)/sum(1.d0/dxlevel(:))
3322 else
3323 ixamin^d=ixomin^d-1;
3324 ixamax^d=ixomax^d-1;
3325 dsurface(ixo^s)= sum(block%surfaceC(ixo^s,:),dim=ndim+1)
3326 do idims=1,ndim
3327 ixa^l=ixo^l-kr(idims,^d);
3328 dsurface(ixo^s)=dsurface(ixo^s)+block%surfaceC(ixa^s,idims)
3329 end do
3330 divb(ixo^s)=abs(divb(ixo^s))*invb(ixo^s)*&
3331 block%dvolume(ixo^s)/dsurface(ixo^s)
3332 end if
3333 end subroutine get_normalized_divb
3334
3335 !> Calculate idirmin and the idirmin:3 components of the common current array
3336 !> make sure that dxlevel(^D) is set correctly.
3337 subroutine get_current(w,ixI^L,ixO^L,idirmin,current)
3339 use mod_geometry
3340 integer, intent(in) :: ixo^l, ixi^l
3341 double precision, intent(in) :: w(ixi^s,1:nw)
3342 integer, intent(out) :: idirmin
3343 ! For ndir=2 only 3rd component of J can exist, ndir=1 is impossible for MHD
3344 double precision :: current(ixi^s,7-2*ndir:3)
3345 integer :: idir, idirmin0
3346
3347 idirmin0 = 7-2*ndir
3348 call curlvector(w(ixi^s,mag(1:ndir)),ixi^l,ixo^l,current,idirmin,idirmin0,ndir)
3349 if(b0field) current(ixo^s,idirmin0:3)=current(ixo^s,idirmin0:3)+&
3350 block%J0(ixo^s,idirmin0:3)
3351 end subroutine get_current
3352
3353 !> If resistivity is not zero, check diffusion time limit for dt
3354 subroutine rmhd_get_dt(w,ixI^L,ixO^L,dtnew,dx^D,x)
3356 use mod_usr_methods
3358 use mod_gravity, only: gravity_get_dt
3359 use mod_cak_force, only: cak_get_dt
3360 use mod_fld, only: fld_radforce_get_dt
3362 integer, intent(in) :: ixi^l, ixo^l
3363 double precision, intent(inout) :: dtnew
3364 double precision, intent(in) :: dx^d
3365 double precision, intent(in) :: w(ixi^s,1:nw)
3366 double precision, intent(in) :: x(ixi^s,1:ndim)
3367 double precision :: dxarr(ndim)
3368 double precision :: current(ixi^s,7-2*ndir:3),eta(ixi^s)
3369 integer :: idirmin,idim
3370
3371 dtnew = bigdouble
3372
3373 if (.not. dt_c) then
3374 ^d&dxarr(^d)=dx^d;
3375 if (rmhd_eta>zero)then
3376 dtnew=dtdiffpar*minval(dxarr(1:ndim))**2/rmhd_eta
3377 else if (rmhd_eta<zero)then
3378 call get_current(w,ixi^l,ixo^l,idirmin,current)
3379 call usr_special_resistivity(w,ixi^l,ixo^l,idirmin,x,current,eta)
3380 dtnew=bigdouble
3381 do idim=1,ndim
3382 if(slab_uniform) then
3383 dtnew=min(dtnew,&
3384 dtdiffpar/(smalldouble+maxval(eta(ixo^s)/dxarr(idim)**2)))
3385 else
3386 dtnew=min(dtnew,&
3387 dtdiffpar/(smalldouble+maxval(eta(ixo^s)/block%ds(ixo^s,idim)**2)))
3388 end if
3389 end do
3390 end if
3391 if(rmhd_eta_hyper>zero) then
3392 if(slab_uniform) then
3393 dtnew=min(dtdiffpar*minval(dxarr(1:ndim))**4/rmhd_eta_hyper,dtnew)
3394 else
3395 dtnew=min(dtdiffpar*minval(block%ds(ixo^s,1:ndim))**4/rmhd_eta_hyper,dtnew)
3396 end if
3397 end if
3398 if(rmhd_radiation_force) then
3399 select case(rmhd_radiation_formalism)
3400 case('fld')
3401 call fld_radforce_get_dt(w,ixi^l,ixo^l,dtnew,dx^d,x)
3402 case('afld')
3403 call afld_radforce_get_dt(w,ixi^l,ixo^l,dtnew,dx^d,x)
3404 case default
3405 call mpistop('Radiation formalism unknown')
3406 end select
3407 endif
3408 if(rmhd_viscosity) then
3409 call viscosity_get_dt(w,ixi^l,ixo^l,dtnew,dx^d,x)
3410 end if
3411 if(rmhd_gravity) then
3412 call gravity_get_dt(w,ixi^l,ixo^l,dtnew,dx^d,x)
3413 end if
3414 if (rmhd_cak_force) then
3415 call cak_get_dt(w,ixi^l,ixo^l,dtnew,dx^d,x)
3416 end if
3417 else
3418 {^ifoned dtnew = dx1*unit_velocity/const_c}
3419 {^nooned dtnew = min(dx^d*unit_velocity/const_c)}
3420 endif
3421 end subroutine rmhd_get_dt
3422
3423 ! Add geometrical source terms to w
3424 subroutine rmhd_add_source_geom(qdt,dtfactor,ixI^L,ixO^L,wCT,wprim,w,x)
3426 use mod_geometry
3427 integer, intent(in) :: ixi^l, ixo^l
3428 double precision, intent(in) :: qdt, dtfactor,x(ixi^s,1:ndim)
3429 double precision, intent(inout) :: wct(ixi^s,1:nw),wprim(ixi^s,1:nw),w(ixi^s,1:nw)
3430 double precision :: tmp,tmp1,invr,cot
3431 integer :: ix^d
3432 integer :: mr_,mphi_ ! Polar var. names
3433 integer :: br_,bphi_
3434
3435 mr_=mom(1); mphi_=mom(1)-1+phi_ ! Polar var. names
3436 br_=mag(1); bphi_=mag(1)-1+phi_
3437 select case (coordinate)
3438 case (cylindrical)
3439 {do ix^db=ixomin^db,ixomax^db\}
3440 ! include dt in invr, invr is always used with qdt
3441 if(local_timestep) then
3442 invr=block%dt(ix^d) * dtfactor/x(ix^d,1)
3443 else
3444 invr=qdt/x(ix^d,1)
3445 end if
3446 if(rmhd_energy) then
3447 tmp=wprim(ix^d,p_)+half*(^c&wprim(ix^d,b^c_)**2+)
3448 else
3449 tmp=rmhd_adiab*wprim(ix^d,rho_)**rmhd_gamma+half*(^c&wprim(ix^d,b^c_)**2+)
3450 end if
3451 if(phi_>0) then
3452 w(ix^d,mr_)=w(ix^d,mr_)+invr*(tmp-&
3453 wprim(ix^d,bphi_)**2+wprim(ix^d,mphi_)*wct(ix^d,mphi_))
3454 w(ix^d,mphi_)=w(ix^d,mphi_)+invr*(&
3455 -wct(ix^d,mphi_)*wprim(ix^d,mr_) &
3456 +wprim(ix^d,bphi_)*wprim(ix^d,br_))
3457 if(.not.stagger_grid) then
3458 w(ix^d,bphi_)=w(ix^d,bphi_)+invr*&
3459 (wprim(ix^d,bphi_)*wprim(ix^d,mr_) &
3460 -wprim(ix^d,br_)*wprim(ix^d,mphi_))
3461 end if
3462 else
3463 w(ix^d,mr_)=w(ix^d,mr_)+invr*tmp
3464 end if
3465 if(rmhd_glm) w(ix^d,br_)=w(ix^d,br_)+wprim(ix^d,psi_)*invr
3466 {end do\}
3467 case (spherical)
3468 {do ix^db=ixomin^db,ixomax^db\}
3469 ! include dt in invr, invr is always used with qdt
3470 if(local_timestep) then
3471 invr=block%dt(ix^d) * dtfactor/x(ix^d,1)
3472 else
3473 invr=qdt/x(ix^d,1)
3474 end if
3475 if(rmhd_energy) then
3476 tmp1=wprim(ix^d,p_)+half*(^c&wprim(ix^d,b^c_)**2+)
3477 else
3478 tmp1=rmhd_adiab*wprim(ix^d,rho_)**rmhd_gamma+half*(^c&wprim(ix^d,b^c_)**2+)
3479 end if
3480 ! m1
3481 {^ifonec
3482 w(ix^d,mom(1))=w(ix^d,mom(1))+two*tmp1*invr
3483 }
3484 {^noonec
3485 w(ix^d,mom(1))=w(ix^d,mom(1))+invr*&
3486 (two*tmp1+(^ce&wprim(ix^d,m^ce_)*wct(ix^d,m^ce_)-wprim(ix^d,b^ce_)**2+))
3487 }
3488 ! b1
3489 if(rmhd_glm) then
3490 w(ix^d,mag(1))=w(ix^d,mag(1))+invr*2.0d0*wprim(ix^d,psi_)
3491 end if
3492 {^ifoned
3493 cot=0.d0
3494 }
3495 {^nooned
3496 cot=1.d0/tan(x(ix^d,2))
3497 }
3498 {^iftwoc
3499 ! m2
3500 w(ix^d,mom(2))=w(ix^d,mom(2))+invr*(tmp1*cot-wprim(ix^d,m1_)*wct(ix^d,m2_)&
3501 +wprim(ix^d,b1_)*wprim(ix^d,b2_))
3502 ! b2
3503 if(.not.stagger_grid) then
3504 tmp=wprim(ix^d,m1_)*wprim(ix^d,b2_)-wprim(ix^d,m2_)*wprim(ix^d,b1_)
3505 if(rmhd_glm) then
3506 tmp=tmp+wprim(ix^d,psi_)*cot
3507 end if
3508 w(ix^d,mag(2))=w(ix^d,mag(2))+tmp*invr
3509 end if
3510 }
3511 {^ifthreec
3512 ! m2
3513 w(ix^d,mom(2))=w(ix^d,mom(2))+invr*(tmp1*cot-wprim(ix^d,m1_)*wct(ix^d,m2_)&
3514 +wprim(ix^d,b1_)*wprim(ix^d,b2_)&
3515 +(wprim(ix^d,m3_)*wct(ix^d,m3_)-wprim(ix^d,b3_)**2)*cot)
3516 ! b2
3517 if(.not.stagger_grid) then
3518 tmp=wprim(ix^d,m1_)*wprim(ix^d,b2_)-wprim(ix^d,m2_)*wprim(ix^d,b1_)
3519 if(rmhd_glm) then
3520 tmp=tmp+wprim(ix^d,psi_)*cot
3521 end if
3522 w(ix^d,mag(2))=w(ix^d,mag(2))+tmp*invr
3523 end if
3524 ! m3
3525 w(ix^d,mom(3))=w(ix^d,mom(3))-invr*&
3526 (wprim(ix^d,m3_)*wct(ix^d,m1_) &
3527 -wprim(ix^d,b3_)*wprim(ix^d,b1_) &
3528 +(wprim(ix^d,m2_)*wct(ix^d,m3_) &
3529 -wprim(ix^d,b2_)*wprim(ix^d,b3_))*cot)
3530 ! b3
3531 if(.not.stagger_grid) then
3532 w(ix^d,mag(3))=w(ix^d,mag(3))+invr*&
3533 (wprim(ix^d,m1_)*wprim(ix^d,b3_) &
3534 -wprim(ix^d,m3_)*wprim(ix^d,b1_) &
3535 -(wprim(ix^d,m3_)*wprim(ix^d,b2_) &
3536 -wprim(ix^d,m2_)*wprim(ix^d,b3_))*cot)
3537 end if
3538 }
3539 {end do\}
3540 end select
3541 end subroutine rmhd_add_source_geom
3542
3543 ! Add geometrical source terms to w
3544 subroutine rmhd_add_source_geom_split(qdt,dtfactor, ixI^L,ixO^L,wCT,wprim,w,x)
3546 use mod_geometry
3547 integer, intent(in) :: ixi^l, ixo^l
3548 double precision, intent(in) :: qdt, dtfactor, x(ixi^s,1:ndim)
3549 double precision, intent(inout) :: wct(ixi^s,1:nw), wprim(ixi^s,1:nw),w(ixi^s,1:nw)
3550 double precision :: tmp(ixi^s),tmp1(ixi^s),tmp2(ixi^s),invrho(ixo^s),invr(ixo^s)
3551 integer :: iw,idir, h1x^l{^nooned, h2x^l}
3552 integer :: mr_,mphi_ ! Polar var. names
3553 integer :: br_,bphi_
3554
3555 mr_=mom(1); mphi_=mom(1)-1+phi_ ! Polar var. names
3556 br_=mag(1); bphi_=mag(1)-1+phi_
3557 if(has_equi_rho0) then
3558 invrho(ixo^s) = 1d0/(wct(ixo^s,rho_) + block%equi_vars(ixo^s,equi_rho0_,b0i))
3559 else
3560 invrho(ixo^s) = 1d0/wct(ixo^s,rho_)
3561 end if
3562 ! include dt in invr, invr is always used with qdt
3563 if(local_timestep) then
3564 invr(ixo^s) = block%dt(ixo^s) * dtfactor/x(ixo^s,1)
3565 else
3566 invr(ixo^s) = qdt/x(ixo^s,1)
3567 end if
3568
3569 select case (coordinate)
3570 case (cylindrical)
3571 call rmhd_get_p_total(wct,x,ixi^l,ixo^l,tmp)
3572 if(phi_>0) then
3573 w(ixo^s,mr_)=w(ixo^s,mr_)+invr(ixo^s)*(tmp(ixo^s)-&
3574 wct(ixo^s,bphi_)**2+wct(ixo^s,mphi_)**2*invrho(ixo^s))
3575 w(ixo^s,mphi_)=w(ixo^s,mphi_)+qdt*invr(ixo^s)*(&
3576 -wct(ixo^s,mphi_)*wct(ixo^s,mr_)*invrho(ixo^s) &
3577 +wct(ixo^s,bphi_)*wct(ixo^s,br_))
3578 if(.not.stagger_grid) then
3579 w(ixo^s,bphi_)=w(ixo^s,bphi_)+invr(ixo^s)*&
3580 (wct(ixo^s,bphi_)*wct(ixo^s,mr_) &
3581 -wct(ixo^s,br_)*wct(ixo^s,mphi_)) &
3582 *invrho(ixo^s)
3583 end if
3584 else
3585 w(ixo^s,mr_)=w(ixo^s,mr_)+invr(ixo^s)*tmp(ixo^s)
3586 end if
3587 if(rmhd_glm) w(ixo^s,br_)=w(ixo^s,br_)+wct(ixo^s,psi_)*invr(ixo^s)
3588 case (spherical)
3589 h1x^l=ixo^l-kr(1,^d); {^nooned h2x^l=ixo^l-kr(2,^d);}
3590 call rmhd_get_p_total(wct,x,ixi^l,ixo^l,tmp1)
3591 tmp(ixo^s)=tmp1(ixo^s)
3592 if(b0field) then
3593 tmp2(ixo^s)=sum(block%B0(ixo^s,:,0)*wct(ixo^s,mag(:)),dim=ndim+1)
3594 tmp(ixo^s)=tmp(ixo^s)+tmp2(ixo^s)
3595 end if
3596 ! m1
3597 tmp(ixo^s)=tmp(ixo^s)*x(ixo^s,1) &
3598 *(block%surfaceC(ixo^s,1)-block%surfaceC(h1x^s,1))/block%dvolume(ixo^s)
3599 if(ndir>1) then
3600 do idir=2,ndir
3601 tmp(ixo^s)=tmp(ixo^s)+wct(ixo^s,mom(idir))**2*invrho(ixo^s)-wct(ixo^s,mag(idir))**2
3602 if(b0field) tmp(ixo^s)=tmp(ixo^s)-2.0d0*block%B0(ixo^s,idir,0)*wct(ixo^s,mag(idir))
3603 end do
3604 end if
3605 w(ixo^s,mom(1))=w(ixo^s,mom(1))+tmp(ixo^s)*invr(ixo^s)
3606 ! b1
3607 if(rmhd_glm) then
3608 w(ixo^s,mag(1))=w(ixo^s,mag(1))+invr(ixo^s)*2.0d0*wct(ixo^s,psi_)
3609 end if
3610 {^nooned
3611 ! m2
3612 tmp(ixo^s)=tmp1(ixo^s)
3613 if(b0field) then
3614 tmp(ixo^s)=tmp(ixo^s)+tmp2(ixo^s)
3615 end if
3616 if(local_timestep) then
3617 tmp1(ixo^s) = block%dt(ixo^s) * tmp(ixo^s)
3618 else
3619 tmp1(ixo^s) = qdt * tmp(ixo^s)
3620 endif
3621 ! This will make hydrostatic p=const an exact solution
3622 w(ixo^s,mom(2))=w(ixo^s,mom(2))+tmp1(ixo^s) &
3623 *(block%surfaceC(ixo^s,2)-block%surfaceC(h2x^s,2)) &
3624 /block%dvolume(ixo^s)
3625 tmp(ixo^s)=-(wct(ixo^s,mom(1))*wct(ixo^s,mom(2))*invrho(ixo^s) &
3626 -wct(ixo^s,mag(1))*wct(ixo^s,mag(2)))
3627 if (b0field) then
3628 tmp(ixo^s)=tmp(ixo^s)+block%B0(ixo^s,1,0)*wct(ixo^s,mag(2)) &
3629 +wct(ixo^s,mag(1))*block%B0(ixo^s,2,0)
3630 end if
3631 if(ndir==3) then
3632 tmp(ixo^s)=tmp(ixo^s)+(wct(ixo^s,mom(3))**2*invrho(ixo^s) &
3633 -wct(ixo^s,mag(3))**2)*dcos(x(ixo^s,2))/dsin(x(ixo^s,2))
3634 if (b0field) then
3635 tmp(ixo^s)=tmp(ixo^s)-2.0d0*block%B0(ixo^s,3,0)*wct(ixo^s,mag(3))&
3636 *dcos(x(ixo^s,2))/dsin(x(ixo^s,2))
3637 end if
3638 end if
3639 w(ixo^s,mom(2))=w(ixo^s,mom(2))+tmp(ixo^s)*invr(ixo^s)
3640 ! b2
3641 if(.not.stagger_grid) then
3642 tmp(ixo^s)=(wct(ixo^s,mom(1))*wct(ixo^s,mag(2)) &
3643 -wct(ixo^s,mom(2))*wct(ixo^s,mag(1)))*invrho(ixo^s)
3644 if(b0field) then
3645 tmp(ixo^s)=tmp(ixo^s)+(wct(ixo^s,mom(1))*block%B0(ixo^s,2,0) &
3646 -wct(ixo^s,mom(2))*block%B0(ixo^s,1,0))*invrho(ixo^s)
3647 end if
3648 if(rmhd_glm) then
3649 tmp(ixo^s)=tmp(ixo^s) &
3650 + dcos(x(ixo^s,2))/dsin(x(ixo^s,2))*wct(ixo^s,psi_)
3651 end if
3652 w(ixo^s,mag(2))=w(ixo^s,mag(2))+tmp(ixo^s)*invr(ixo^s)
3653 end if
3654 }
3655 if(ndir==3) then
3656 ! m3
3657 tmp(ixo^s)=-(wct(ixo^s,mom(3))*wct(ixo^s,mom(1))*invrho(ixo^s) &
3658 -wct(ixo^s,mag(3))*wct(ixo^s,mag(1))) {^nooned &
3659 -(wct(ixo^s,mom(2))*wct(ixo^s,mom(3))*invrho(ixo^s) &
3660 -wct(ixo^s,mag(2))*wct(ixo^s,mag(3))) &
3661 *dcos(x(ixo^s,2))/dsin(x(ixo^s,2)) }
3662 if (b0field) then
3663 tmp(ixo^s)=tmp(ixo^s)+block%B0(ixo^s,1,0)*wct(ixo^s,mag(3)) &
3664 +wct(ixo^s,mag(1))*block%B0(ixo^s,3,0) {^nooned &
3665 +(block%B0(ixo^s,2,0)*wct(ixo^s,mag(3)) &
3666 +wct(ixo^s,mag(2))*block%B0(ixo^s,3,0)) &
3667 *dcos(x(ixo^s,2))/dsin(x(ixo^s,2)) }
3668 end if
3669 w(ixo^s,mom(3))=w(ixo^s,mom(3))+tmp(ixo^s)*invr(ixo^s)
3670 ! b3
3671 if(.not.stagger_grid) then
3672 tmp(ixo^s)=(wct(ixo^s,mom(1))*wct(ixo^s,mag(3)) &
3673 -wct(ixo^s,mom(3))*wct(ixo^s,mag(1)))*invrho(ixo^s) {^nooned &
3674 -(wct(ixo^s,mom(3))*wct(ixo^s,mag(2)) &
3675 -wct(ixo^s,mom(2))*wct(ixo^s,mag(3)))*dcos(x(ixo^s,2)) &
3676 *invrho(ixo^s)/dsin(x(ixo^s,2)) }
3677 if (b0field) then
3678 tmp(ixo^s)=tmp(ixo^s)+(wct(ixo^s,mom(1))*block%B0(ixo^s,3,0) &
3679 -wct(ixo^s,mom(3))*block%B0(ixo^s,1,0))*invrho(ixo^s){^nooned &
3680 -(wct(ixo^s,mom(3))*block%B0(ixo^s,2,0) &
3681 -wct(ixo^s,mom(2))*block%B0(ixo^s,3,0))*dcos(x(ixo^s,2)) &
3682 *invrho(ixo^s)/dsin(x(ixo^s,2)) }
3683 end if
3684 w(ixo^s,mag(3))=w(ixo^s,mag(3))+tmp(ixo^s)*invr(ixo^s)
3685 end if
3686 end if
3687 end select
3688 end subroutine rmhd_add_source_geom_split
3689
3690 !> Compute 2 times total magnetic energy
3691 function rmhd_mag_en_all(w, ixI^L, ixO^L) result(mge)
3693 integer, intent(in) :: ixi^l, ixo^l
3694 double precision, intent(in) :: w(ixi^s, nw)
3695 double precision :: mge(ixo^s)
3696
3697 if (b0field) then
3698 mge = sum((w(ixo^s, mag(:))+block%B0(ixo^s,:,b0i))**2, dim=ndim+1)
3699 else
3700 mge = sum(w(ixo^s, mag(:))**2, dim=ndim+1)
3701 end if
3702 end function rmhd_mag_en_all
3703
3704 subroutine rmhd_modify_wlr(ixI^L,ixO^L,qt,wLC,wRC,wLp,wRp,s,idir)
3706 use mod_usr_methods
3707 integer, intent(in) :: ixi^l, ixo^l, idir
3708 double precision, intent(in) :: qt
3709 double precision, intent(inout) :: wlc(ixi^s,1:nw), wrc(ixi^s,1:nw)
3710 double precision, intent(inout) :: wlp(ixi^s,1:nw), wrp(ixi^s,1:nw)
3711 type(state) :: s
3712 double precision :: db(ixo^s), dpsi(ixo^s)
3713 integer :: ix^d
3714
3715 if(stagger_grid) then
3716 {do ix^db=ixomin^db,ixomax^db\}
3717 wlc(ix^d,mag(idir))=s%ws(ix^d,idir)
3718 wrc(ix^d,mag(idir))=s%ws(ix^d,idir)
3719 wlp(ix^d,mag(idir))=s%ws(ix^d,idir)
3720 wrp(ix^d,mag(idir))=s%ws(ix^d,idir)
3721 {end do\}
3722 else
3723 ! Solve the Riemann problem for the linear 2x2 system for normal
3724 ! B-field and GLM_Psi according to Dedner 2002:
3725 ! This implements eq. (42) in Dedner et al. 2002 JcP 175
3726 ! Gives the Riemann solution on the interface
3727 ! for the normal B component and Psi in the GLM-MHD system.
3728 ! 23/04/2013 Oliver Porth
3729 {do ix^db=ixomin^db,ixomax^db\}
3730 db(ix^d)=wrp(ix^d,mag(idir))-wlp(ix^d,mag(idir))
3731 dpsi(ix^d)=wrp(ix^d,psi_)-wlp(ix^d,psi_)
3732 wlp(ix^d,mag(idir))=half*(wrp(ix^d,mag(idir))+wlp(ix^d,mag(idir))-dpsi(ix^d)/cmax_global)
3733 wlp(ix^d,psi_)=half*(wrp(ix^d,psi_)+wlp(ix^d,psi_)-db(ix^d)*cmax_global)
3734 wrp(ix^d,mag(idir))=wlp(ix^d,mag(idir))
3735 wrp(ix^d,psi_)=wlp(ix^d,psi_)
3736 if(total_energy) then
3737 wrc(ix^d,e_)=wrc(ix^d,e_)-half*wrc(ix^d,mag(idir))**2
3738 wlc(ix^d,e_)=wlc(ix^d,e_)-half*wlc(ix^d,mag(idir))**2
3739 end if
3740 wrc(ix^d,mag(idir))=wlp(ix^d,mag(idir))
3741 wrc(ix^d,psi_)=wlp(ix^d,psi_)
3742 wlc(ix^d,mag(idir))=wlp(ix^d,mag(idir))
3743 wlc(ix^d,psi_)=wlp(ix^d,psi_)
3744 ! modify total energy according to the change of magnetic field
3745 if(total_energy) then
3746 wrc(ix^d,e_)=wrc(ix^d,e_)+half*wrc(ix^d,mag(idir))**2
3747 wlc(ix^d,e_)=wlc(ix^d,e_)+half*wlc(ix^d,mag(idir))**2
3748 end if
3749 {end do\}
3750 end if
3751 if(associated(usr_set_wlr)) call usr_set_wlr(ixi^l,ixo^l,qt,wlc,wrc,wlp,wrp,s,idir)
3752 end subroutine rmhd_modify_wlr
3753
3754 subroutine rmhd_boundary_adjust(igrid,psb)
3756 integer, intent(in) :: igrid
3757 type(state), target :: psb(max_blocks)
3758 integer :: ib, idims, iside, ixo^l, i^d
3759
3760 block=>ps(igrid)
3761 ^d&dxlevel(^d)=rnode(rpdx^d_,igrid);
3762 do idims=1,ndim
3763 ! to avoid using as yet unknown corner info in more than 1D, we
3764 ! fill only interior mesh ranges of the ghost cell ranges at first,
3765 ! and progressively enlarge the ranges to include corners later
3766 do iside=1,2
3767 i^d=kr(^d,idims)*(2*iside-3);
3768 if (neighbor_type(i^d,igrid)/=1) cycle
3769 ib=(idims-1)*2+iside
3770 if(.not.boundary_divbfix(ib)) cycle
3771 if(any(typeboundary(:,ib)==bc_special)) then
3772 ! MF nonlinear force-free B field extrapolation and data driven
3773 ! require normal B of the first ghost cell layer to be untouched by
3774 ! fixdivB=0 process, set boundary_divbfix_skip(iB)=1 in par file
3775 select case (idims)
3776 {case (^d)
3777 if (iside==2) then
3778 ! maximal boundary
3779 ixomin^dd=ixghi^d+1-nghostcells+boundary_divbfix_skip(2*^d)^d%ixOmin^dd=ixglo^dd;
3780 ixomax^dd=ixghi^dd;
3781 else
3782 ! minimal boundary
3783 ixomin^dd=ixglo^dd;
3784 ixomax^dd=ixglo^d-1+nghostcells-boundary_divbfix_skip(2*^d-1)^d%ixOmax^dd=ixghi^dd;
3785 end if \}
3786 end select
3787 call fixdivb_boundary(ixg^ll,ixo^l,psb(igrid)%w,psb(igrid)%x,ib)
3788 end if
3789 end do
3790 end do
3791 end subroutine rmhd_boundary_adjust
3792
3793 subroutine fixdivb_boundary(ixG^L,ixO^L,w,x,iB)
3795 integer, intent(in) :: ixg^l,ixo^l,ib
3796 double precision, intent(inout) :: w(ixg^s,1:nw)
3797 double precision, intent(in) :: x(ixg^s,1:ndim)
3798 double precision :: dx1x2,dx1x3,dx2x1,dx2x3,dx3x1,dx3x2
3799 integer :: ix^d,ixf^l
3800
3801 select case(ib)
3802 case(1)
3803 ! 2nd order CD for divB=0 to set normal B component better
3804 if(total_energy) call rmhd_to_primitive(ixg^l,ixo^l,w,x)
3805 {^iftwod
3806 ixfmin1=ixomin1+1
3807 ixfmax1=ixomax1+1
3808 ixfmin2=ixomin2+1
3809 ixfmax2=ixomax2-1
3810 if(slab_uniform) then
3811 dx1x2=dxlevel(1)/dxlevel(2)
3812 do ix1=ixfmax1,ixfmin1,-1
3813 w(ix1-1,ixfmin2:ixfmax2,mag(1))=w(ix1+1,ixfmin2:ixfmax2,mag(1)) &
3814 +dx1x2*(w(ix1,ixfmin2+1:ixfmax2+1,mag(2))-&
3815 w(ix1,ixfmin2-1:ixfmax2-1,mag(2)))
3816 enddo
3817 else
3818 do ix1=ixfmax1,ixfmin1,-1
3819 w(ix1-1,ixfmin2:ixfmax2,mag(1))=( (w(ix1+1,ixfmin2:ixfmax2,mag(1))+&
3820 w(ix1,ixfmin2:ixfmax2,mag(1)))*block%surfaceC(ix1,ixfmin2:ixfmax2,1)&
3821 +(w(ix1,ixfmin2+1:ixfmax2+1,mag(2))+w(ix1,ixfmin2:ixfmax2,mag(2)))*&
3822 block%surfaceC(ix1,ixfmin2:ixfmax2,2)&
3823 -(w(ix1,ixfmin2:ixfmax2,mag(2))+w(ix1,ixfmin2-1:ixfmax2-1,mag(2)))*&
3824 block%surfaceC(ix1,ixfmin2-1:ixfmax2-1,2) )&
3825 /block%surfaceC(ix1-1,ixfmin2:ixfmax2,1)-w(ix1,ixfmin2:ixfmax2,mag(1))
3826 end do
3827 end if
3828 }
3829 {^ifthreed
3830 ixfmin1=ixomin1+1
3831 ixfmax1=ixomax1+1
3832 ixfmin2=ixomin2+1
3833 ixfmax2=ixomax2-1
3834 ixfmin3=ixomin3+1
3835 ixfmax3=ixomax3-1
3836 if(slab_uniform) then
3837 dx1x2=dxlevel(1)/dxlevel(2)
3838 dx1x3=dxlevel(1)/dxlevel(3)
3839 do ix1=ixfmax1,ixfmin1,-1
3840 w(ix1-1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,mag(1))=&
3841 w(ix1+1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,mag(1)) &
3842 +dx1x2*(w(ix1,ixfmin2+1:ixfmax2+1,ixfmin3:ixfmax3,mag(2))-&
3843 w(ix1,ixfmin2-1:ixfmax2-1,ixfmin3:ixfmax3,mag(2))) &
3844 +dx1x3*(w(ix1,ixfmin2:ixfmax2,ixfmin3+1:ixfmax3+1,mag(3))-&
3845 w(ix1,ixfmin2:ixfmax2,ixfmin3-1:ixfmax3-1,mag(3)))
3846 end do
3847 else
3848 do ix1=ixfmax1,ixfmin1,-1
3849 w(ix1-1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,mag(1))=&
3850 ( (w(ix1+1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,mag(1))+&
3851 w(ix1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,mag(1)))*&
3852 block%surfaceC(ix1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,1)&
3853 +(w(ix1,ixfmin2+1:ixfmax2+1,ixfmin3:ixfmax3,mag(2))+&
3854 w(ix1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,mag(2)))*&
3855 block%surfaceC(ix1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,2)&
3856 -(w(ix1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,mag(2))+&
3857 w(ix1,ixfmin2-1:ixfmax2-1,ixfmin3:ixfmax3,mag(2)))*&
3858 block%surfaceC(ix1,ixfmin2-1:ixfmax2-1,ixfmin3:ixfmax3,2)&
3859 +(w(ix1,ixfmin2:ixfmax2,ixfmin3+1:ixfmax3+1,mag(3))+&
3860 w(ix1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,mag(3)))*&
3861 block%surfaceC(ix1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,3)&
3862 -(w(ix1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,mag(3))+&
3863 w(ix1,ixfmin2:ixfmax2,ixfmin3-1:ixfmax3-1,mag(3)))*&
3864 block%surfaceC(ix1,ixfmin2:ixfmax2,ixfmin3-1:ixfmax3-1,3) )&
3865 /block%surfaceC(ix1-1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,1)-&
3866 w(ix1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,mag(1))
3867 end do
3868 end if
3869 }
3870 if(total_energy) call rmhd_to_conserved(ixg^l,ixo^l,w,x)
3871 case(2)
3872 if(total_energy) call rmhd_to_primitive(ixg^l,ixo^l,w,x)
3873 {^iftwod
3874 ixfmin1=ixomin1-1
3875 ixfmax1=ixomax1-1
3876 ixfmin2=ixomin2+1
3877 ixfmax2=ixomax2-1
3878 if(slab_uniform) then
3879 dx1x2=dxlevel(1)/dxlevel(2)
3880 do ix1=ixfmin1,ixfmax1
3881 w(ix1+1,ixfmin2:ixfmax2,mag(1))=w(ix1-1,ixfmin2:ixfmax2,mag(1)) &
3882 -dx1x2*(w(ix1,ixfmin2+1:ixfmax2+1,mag(2))-&
3883 w(ix1,ixfmin2-1:ixfmax2-1,mag(2)))
3884 enddo
3885 else
3886 do ix1=ixfmin1,ixfmax1
3887 w(ix1+1,ixfmin2:ixfmax2,mag(1))=( (w(ix1-1,ixfmin2:ixfmax2,mag(1))+&
3888 w(ix1,ixfmin2:ixfmax2,mag(1)))*block%surfaceC(ix1-1,ixfmin2:ixfmax2,1)&
3889 -(w(ix1,ixfmin2+1:ixfmax2+1,mag(2))+w(ix1,ixfmin2:ixfmax2,mag(2)))*&
3890 block%surfaceC(ix1,ixfmin2:ixfmax2,2)&
3891 +(w(ix1,ixfmin2:ixfmax2,mag(2))+w(ix1,ixfmin2-1:ixfmax2-1,mag(2)))*&
3892 block%surfaceC(ix1,ixfmin2-1:ixfmax2-1,2) )&
3893 /block%surfaceC(ix1,ixfmin2:ixfmax2,1)-w(ix1,ixfmin2:ixfmax2,mag(1))
3894 end do
3895 end if
3896 }
3897 {^ifthreed
3898 ixfmin1=ixomin1-1
3899 ixfmax1=ixomax1-1
3900 ixfmin2=ixomin2+1
3901 ixfmax2=ixomax2-1
3902 ixfmin3=ixomin3+1
3903 ixfmax3=ixomax3-1
3904 if(slab_uniform) then
3905 dx1x2=dxlevel(1)/dxlevel(2)
3906 dx1x3=dxlevel(1)/dxlevel(3)
3907 do ix1=ixfmin1,ixfmax1
3908 w(ix1+1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,mag(1))=&
3909 w(ix1-1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,mag(1)) &
3910 -dx1x2*(w(ix1,ixfmin2+1:ixfmax2+1,ixfmin3:ixfmax3,mag(2))-&
3911 w(ix1,ixfmin2-1:ixfmax2-1,ixfmin3:ixfmax3,mag(2))) &
3912 -dx1x3*(w(ix1,ixfmin2:ixfmax2,ixfmin3+1:ixfmax3+1,mag(3))-&
3913 w(ix1,ixfmin2:ixfmax2,ixfmin3-1:ixfmax3-1,mag(3)))
3914 end do
3915 else
3916 do ix1=ixfmin1,ixfmax1
3917 w(ix1+1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,mag(1))=&
3918 ( (w(ix1-1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,mag(1))+&
3919 w(ix1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,mag(1)))*&
3920 block%surfaceC(ix1-1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,1)&
3921 -(w(ix1,ixfmin2+1:ixfmax2+1,ixfmin3:ixfmax3,mag(2))+&
3922 w(ix1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,mag(2)))*&
3923 block%surfaceC(ix1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,2)&
3924 +(w(ix1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,mag(2))+&
3925 w(ix1,ixfmin2-1:ixfmax2-1,ixfmin3:ixfmax3,mag(2)))*&
3926 block%surfaceC(ix1,ixfmin2-1:ixfmax2-1,ixfmin3:ixfmax3,2)&
3927 -(w(ix1,ixfmin2:ixfmax2,ixfmin3+1:ixfmax3+1,mag(3))+&
3928 w(ix1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,mag(3)))*&
3929 block%surfaceC(ix1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,3)&
3930 +(w(ix1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,mag(3))+&
3931 w(ix1,ixfmin2:ixfmax2,ixfmin3-1:ixfmax3-1,mag(3)))*&
3932 block%surfaceC(ix1,ixfmin2:ixfmax2,ixfmin3-1:ixfmax3-1,3) )&
3933 /block%surfaceC(ix1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,1)-&
3934 w(ix1,ixfmin2:ixfmax2,ixfmin3:ixfmax3,mag(1))
3935 end do
3936 end if
3937 }
3938 if(total_energy) call rmhd_to_conserved(ixg^l,ixo^l,w,x)
3939 case(3)
3940 if(total_energy) call rmhd_to_primitive(ixg^l,ixo^l,w,x)
3941 {^iftwod
3942 ixfmin1=ixomin1+1
3943 ixfmax1=ixomax1-1
3944 ixfmin2=ixomin2+1
3945 ixfmax2=ixomax2+1
3946 if(slab_uniform) then
3947 dx2x1=dxlevel(2)/dxlevel(1)
3948 do ix2=ixfmax2,ixfmin2,-1
3949 w(ixfmin1:ixfmax1,ix2-1,mag(2))=w(ixfmin1:ixfmax1,ix2+1,mag(2)) &
3950 +dx2x1*(w(ixfmin1+1:ixfmax1+1,ix2,mag(1))-&
3951 w(ixfmin1-1:ixfmax1-1,ix2,mag(1)))
3952 enddo
3953 else
3954 do ix2=ixfmax2,ixfmin2,-1
3955 w(ixfmin1:ixfmax1,ix2-1,mag(2))=( (w(ixfmin1:ixfmax1,ix2+1,mag(2))+&
3956 w(ixfmin1:ixfmax1,ix2,mag(2)))*block%surfaceC(ixfmin1:ixfmax1,ix2,2)&
3957 +(w(ixfmin1+1:ixfmax1+1,ix2,mag(1))+w(ixfmin1:ixfmax1,ix2,mag(1)))*&
3958 block%surfaceC(ixfmin1:ixfmax1,ix2,1)&
3959 -(w(ixfmin1:ixfmax1,ix2,mag(1))+w(ixfmin1-1:ixfmax1-1,ix2,mag(1)))*&
3960 block%surfaceC(ixfmin1-1:ixfmax1-1,ix2,1) )&
3961 /block%surfaceC(ixfmin1:ixfmax1,ix2-1,2)-w(ixfmin1:ixfmax1,ix2,mag(2))
3962 end do
3963 end if
3964 }
3965 {^ifthreed
3966 ixfmin1=ixomin1+1
3967 ixfmax1=ixomax1-1
3968 ixfmin3=ixomin3+1
3969 ixfmax3=ixomax3-1
3970 ixfmin2=ixomin2+1
3971 ixfmax2=ixomax2+1
3972 if(slab_uniform) then
3973 dx2x1=dxlevel(2)/dxlevel(1)
3974 dx2x3=dxlevel(2)/dxlevel(3)
3975 do ix2=ixfmax2,ixfmin2,-1
3976 w(ixfmin1:ixfmax1,ix2-1,ixfmin3:ixfmax3,mag(2))=w(ixfmin1:ixfmax1,&
3977 ix2+1,ixfmin3:ixfmax3,mag(2)) &
3978 +dx2x1*(w(ixfmin1+1:ixfmax1+1,ix2,ixfmin3:ixfmax3,mag(1))-&
3979 w(ixfmin1-1:ixfmax1-1,ix2,ixfmin3:ixfmax3,mag(1))) &
3980 +dx2x3*(w(ixfmin1:ixfmax1,ix2,ixfmin3+1:ixfmax3+1,mag(3))-&
3981 w(ixfmin1:ixfmax1,ix2,ixfmin3-1:ixfmax3-1,mag(3)))
3982 end do
3983 else
3984 do ix2=ixfmax2,ixfmin2,-1
3985 w(ixfmin1:ixfmax1,ix2-1,ixfmin3:ixfmax3,mag(2))=&
3986 ( (w(ixfmin1:ixfmax1,ix2+1,ixfmin3:ixfmax3,mag(2))+&
3987 w(ixfmin1:ixfmax1,ix2,ixfmin3:ixfmax3,mag(2)))*&
3988 block%surfaceC(ixfmin1:ixfmax1,ix2,ixfmin3:ixfmax3,2)&
3989 +(w(ixfmin1+1:ixfmax1+1,ix2,ixfmin3:ixfmax3,mag(1))+&
3990 w(ixfmin1:ixfmax1,ix2,ixfmin3:ixfmax3,mag(1)))*&
3991 block%surfaceC(ixfmin1:ixfmax1,ix2,ixfmin3:ixfmax3,1)&
3992 -(w(ixfmin1:ixfmax1,ix2,ixfmin3:ixfmax3,mag(1))+&
3993 w(ixfmin1-1:ixfmax1-1,ix2,ixfmin3:ixfmax3,mag(1)))*&
3994 block%surfaceC(ixfmin1-1:ixfmax1-1,ix2,ixfmin3:ixfmax3,1)&
3995 +(w(ixfmin1:ixfmax1,ix2,ixfmin3+1:ixfmax3+1,mag(3))+&
3996 w(ixfmin1:ixfmax1,ix2,ixfmin3:ixfmax3,mag(3)))*&
3997 block%surfaceC(ixfmin1:ixfmax1,ix2,ixfmin3:ixfmax3,3)&
3998 -(w(ixfmin1:ixfmax1,ix2,ixfmin3:ixfmax3,mag(3))+&
3999 w(ixfmin1:ixfmax1,ix2,ixfmin3-1:ixfmax3-1,mag(3)))*&
4000 block%surfaceC(ixfmin1:ixfmax1,ix2,ixfmin3-1:ixfmax3-1,3) )&
4001 /block%surfaceC(ixfmin1:ixfmax1,ix2-1,ixfmin3:ixfmax3,2)-&
4002 w(ixfmin1:ixfmax1,ix2,ixfmin3:ixfmax3,mag(2))
4003 end do
4004 end if
4005 }
4006 if(total_energy) call rmhd_to_conserved(ixg^l,ixo^l,w,x)
4007 case(4)
4008 if(total_energy) call rmhd_to_primitive(ixg^l,ixo^l,w,x)
4009 {^iftwod
4010 ixfmin1=ixomin1+1
4011 ixfmax1=ixomax1-1
4012 ixfmin2=ixomin2-1
4013 ixfmax2=ixomax2-1
4014 if(slab_uniform) then
4015 dx2x1=dxlevel(2)/dxlevel(1)
4016 do ix2=ixfmin2,ixfmax2
4017 w(ixfmin1:ixfmax1,ix2+1,mag(2))=w(ixfmin1:ixfmax1,ix2-1,mag(2)) &
4018 -dx2x1*(w(ixfmin1+1:ixfmax1+1,ix2,mag(1))-&
4019 w(ixfmin1-1:ixfmax1-1,ix2,mag(1)))
4020 end do
4021 else
4022 do ix2=ixfmin2,ixfmax2
4023 w(ixfmin1:ixfmax1,ix2+1,mag(2))=( (w(ixfmin1:ixfmax1,ix2-1,mag(2))+&
4024 w(ixfmin1:ixfmax1,ix2,mag(2)))*block%surfaceC(ixfmin1:ixfmax1,ix2-1,2)&
4025 -(w(ixfmin1+1:ixfmax1+1,ix2,mag(1))+w(ixfmin1:ixfmax1,ix2,mag(1)))*&
4026 block%surfaceC(ixfmin1:ixfmax1,ix2,1)&
4027 +(w(ixfmin1:ixfmax1,ix2,mag(1))+w(ixfmin1-1:ixfmax1-1,ix2,mag(1)))*&
4028 block%surfaceC(ixfmin1-1:ixfmax1-1,ix2,1) )&
4029 /block%surfaceC(ixfmin1:ixfmax1,ix2,2)-w(ixfmin1:ixfmax1,ix2,mag(2))
4030 end do
4031 end if
4032 }
4033 {^ifthreed
4034 ixfmin1=ixomin1+1
4035 ixfmax1=ixomax1-1
4036 ixfmin3=ixomin3+1
4037 ixfmax3=ixomax3-1
4038 ixfmin2=ixomin2-1
4039 ixfmax2=ixomax2-1
4040 if(slab_uniform) then
4041 dx2x1=dxlevel(2)/dxlevel(1)
4042 dx2x3=dxlevel(2)/dxlevel(3)
4043 do ix2=ixfmin2,ixfmax2
4044 w(ixfmin1:ixfmax1,ix2+1,ixfmin3:ixfmax3,mag(2))=w(ixfmin1:ixfmax1,&
4045 ix2-1,ixfmin3:ixfmax3,mag(2)) &
4046 -dx2x1*(w(ixfmin1+1:ixfmax1+1,ix2,ixfmin3:ixfmax3,mag(1))-&
4047 w(ixfmin1-1:ixfmax1-1,ix2,ixfmin3:ixfmax3,mag(1))) &
4048 -dx2x3*(w(ixfmin1:ixfmax1,ix2,ixfmin3+1:ixfmax3+1,mag(3))-&
4049 w(ixfmin1:ixfmax1,ix2,ixfmin3-1:ixfmax3-1,mag(3)))
4050 end do
4051 else
4052 do ix2=ixfmin2,ixfmax2
4053 w(ixfmin1:ixfmax1,ix2+1,ixfmin3:ixfmax3,mag(2))=&
4054 ( (w(ixfmin1:ixfmax1,ix2-1,ixfmin3:ixfmax3,mag(2))+&
4055 w(ixfmin1:ixfmax1,ix2,ixfmin3:ixfmax3,mag(2)))*&
4056 block%surfaceC(ixfmin1:ixfmax1,ix2-1,ixfmin3:ixfmax3,2)&
4057 -(w(ixfmin1+1:ixfmax1+1,ix2,ixfmin3:ixfmax3,mag(1))+&
4058 w(ixfmin1:ixfmax1,ix2,ixfmin3:ixfmax3,mag(1)))*&
4059 block%surfaceC(ixfmin1:ixfmax1,ix2,ixfmin3:ixfmax3,1)&
4060 +(w(ixfmin1:ixfmax1,ix2,ixfmin3:ixfmax3,mag(1))+&
4061 w(ixfmin1-1:ixfmax1-1,ix2,ixfmin3:ixfmax3,mag(1)))*&
4062 block%surfaceC(ixfmin1-1:ixfmax1-1,ix2,ixfmin3:ixfmax3,1)&
4063 -(w(ixfmin1:ixfmax1,ix2,ixfmin3+1:ixfmax3+1,mag(3))+&
4064 w(ixfmin1:ixfmax1,ix2,ixfmin3:ixfmax3,mag(3)))*&
4065 block%surfaceC(ixfmin1:ixfmax1,ix2,ixfmin3:ixfmax3,3)&
4066 +(w(ixfmin1:ixfmax1,ix2,ixfmin3:ixfmax3,mag(3))+&
4067 w(ixfmin1:ixfmax1,ix2,ixfmin3-1:ixfmax3-1,mag(3)))*&
4068 block%surfaceC(ixfmin1:ixfmax1,ix2,ixfmin3-1:ixfmax3-1,3) )&
4069 /block%surfaceC(ixfmin1:ixfmax1,ix2,ixfmin3:ixfmax3,2)-&
4070 w(ixfmin1:ixfmax1,ix2,ixfmin3:ixfmax3,mag(2))
4071 end do
4072 end if
4073 }
4074 if(total_energy) call rmhd_to_conserved(ixg^l,ixo^l,w,x)
4075 {^ifthreed
4076 case(5)
4077 if(total_energy) call rmhd_to_primitive(ixg^l,ixo^l,w,x)
4078 ixfmin1=ixomin1+1
4079 ixfmax1=ixomax1-1
4080 ixfmin2=ixomin2+1
4081 ixfmax2=ixomax2-1
4082 ixfmin3=ixomin3+1
4083 ixfmax3=ixomax3+1
4084 if(slab_uniform) then
4085 dx3x1=dxlevel(3)/dxlevel(1)
4086 dx3x2=dxlevel(3)/dxlevel(2)
4087 do ix3=ixfmax3,ixfmin3,-1
4088 w(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3-1,mag(3))=w(ixfmin1:ixfmax1,&
4089 ixfmin2:ixfmax2,ix3+1,mag(3)) &
4090 +dx3x1*(w(ixfmin1+1:ixfmax1+1,ixfmin2:ixfmax2,ix3,mag(1))-&
4091 w(ixfmin1-1:ixfmax1-1,ixfmin2:ixfmax2,ix3,mag(1))) &
4092 +dx3x2*(w(ixfmin1:ixfmax1,ixfmin2+1:ixfmax2+1,ix3,mag(2))-&
4093 w(ixfmin1:ixfmax1,ixfmin2-1:ixfmax2-1,ix3,mag(2)))
4094 end do
4095 else
4096 do ix3=ixfmax3,ixfmin3,-1
4097 w(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3-1,mag(3))=&
4098 ( (w(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3+1,mag(3))+&
4099 w(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3,mag(3)))*&
4100 block%surfaceC(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3,3)&
4101 +(w(ixfmin1+1:ixfmax1+1,ixfmin2:ixfmax2,ix3,mag(1))+&
4102 w(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3,mag(1)))*&
4103 block%surfaceC(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3,1)&
4104 -(w(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3,mag(1))+&
4105 w(ixfmin1-1:ixfmax1-1,ixfmin2:ixfmax2,ix3,mag(1)))*&
4106 block%surfaceC(ixfmin1-1:ixfmax1-1,ixfmin2:ixfmax2,ix3,1)&
4107 +(w(ixfmin1:ixfmax1,ixfmin2+1:ixfmax2+1,ix3,mag(2))+&
4108 w(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3,mag(2)))*&
4109 block%surfaceC(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3,2)&
4110 -(w(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3,mag(2))+&
4111 w(ixfmin1:ixfmax1,ixfmin2-1:ixfmax2-1,ix3,mag(2)))*&
4112 block%surfaceC(ixfmin1:ixfmax1,ixfmin2-1:ixfmax2-1,ix3,2) )&
4113 /block%surfaceC(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3-1,3)-&
4114 w(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3,mag(3))
4115 end do
4116 end if
4117 if(total_energy) call rmhd_to_conserved(ixg^l,ixo^l,w,x)
4118 case(6)
4119 if(total_energy) call rmhd_to_primitive(ixg^l,ixo^l,w,x)
4120 ixfmin1=ixomin1+1
4121 ixfmax1=ixomax1-1
4122 ixfmin2=ixomin2+1
4123 ixfmax2=ixomax2-1
4124 ixfmin3=ixomin3-1
4125 ixfmax3=ixomax3-1
4126 if(slab_uniform) then
4127 dx3x1=dxlevel(3)/dxlevel(1)
4128 dx3x2=dxlevel(3)/dxlevel(2)
4129 do ix3=ixfmin3,ixfmax3
4130 w(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3+1,mag(3))=w(ixfmin1:ixfmax1,&
4131 ixfmin2:ixfmax2,ix3-1,mag(3)) &
4132 -dx3x1*(w(ixfmin1+1:ixfmax1+1,ixfmin2:ixfmax2,ix3,mag(1))-&
4133 w(ixfmin1-1:ixfmax1-1,ixfmin2:ixfmax2,ix3,mag(1))) &
4134 -dx3x2*(w(ixfmin1:ixfmax1,ixfmin2+1:ixfmax2+1,ix3,mag(2))-&
4135 w(ixfmin1:ixfmax1,ixfmin2-1:ixfmax2-1,ix3,mag(2)))
4136 end do
4137 else
4138 do ix3=ixfmin3,ixfmax3
4139 w(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3+1,mag(3))=&
4140 ( (w(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3-1,mag(3))+&
4141 w(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3,mag(3)))*&
4142 block%surfaceC(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3-1,3)&
4143 -(w(ixfmin1+1:ixfmax1+1,ixfmin2:ixfmax2,ix3,mag(1))+&
4144 w(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3,mag(1)))*&
4145 block%surfaceC(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3,1)&
4146 +(w(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3,mag(1))+&
4147 w(ixfmin1-1:ixfmax1-1,ixfmin2:ixfmax2,ix3,mag(1)))*&
4148 block%surfaceC(ixfmin1-1:ixfmax1-1,ixfmin2:ixfmax2,ix3,1)&
4149 -(w(ixfmin1:ixfmax1,ixfmin2+1:ixfmax2+1,ix3,mag(2))+&
4150 w(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3,mag(2)))*&
4151 block%surfaceC(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3,2)&
4152 +(w(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3,mag(2))+&
4153 w(ixfmin1:ixfmax1,ixfmin2-1:ixfmax2-1,ix3,mag(2)))*&
4154 block%surfaceC(ixfmin1:ixfmax1,ixfmin2-1:ixfmax2-1,ix3,2) )&
4155 /block%surfaceC(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3,3)-&
4156 w(ixfmin1:ixfmax1,ixfmin2:ixfmax2,ix3,mag(3))
4157 end do
4158 end if
4159 if(total_energy) call rmhd_to_conserved(ixg^l,ixo^l,w,x)
4160 }
4161 case default
4162 call mpistop("Special boundary is not defined for this region")
4163 end select
4164 end subroutine fixdivb_boundary
4165
4166 {^nooned
4167 subroutine rmhd_clean_divb_multigrid(qdt, qt, active)
4168 use mod_forest
4171 use mod_geometry
4172 double precision, intent(in) :: qdt !< Current time step
4173 double precision, intent(in) :: qt !< Current time
4174 logical, intent(inout) :: active !< Output if the source is active
4175 integer :: id
4176 integer, parameter :: max_its = 50
4177 double precision :: residual_it(max_its), max_divb
4178 double precision :: tmp(ixg^t), grad(ixg^t, ndim)
4179 double precision :: res
4180 double precision, parameter :: max_residual = 1d-3
4181 double precision, parameter :: residual_reduction = 1d-10
4182 integer :: iigrid, igrid
4183 integer :: n, nc, lvl, ix^l, ixc^l, idim
4184 type(tree_node), pointer :: pnode
4185
4186 mg%operator_type = mg_laplacian
4187 ! Set boundary conditions
4188 do n = 1, 2*ndim
4189 idim = (n+1)/2
4190 select case (typeboundary(mag(idim), n))
4191 case (bc_symm)
4192 ! d/dx B = 0, take phi = 0
4193 mg%bc(n, mg_iphi)%bc_type = mg_bc_dirichlet
4194 mg%bc(n, mg_iphi)%bc_value = 0.0_dp
4195 case (bc_asymm)
4196 ! B = 0, so grad(phi) = 0
4197 mg%bc(n, mg_iphi)%bc_type = mg_bc_neumann
4198 mg%bc(n, mg_iphi)%bc_value = 0.0_dp
4199 case (bc_cont)
4200 mg%bc(n, mg_iphi)%bc_type = mg_bc_dirichlet
4201 mg%bc(n, mg_iphi)%bc_value = 0.0_dp
4202 case (bc_special)
4203 ! Assume Dirichlet boundary conditions, derivative zero
4204 mg%bc(n, mg_iphi)%bc_type = mg_bc_dirichlet
4205 mg%bc(n, mg_iphi)%bc_value = 0.0_dp
4206 case (bc_periodic)
4207 ! Nothing to do here
4208 case default
4209 write(*,*) "rmhd_clean_divb_multigrid warning: unknown boundary type"
4210 mg%bc(n, mg_iphi)%bc_type = mg_bc_dirichlet
4211 mg%bc(n, mg_iphi)%bc_value = 0.0_dp
4212 end select
4213 end do
4214
4215 ix^l=ixm^ll^ladd1;
4216 max_divb = 0.0d0
4217 ! Store divergence of B as right-hand side
4218 do iigrid = 1, igridstail
4219 igrid = igrids(iigrid);
4220 pnode => igrid_to_node(igrid, mype)%node
4221 id = pnode%id
4222 lvl = mg%boxes(id)%lvl
4223 nc = mg%box_size_lvl(lvl)
4224
4225 ! Geometry subroutines expect this to be set
4226 block => ps(igrid)
4227 ^d&dxlevel(^d)=rnode(rpdx^d_,igrid);
4228
4229 call get_divb(ps(igrid)%w(ixg^t, 1:nw), ixg^ll, ixm^ll, tmp, &
4231 mg%boxes(id)%cc({1:nc}, mg_irhs) = tmp(ixm^t)
4232 max_divb = max(max_divb, maxval(abs(tmp(ixm^t))))
4233 end do
4234
4235 ! Solve laplacian(phi) = divB
4236 if(stagger_grid) then
4237 call mpi_allreduce(mpi_in_place, max_divb, 1, mpi_double_precision, &
4238 mpi_max, icomm, ierrmpi)
4239
4240 if (mype == 0) print *, "Performing multigrid divB cleaning"
4241 if (mype == 0) print *, "iteration vs residual"
4242 ! Solve laplacian(phi) = divB
4243 do n = 1, max_its
4244 call mg_fas_fmg(mg, n>1, max_res=residual_it(n))
4245 if (mype == 0) write(*, "(I4,E11.3)") n, residual_it(n)
4246 if (residual_it(n) < residual_reduction * max_divb) exit
4247 end do
4248 if (mype == 0 .and. n > max_its) then
4249 print *, "divb_multigrid warning: not fully converged"
4250 print *, "current amplitude of divb: ", residual_it(max_its)
4251 print *, "multigrid smallest grid: ", &
4252 mg%domain_size_lvl(:, mg%lowest_lvl)
4253 print *, "note: smallest grid ideally has <= 8 cells"
4254 print *, "multigrid dx/dy/dz ratio: ", mg%dr(:, 1)/mg%dr(1, 1)
4255 print *, "note: dx/dy/dz should be similar"
4256 end if
4257 else
4258 do n = 1, max_its
4259 call mg_fas_vcycle(mg, max_res=res)
4260 if (res < max_residual) exit
4261 end do
4262 if (res > max_residual) call mpistop("divb_multigrid: no convergence")
4263 end if
4264
4265 ! Correct the magnetic field
4266 do iigrid = 1, igridstail
4267 igrid = igrids(iigrid);
4268 pnode => igrid_to_node(igrid, mype)%node
4269 id = pnode%id
4270 ! Geometry subroutines expect this to be set
4271 block => ps(igrid)
4272 ^d&dxlevel(^d)=rnode(rpdx^d_,igrid);
4273 ! Compute the gradient of phi
4274 tmp(ix^s) = mg%boxes(id)%cc({:,}, mg_iphi)
4275 if(stagger_grid) then
4276 do idim =1, ndim
4277 ixcmin^d=ixmlo^d-kr(idim,^d);
4278 ixcmax^d=ixmhi^d;
4279 call gradientf(tmp,ps(igrid)%x,ixg^ll,ixc^l,idim,grad(ixg^t,idim))
4280 ! Apply the correction B* = B - gradient(phi)
4281 ps(igrid)%ws(ixc^s,idim)=ps(igrid)%ws(ixc^s,idim)-grad(ixc^s,idim)
4282 end do
4283 ! store cell-center magnetic energy
4284 tmp(ixm^t) = sum(ps(igrid)%w(ixm^t, mag(1:ndim))**2, dim=ndim+1)
4285 ! change cell-center magnetic field
4286 call rmhd_face_to_center(ixm^ll,ps(igrid))
4287 else
4288 do idim = 1, ndim
4289 call gradient(tmp,ixg^ll,ixm^ll,idim,grad(ixg^t, idim))
4290 end do
4291 ! store cell-center magnetic energy
4292 tmp(ixm^t) = sum(ps(igrid)%w(ixm^t, mag(1:ndim))**2, dim=ndim+1)
4293 ! Apply the correction B* = B - gradient(phi)
4294 ps(igrid)%w(ixm^t, mag(1:ndim)) = &
4295 ps(igrid)%w(ixm^t, mag(1:ndim)) - grad(ixm^t, :)
4296 end if
4297 if(total_energy) then
4298 ! Determine magnetic energy difference
4299 tmp(ixm^t) = 0.5_dp * (sum(ps(igrid)%w(ixm^t, &
4300 mag(1:ndim))**2, dim=ndim+1) - tmp(ixm^t))
4301 ! Keep thermal pressure the same
4302 ps(igrid)%w(ixm^t, e_) = ps(igrid)%w(ixm^t, e_) + tmp(ixm^t)
4303 end if
4304 end do
4305 active = .true.
4306 end subroutine rmhd_clean_divb_multigrid
4307 }
4308
4309 !> get electric field though averaging neighors to update faces in CT
4310 subroutine rmhd_update_faces_average(ixI^L,ixO^L,qt,qdt,wp,fC,fE,sCT,s,vcts)
4312 use mod_usr_methods
4313
4314 integer, intent(in) :: ixi^l, ixo^l
4315 double precision, intent(in) :: qt,qdt
4316 ! cell-center primitive variables
4317 double precision, intent(in) :: wp(ixi^s,1:nw)
4318 type(state) :: sct, s
4319 type(ct_velocity) :: vcts
4320 double precision, intent(in) :: fc(ixi^s,1:nwflux,1:ndim)
4321 double precision, intent(inout) :: fe(ixi^s,sdim:3)
4322
4323 double precision :: circ(ixi^s,1:ndim)
4324 ! non-ideal electric field on cell edges
4325 double precision, dimension(ixI^S,sdim:3) :: e_resi
4326 integer :: ix^d,ixc^l,ixa^l,i1kr^d,i2kr^d
4327 integer :: idim1,idim2,idir,iwdim1,iwdim2
4328
4329 associate(bfaces=>s%ws,x=>s%x)
4330
4331 ! Calculate contribution to FEM of each edge,
4332 ! that is, estimate value of line integral of
4333 ! electric field in the positive idir direction.
4334
4335 ! if there is resistivity, get eta J
4336 if(rmhd_eta/=zero) call get_resistive_electric_field(ixi^l,ixo^l,wp,sct,s,e_resi)
4337
4338 do idim1=1,ndim
4339 iwdim1 = mag(idim1)
4340 i1kr^d=kr(idim1,^d);
4341 do idim2=1,ndim
4342 iwdim2 = mag(idim2)
4343 i2kr^d=kr(idim2,^d);
4344 do idir=sdim,3! Direction of line integral
4345 ! Allow only even permutations
4346 if (lvc(idim1,idim2,idir)==1) then
4347 ixcmax^d=ixomax^d;
4348 ixcmin^d=ixomin^d+kr(idir,^d)-1;
4349 ! average cell-face electric field to cell edges
4350 {do ix^db=ixcmin^db,ixcmax^db\}
4351 fe(ix^d,idir)=quarter*&
4352 (fc(ix^d,iwdim1,idim2)+fc({ix^d+i1kr^d},iwdim1,idim2)&
4353 -fc(ix^d,iwdim2,idim1)-fc({ix^d+i2kr^d},iwdim2,idim1))
4354 ! add resistive electric field at cell edges E=-vxB+eta J
4355 if(rmhd_eta/=zero) fe(ix^d,idir)=fe(ix^d,idir)+e_resi(ix^d,idir)
4356 ! times time step and edge length
4357 fe(ix^d,idir)=fe(ix^d,idir)*qdt*s%dsC(ix^d,idir)
4358 {end do\}
4359 end if
4360 end do
4361 end do
4362 end do
4363
4364 ! allow user to change inductive electric field, especially for boundary driven applications
4365 if(associated(usr_set_electric_field)) &
4366 call usr_set_electric_field(ixi^l,ixo^l,qt,qdt,fe,sct)
4367
4368 circ(ixi^s,1:ndim)=zero
4369
4370 ! Calculate circulation on each face
4371 do idim1=1,ndim ! Coordinate perpendicular to face
4372 ixcmax^d=ixomax^d;
4373 ixcmin^d=ixomin^d-kr(idim1,^d);
4374 do idim2=1,ndim
4375 ixa^l=ixc^l-kr(idim2,^d);
4376 do idir=sdim,3 ! Direction of line integral
4377 ! Assemble indices
4378 if(lvc(idim1,idim2,idir)==1) then
4379 ! Add line integrals in direction idir
4380 circ(ixc^s,idim1)=circ(ixc^s,idim1)&
4381 +(fe(ixc^s,idir)&
4382 -fe(ixa^s,idir))
4383 else if(lvc(idim1,idim2,idir)==-1) then
4384 ! Add line integrals in direction idir
4385 circ(ixc^s,idim1)=circ(ixc^s,idim1)&
4386 -(fe(ixc^s,idir)&
4387 -fe(ixa^s,idir))
4388 end if
4389 end do
4390 end do
4391 {do ix^db=ixcmin^db,ixcmax^db\}
4392 ! Divide by the area of the face to get dB/dt
4393 if(s%surfaceC(ix^d,idim1) > smalldouble) then
4394 ! Time update cell-face magnetic field component
4395 bfaces(ix^d,idim1)=bfaces(ix^d,idim1)-circ(ix^d,idim1)/s%surfaceC(ix^d,idim1)
4396 end if
4397 {end do\}
4398 end do
4399
4400 end associate
4401
4402 end subroutine rmhd_update_faces_average
4403
4404 !> update faces using UCT contact mode by Gardiner and Stone 2005 JCP 205, 509
4405 subroutine rmhd_update_faces_contact(ixI^L,ixO^L,qt,qdt,wp,fC,fE,sCT,s,vcts)
4407 use mod_usr_methods
4408 use mod_geometry
4409
4410 integer, intent(in) :: ixi^l, ixo^l
4411 double precision, intent(in) :: qt, qdt
4412 ! cell-center primitive variables
4413 double precision, intent(in) :: wp(ixi^s,1:nw)
4414 type(state) :: sct, s
4415 type(ct_velocity) :: vcts
4416 double precision, intent(in) :: fc(ixi^s,1:nwflux,1:ndim)
4417 double precision, intent(inout) :: fe(ixi^s,sdim:3)
4418
4419 double precision :: circ(ixi^s,1:ndim)
4420 ! electric field at cell centers
4421 double precision :: ecc(ixi^s,sdim:3)
4422 double precision :: ein(ixi^s,sdim:3)
4423 ! gradient of E at left and right side of a cell face
4424 double precision :: el(ixi^s),er(ixi^s)
4425 ! gradient of E at left and right side of a cell corner
4426 double precision :: elc,erc
4427 ! non-ideal electric field on cell edges
4428 double precision, dimension(ixI^S,sdim:3) :: e_resi
4429 ! current on cell edges
4430 double precision :: jce(ixi^s,sdim:3)
4431 ! location at cell faces
4432 double precision :: xs(ixgs^t,1:ndim)
4433 double precision :: gradi(ixgs^t)
4434 integer :: ixc^l,ixa^l
4435 integer :: idim1,idim2,idir,iwdim1,iwdim2,ix^d,i1kr^d,i2kr^d
4436
4437 associate(bfaces=>s%ws,x=>s%x,w=>s%w,vnorm=>vcts%vnorm,wcts=>sct%ws)
4438
4439 ! if there is resistivity, get eta J
4440 if(rmhd_eta/=zero) call get_resistive_electric_field(ixi^l,ixo^l,wp,sct,s,e_resi)
4441
4442 if(b0field) then
4443 {do ix^db=iximin^db,iximax^db\}
4444 ! Calculate electric field at cell centers
4445 {^ifthreed
4446 ecc(ix^d,1)=(wp(ix^d,b2_)+block%B0(ix^d,2,0))*wp(ix^d,m3_)-(wp(ix^d,b3_)+block%B0(ix^d,3,0))*wp(ix^d,m2_)
4447 ecc(ix^d,2)=(wp(ix^d,b3_)+block%B0(ix^d,3,0))*wp(ix^d,m1_)-(wp(ix^d,b1_)+block%B0(ix^d,1,0))*wp(ix^d,m3_)
4448 ecc(ix^d,3)=(wp(ix^d,b1_)+block%B0(ix^d,1,0))*wp(ix^d,m2_)-(wp(ix^d,b2_)+block%B0(ix^d,2,0))*wp(ix^d,m1_)
4449 }
4450 {^iftwod
4451 ecc(ix^d,3)=wp(ix^d,b1_)*wp(ix^d,m2_)-wp(ix^d,b2_)*wp(ix^d,m1_)
4452 }
4453 {^ifoned
4454 ecc(ix^d,3)=0.d0
4455 }
4456 {end do\}
4457 else
4458 {do ix^db=iximin^db,iximax^db\}
4459 ! Calculate electric field at cell centers
4460 {^ifthreed
4461 ecc(ix^d,1)=wp(ix^d,b2_)*wp(ix^d,m3_)-wp(ix^d,b3_)*wp(ix^d,m2_)
4462 ecc(ix^d,2)=wp(ix^d,b3_)*wp(ix^d,m1_)-wp(ix^d,b1_)*wp(ix^d,m3_)
4463 ecc(ix^d,3)=wp(ix^d,b1_)*wp(ix^d,m2_)-wp(ix^d,b2_)*wp(ix^d,m1_)
4464 }
4465 {^iftwod
4466 ecc(ix^d,3)=wp(ix^d,b1_)*wp(ix^d,m2_)-wp(ix^d,b2_)*wp(ix^d,m1_)
4467 }
4468 {^ifoned
4469 ecc(ix^d,3)=0.d0
4470 }
4471 {end do\}
4472 end if
4473
4474 ! Calculate contribution to FEM of each edge,
4475 ! that is, estimate value of line integral of
4476 ! electric field in the positive idir direction.
4477 ! evaluate electric field along cell edges according to equation (41)
4478 do idim1=1,ndim
4479 iwdim1 = mag(idim1)
4480 i1kr^d=kr(idim1,^d);
4481 do idim2=1,ndim
4482 iwdim2 = mag(idim2)
4483 i2kr^d=kr(idim2,^d);
4484 do idir=sdim,3 ! Direction of line integral
4485 ! Allow only even permutations
4486 if (lvc(idim1,idim2,idir)==1) then
4487 ixcmax^d=ixomax^d;
4488 ixcmin^d=ixomin^d+kr(idir,^d)-1;
4489 ! Assemble indices
4490 ! average cell-face electric field to cell edges
4491 {do ix^db=ixcmin^db,ixcmax^db\}
4492 fe(ix^d,idir)=quarter*&
4493 (fc(ix^d,iwdim1,idim2)+fc({ix^d+i1kr^d},iwdim1,idim2)&
4494 -fc(ix^d,iwdim2,idim1)-fc({ix^d+i2kr^d},iwdim2,idim1))
4495 if(partial_energy) ein(ix^d,idir)=fe(ix^d,idir)
4496 {end do\}
4497 ! add slope in idim2 direction from equation (50)
4498 ixamin^d=ixcmin^d;
4499 ixamax^d=ixcmax^d+i1kr^d;
4500 {do ix^db=ixamin^db,ixamax^db\}
4501 el(ix^d)=fc(ix^d,iwdim1,idim2)-ecc(ix^d,idir)
4502 er(ix^d)=fc(ix^d,iwdim1,idim2)-ecc({ix^d+i2kr^d},idir)
4503 {end do\}
4504 {!dir$ ivdep
4505 do ix^db=ixcmin^db,ixcmax^db\}
4506 if(vnorm(ix^d,idim1)>0.d0) then
4507 elc=el(ix^d)
4508 else if(vnorm(ix^d,idim1)<0.d0) then
4509 elc=el({ix^d+i1kr^d})
4510 else
4511 elc=0.5d0*(el(ix^d)+el({ix^d+i1kr^d}))
4512 end if
4513 if(vnorm({ix^d+i2kr^d},idim1)>0.d0) then
4514 erc=er(ix^d)
4515 else if(vnorm({ix^d+i2kr^d},idim1)<0.d0) then
4516 erc=er({ix^d+i1kr^d})
4517 else
4518 erc=0.5d0*(er(ix^d)+er({ix^d+i1kr^d}))
4519 end if
4520 fe(ix^d,idir)=fe(ix^d,idir)+0.25d0*(elc+erc)
4521 {end do\}
4522
4523 ! add slope in idim1 direction from equation (50)
4524 ixamin^d=ixcmin^d;
4525 ixamax^d=ixcmax^d+i2kr^d;
4526 {do ix^db=ixamin^db,ixamax^db\}
4527 el(ix^d)=-fc(ix^d,iwdim2,idim1)-ecc(ix^d,idir)
4528 er(ix^d)=-fc(ix^d,iwdim2,idim1)-ecc({ix^d+i1kr^d},idir)
4529 {end do\}
4530 {!dir$ ivdep
4531 do ix^db=ixcmin^db,ixcmax^db\}
4532 if(vnorm(ix^d,idim2)>0.d0) then
4533 elc=el(ix^d)
4534 else if(vnorm(ix^d,idim2)<0.d0) then
4535 elc=el({ix^d+i2kr^d})
4536 else
4537 elc=0.5d0*(el(ix^d)+el({ix^d+i2kr^d}))
4538 end if
4539 if(vnorm({ix^d+i1kr^d},idim2)>0.d0) then
4540 erc=er(ix^d)
4541 else if(vnorm({ix^d+i1kr^d},idim2)<0.d0) then
4542 erc=er({ix^d+i2kr^d})
4543 else
4544 erc=0.5d0*(er(ix^d)+er({ix^d+i2kr^d}))
4545 end if
4546 fe(ix^d,idir)=fe(ix^d,idir)+0.25d0*(elc+erc)
4547 ! difference between average and upwind interpolated E
4548 if(partial_energy) ein(ix^d,idir)=fe(ix^d,idir)-ein(ix^d,idir)
4549 ! add resistive electric field at cell edges E=-vxB+eta J
4550 if(rmhd_eta/=zero) fe(ix^d,idir)=fe(ix^d,idir)+e_resi(ix^d,idir)
4551 ! times time step and edge length
4552 fe(ix^d,idir)=fe(ix^d,idir)*qdt*s%dsC(ix^d,idir)
4553 {end do\}
4554 end if
4555 end do
4556 end do
4557 end do
4558
4559 if(partial_energy) then
4560 ! add upwind diffused magnetic energy back to energy
4561 ! calculate current density at cell edges
4562 jce=0.d0
4563 do idim1=1,ndim
4564 do idim2=1,ndim
4565 do idir=sdim,3
4566 if (lvc(idim1,idim2,idir)==0) cycle
4567 ixcmax^d=ixomax^d;
4568 ixcmin^d=ixomin^d+kr(idir,^d)-1;
4569 ixamax^d=ixcmax^d-kr(idir,^d)+1;
4570 ixamin^d=ixcmin^d;
4571 ! current at transverse faces
4572 xs(ixa^s,:)=x(ixa^s,:)
4573 xs(ixa^s,idim2)=x(ixa^s,idim2)+half*s%dx(ixa^s,idim2)
4574 call gradientf(wcts(ixgs^t,idim2),xs,ixgs^ll,ixc^l,idim1,gradi)
4575 if (lvc(idim1,idim2,idir)==1) then
4576 jce(ixc^s,idir)=jce(ixc^s,idir)+gradi(ixc^s)
4577 else
4578 jce(ixc^s,idir)=jce(ixc^s,idir)-gradi(ixc^s)
4579 end if
4580 end do
4581 end do
4582 end do
4583 do idir=sdim,3
4584 ixcmax^d=ixomax^d;
4585 ixcmin^d=ixomin^d+kr(idir,^d)-1;
4586 ! E dot J on cell edges
4587 ein(ixc^s,idir)=ein(ixc^s,idir)*jce(ixc^s,idir)
4588 ! average from cell edge to cell center
4589 {^ifthreed
4590 if(idir==1) then
4591 {do ix^db=ixomin^db,ixomax^db\}
4592 jce(ix^d,idir)=0.25d0*(ein(ix^d,idir)+ein(ix1,ix2-1,ix3,idir)+ein(ix1,ix2,ix3-1,idir)&
4593 +ein(ix1,ix2-1,ix3-1,idir))
4594 if(jce(ix^d,idir)<0.d0) jce(ix^d,idir)=0.d0
4595 w(ix^d,e_)=w(ix^d,e_)+qdt*jce(ix^d,idir)
4596 {end do\}
4597 else if(idir==2) then
4598 {do ix^db=ixomin^db,ixomax^db\}
4599 jce(ix^d,idir)=0.25d0*(ein(ix^d,idir)+ein(ix1-1,ix2,ix3,idir)+ein(ix1,ix2,ix3-1,idir)&
4600 +ein(ix1-1,ix2,ix3-1,idir))
4601 if(jce(ix^d,idir)<0.d0) jce(ix^d,idir)=0.d0
4602 w(ix^d,e_)=w(ix^d,e_)+qdt*jce(ix^d,idir)
4603 {end do\}
4604 else
4605 {do ix^db=ixomin^db,ixomax^db\}
4606 jce(ix^d,idir)=0.25d0*(ein(ix^d,idir)+ein(ix1-1,ix2,ix3,idir)+ein(ix1,ix2-1,ix3,idir)&
4607 +ein(ix1-1,ix2-1,ix3,idir))
4608 if(jce(ix^d,idir)<0.d0) jce(ix^d,idir)=0.d0
4609 w(ix^d,e_)=w(ix^d,e_)+qdt*jce(ix^d,idir)
4610 {end do\}
4611 end if
4612 }
4613 {^iftwod
4614 !idir=3
4615 {do ix^db=ixomin^db,ixomax^db\}
4616 jce(ix^d,idir)=0.25d0*(ein(ix^d,idir)+ein(ix1-1,ix2,idir)+ein(ix1,ix2-1,idir)&
4617 +ein(ix1-1,ix2-1,idir))
4618 if(jce(ix^d,idir)<0.d0) jce(ix^d,idir)=0.d0
4619 w(ix^d,e_)=w(ix^d,e_)+qdt*jce(ix^d,idir)
4620 {end do\}
4621 }
4622 ! save additional numerical resistive heating to an extra variable
4623 if(nwextra>0) then
4624 block%w(ixo^s,nw)=block%w(ixo^s,nw)+jce(ixo^s,idir)
4625 end if
4626 end do
4627 end if
4628
4629 ! allow user to change inductive electric field, especially for boundary driven applications
4630 if(associated(usr_set_electric_field)) &
4631 call usr_set_electric_field(ixi^l,ixo^l,qt,qdt,fe,sct)
4632
4633 circ(ixi^s,1:ndim)=zero
4634
4635 ! Calculate circulation on each face
4636 do idim1=1,ndim ! Coordinate perpendicular to face
4637 ixcmax^d=ixomax^d;
4638 ixcmin^d=ixomin^d-kr(idim1,^d);
4639 do idim2=1,ndim
4640 ixa^l=ixc^l-kr(idim2,^d);
4641 do idir=sdim,3 ! Direction of line integral
4642 ! Assemble indices
4643 if(lvc(idim1,idim2,idir)==1) then
4644 ! Add line integrals in direction idir
4645 circ(ixc^s,idim1)=circ(ixc^s,idim1)&
4646 +(fe(ixc^s,idir)&
4647 -fe(ixa^s,idir))
4648 else if(lvc(idim1,idim2,idir)==-1) then
4649 ! Add line integrals in direction idir
4650 circ(ixc^s,idim1)=circ(ixc^s,idim1)&
4651 -(fe(ixc^s,idir)&
4652 -fe(ixa^s,idir))
4653 end if
4654 end do
4655 end do
4656 {do ix^db=ixcmin^db,ixcmax^db\}
4657 ! Divide by the area of the face to get dB/dt
4658 if(s%surfaceC(ix^d,idim1) > smalldouble) then
4659 ! Time update cell-face magnetic field component
4660 bfaces(ix^d,idim1)=bfaces(ix^d,idim1)-circ(ix^d,idim1)/s%surfaceC(ix^d,idim1)
4661 end if
4662 {end do\}
4663 end do
4664
4665 end associate
4666
4667 end subroutine rmhd_update_faces_contact
4668
4669 !> update faces
4670 subroutine rmhd_update_faces_hll(ixI^L,ixO^L,qt,qdt,wp,fC,fE,sCT,s,vcts)
4672 use mod_usr_methods
4674
4675 integer, intent(in) :: ixi^l, ixo^l
4676 double precision, intent(in) :: qt, qdt
4677 ! cell-center primitive variables
4678 double precision, intent(in) :: wp(ixi^s,1:nw)
4679 type(state) :: sct, s
4680 type(ct_velocity) :: vcts
4681 double precision, intent(in) :: fc(ixi^s,1:nwflux,1:ndim)
4682 double precision, intent(inout) :: fe(ixi^s,sdim:3)
4683
4684 double precision :: vtill(ixi^s,2)
4685 double precision :: vtilr(ixi^s,2)
4686 double precision :: bfacetot(ixi^s,ndim)
4687 double precision :: btill(ixi^s,ndim)
4688 double precision :: btilr(ixi^s,ndim)
4689 double precision :: cp(ixi^s,2)
4690 double precision :: cm(ixi^s,2)
4691 double precision :: circ(ixi^s,1:ndim)
4692 ! non-ideal electric field on cell edges
4693 double precision, dimension(ixI^S,sdim:3) :: e_resi
4694 integer :: hxc^l,ixc^l,ixcp^l,jxc^l,ixcm^l
4695 integer :: idim1,idim2,idir,ix^d
4696
4697 associate(bfaces=>s%ws,bfacesct=>sct%ws,x=>s%x,vbarc=>vcts%vbarC,cbarmin=>vcts%cbarmin,&
4698 cbarmax=>vcts%cbarmax)
4699
4700 ! Calculate contribution to FEM of each edge,
4701 ! that is, estimate value of line integral of
4702 ! electric field in the positive idir direction.
4703
4704 ! Loop over components of electric field
4705
4706 ! idir: electric field component we need to calculate
4707 ! idim1: directions in which we already performed the reconstruction
4708 ! idim2: directions in which we perform the reconstruction
4709
4710 ! if there is resistivity, get eta J
4711 if(rmhd_eta/=zero) call get_resistive_electric_field(ixi^l,ixo^l,wp,sct,s,e_resi)
4712
4713 do idir=sdim,3
4714 ! Indices
4715 ! idir: electric field component
4716 ! idim1: one surface
4717 ! idim2: the other surface
4718 ! cyclic permutation: idim1,idim2,idir=1,2,3
4719 ! Velocity components on the surface
4720 ! follow cyclic premutations:
4721 ! Sx(1),Sx(2)=y,z ; Sy(1),Sy(2)=z,x ; Sz(1),Sz(2)=x,y
4722
4723 ixcmax^d=ixomax^d;
4724 ixcmin^d=ixomin^d-1+kr(idir,^d);
4725
4726 ! Set indices and directions
4727 idim1=mod(idir,3)+1
4728 idim2=mod(idir+1,3)+1
4729
4730 jxc^l=ixc^l+kr(idim1,^d);
4731 ixcp^l=ixc^l+kr(idim2,^d);
4732
4733 ! Reconstruct transverse transport velocities
4734 call reconstruct(ixi^l,ixc^l,idim2,vbarc(ixi^s,idim1,1),&
4735 vtill(ixi^s,2),vtilr(ixi^s,2))
4736
4737 call reconstruct(ixi^l,ixc^l,idim1,vbarc(ixi^s,idim2,2),&
4738 vtill(ixi^s,1),vtilr(ixi^s,1))
4739
4740 ! Reconstruct magnetic fields
4741 ! Eventhough the arrays are larger, reconstruct works with
4742 ! the limits ixG.
4743 if(b0field) then
4744 bfacetot(ixi^s,idim1)=bfacesct(ixi^s,idim1)+block%B0(ixi^s,idim1,idim1)
4745 bfacetot(ixi^s,idim2)=bfacesct(ixi^s,idim2)+block%B0(ixi^s,idim2,idim2)
4746 else
4747 bfacetot(ixi^s,idim1)=bfacesct(ixi^s,idim1)
4748 bfacetot(ixi^s,idim2)=bfacesct(ixi^s,idim2)
4749 end if
4750 call reconstruct(ixi^l,ixc^l,idim2,bfacetot(ixi^s,idim1),&
4751 btill(ixi^s,idim1),btilr(ixi^s,idim1))
4752
4753 call reconstruct(ixi^l,ixc^l,idim1,bfacetot(ixi^s,idim2),&
4754 btill(ixi^s,idim2),btilr(ixi^s,idim2))
4755
4756 ! Take the maximum characteristic
4757
4758 cm(ixc^s,1)=max(cbarmin(ixcp^s,idim1),cbarmin(ixc^s,idim1))
4759 cp(ixc^s,1)=max(cbarmax(ixcp^s,idim1),cbarmax(ixc^s,idim1))
4760
4761 cm(ixc^s,2)=max(cbarmin(jxc^s,idim2),cbarmin(ixc^s,idim2))
4762 cp(ixc^s,2)=max(cbarmax(jxc^s,idim2),cbarmax(ixc^s,idim2))
4763
4764
4765 ! Calculate eletric field
4766 fe(ixc^s,idir)=-(cp(ixc^s,1)*vtill(ixc^s,1)*btill(ixc^s,idim2) &
4767 + cm(ixc^s,1)*vtilr(ixc^s,1)*btilr(ixc^s,idim2) &
4768 - cp(ixc^s,1)*cm(ixc^s,1)*(btilr(ixc^s,idim2)-btill(ixc^s,idim2)))&
4769 /(cp(ixc^s,1)+cm(ixc^s,1)) &
4770 +(cp(ixc^s,2)*vtill(ixc^s,2)*btill(ixc^s,idim1) &
4771 + cm(ixc^s,2)*vtilr(ixc^s,2)*btilr(ixc^s,idim1) &
4772 - cp(ixc^s,2)*cm(ixc^s,2)*(btilr(ixc^s,idim1)-btill(ixc^s,idim1)))&
4773 /(cp(ixc^s,2)+cm(ixc^s,2))
4774
4775 ! add resistive electric field at cell edges E=-vxB+eta J
4776 if(rmhd_eta/=zero) fe(ixc^s,idir)=fe(ixc^s,idir)+e_resi(ixc^s,idir)
4777 fe(ixc^s,idir)=qdt*s%dsC(ixc^s,idir)*fe(ixc^s,idir)
4778
4779 if (.not.slab) then
4780 where(abs(x(ixc^s,r_)+half*dxlevel(r_)).lt.1.0d-9)
4781 fe(ixc^s,idir)=zero
4782 end where
4783 end if
4784
4785 end do
4786
4787 ! allow user to change inductive electric field, especially for boundary driven applications
4788 if(associated(usr_set_electric_field)) &
4789 call usr_set_electric_field(ixi^l,ixo^l,qt,qdt,fe,sct)
4790
4791 circ(ixi^s,1:ndim)=zero
4792
4793 ! Calculate circulation on each face: interal(fE dot dl)
4794 do idim1=1,ndim ! Coordinate perpendicular to face
4795 ixcmax^d=ixomax^d;
4796 ixcmin^d=ixomin^d-kr(idim1,^d);
4797 do idim2=1,ndim
4798 do idir=sdim,3 ! Direction of line integral
4799 ! Assemble indices
4800 if(lvc(idim1,idim2,idir)/=0) then
4801 hxc^l=ixc^l-kr(idim2,^d);
4802 ! Add line integrals in direction idir
4803 circ(ixc^s,idim1)=circ(ixc^s,idim1)&
4804 +lvc(idim1,idim2,idir)&
4805 *(fe(ixc^s,idir)&
4806 -fe(hxc^s,idir))
4807 end if
4808 end do
4809 end do
4810 {do ix^db=ixcmin^db,ixcmax^db\}
4811 ! Divide by the area of the face to get dB/dt
4812 if(s%surfaceC(ix^d,idim1) > smalldouble) then
4813 ! Time update cell-face magnetic field component
4814 bfaces(ix^d,idim1)=bfaces(ix^d,idim1)-circ(ix^d,idim1)/s%surfaceC(ix^d,idim1)
4815 end if
4816 {end do\}
4817 end do
4818
4819 end associate
4820 end subroutine rmhd_update_faces_hll
4821
4822 !> calculate eta J at cell edges
4823 subroutine get_resistive_electric_field(ixI^L,ixO^L,wp,sCT,s,jce)
4825 use mod_usr_methods
4826 use mod_geometry
4827
4828 integer, intent(in) :: ixi^l, ixo^l
4829 ! cell-center primitive variables
4830 double precision, intent(in) :: wp(ixi^s,1:nw)
4831 type(state), intent(in) :: sct, s
4832 ! current on cell edges
4833 double precision :: jce(ixi^s,sdim:3)
4834
4835 ! current on cell centers
4836 double precision :: jcc(ixi^s,7-2*ndir:3)
4837 ! location at cell faces
4838 double precision :: xs(ixgs^t,1:ndim)
4839 ! resistivity
4840 double precision :: eta(ixi^s)
4841 double precision :: gradi(ixgs^t)
4842 integer :: ix^d,ixc^l,ixa^l,ixb^l,idir,idirmin,idim1,idim2
4843
4844 associate(x=>s%x,dx=>s%dx,w=>s%w,wct=>sct%w,wcts=>sct%ws)
4845 ! calculate current density at cell edges
4846 jce=0.d0
4847 do idim1=1,ndim
4848 do idim2=1,ndim
4849 do idir=sdim,3
4850 if (lvc(idim1,idim2,idir)==0) cycle
4851 ixcmax^d=ixomax^d;
4852 ixcmin^d=ixomin^d+kr(idir,^d)-1;
4853 ixbmax^d=ixcmax^d-kr(idir,^d)+1;
4854 ixbmin^d=ixcmin^d;
4855 ! current at transverse faces
4856 xs(ixb^s,:)=x(ixb^s,:)
4857 xs(ixb^s,idim2)=x(ixb^s,idim2)+half*dx(ixb^s,idim2)
4858 call gradientf(wcts(ixgs^t,idim2),xs,ixgs^ll,ixc^l,idim1,gradi,2)
4859 if (lvc(idim1,idim2,idir)==1) then
4860 jce(ixc^s,idir)=jce(ixc^s,idir)+gradi(ixc^s)
4861 else
4862 jce(ixc^s,idir)=jce(ixc^s,idir)-gradi(ixc^s)
4863 end if
4864 end do
4865 end do
4866 end do
4867 ! get resistivity
4868 if(rmhd_eta>zero)then
4869 jce(ixi^s,:)=jce(ixi^s,:)*rmhd_eta
4870 else
4871 ixa^l=ixo^l^ladd1;
4872 call get_current(wct,ixi^l,ixa^l,idirmin,jcc)
4873 call usr_special_resistivity(wp,ixi^l,ixa^l,idirmin,x,jcc,eta)
4874 ! calcuate eta on cell edges
4875 do idir=sdim,3
4876 ixcmax^d=ixomax^d;
4877 ixcmin^d=ixomin^d+kr(idir,^d)-1;
4878 jcc(ixc^s,idir)=0.d0
4879 {do ix^db=0,1\}
4880 if({ ix^d==1 .and. ^d==idir | .or.}) cycle
4881 ixamin^d=ixcmin^d+ix^d;
4882 ixamax^d=ixcmax^d+ix^d;
4883 jcc(ixc^s,idir)=jcc(ixc^s,idir)+eta(ixa^s)
4884 {end do\}
4885 jcc(ixc^s,idir)=jcc(ixc^s,idir)*0.25d0
4886 jce(ixc^s,idir)=jce(ixc^s,idir)*jcc(ixc^s,idir)
4887 end do
4888 end if
4889
4890 end associate
4891 end subroutine get_resistive_electric_field
4892
4893 !> calculate cell-center values from face-center values
4894 subroutine rmhd_face_to_center(ixO^L,s)
4896 ! Non-staggered interpolation range
4897 integer, intent(in) :: ixo^l
4898 type(state) :: s
4899 integer :: ix^d
4900
4901 ! calculate cell-center values from face-center values in 2nd order
4902 ! because the staggered arrays have an additional place to the left.
4903 ! Interpolate to cell barycentre using arithmetic average
4904 ! This might be done better later, to make the method less diffusive.
4905 {!dir$ ivdep
4906 do ix^db=ixomin^db,ixomax^db\}
4907 {^ifthreed
4908 s%w(ix^d,b1_)=half/s%surface(ix^d,1)*(s%ws(ix^d,1)*s%surfaceC(ix^d,1)&
4909 +s%ws(ix1-1,ix2,ix3,1)*s%surfaceC(ix1-1,ix2,ix3,1))
4910 s%w(ix^d,b2_)=half/s%surface(ix^d,2)*(s%ws(ix^d,2)*s%surfaceC(ix^d,2)&
4911 +s%ws(ix1,ix2-1,ix3,2)*s%surfaceC(ix1,ix2-1,ix3,2))
4912 s%w(ix^d,b3_)=half/s%surface(ix^d,3)*(s%ws(ix^d,3)*s%surfaceC(ix^d,3)&
4913 +s%ws(ix1,ix2,ix3-1,3)*s%surfaceC(ix1,ix2,ix3-1,3))
4914 }
4915 {^iftwod
4916 s%w(ix^d,b1_)=half/s%surface(ix^d,1)*(s%ws(ix^d,1)*s%surfaceC(ix^d,1)&
4917 +s%ws(ix1-1,ix2,1)*s%surfaceC(ix1-1,ix2,1))
4918 s%w(ix^d,b2_)=half/s%surface(ix^d,2)*(s%ws(ix^d,2)*s%surfaceC(ix^d,2)&
4919 +s%ws(ix1,ix2-1,2)*s%surfaceC(ix1,ix2-1,2))
4920 }
4921 {end do\}
4922 ! calculate cell-center values from face-center values in 4th order
4923 !do idim=1,ndim
4924 ! gxO^L=ixO^L-2*kr(idim,^D);
4925 ! hxO^L=ixO^L-kr(idim,^D);
4926 ! jxO^L=ixO^L+kr(idim,^D);
4927
4928 ! ! Interpolate to cell barycentre using fourth order central formula
4929 ! w(ixO^S,mag(idim))=(0.0625d0/s%surface(ixO^S,idim))*&
4930 ! ( -ws(gxO^S,idim)*s%surfaceC(gxO^S,idim) &
4931 ! +9.0d0*ws(hxO^S,idim)*s%surfaceC(hxO^S,idim) &
4932 ! +9.0d0*ws(ixO^S,idim)*s%surfaceC(ixO^S,idim) &
4933 ! -ws(jxO^S,idim)*s%surfaceC(jxO^S,idim) )
4934 !end do
4935
4936 ! calculate cell-center values from face-center values in 6th order
4937 !do idim=1,ndim
4938 ! fxO^L=ixO^L-3*kr(idim,^D);
4939 ! gxO^L=ixO^L-2*kr(idim,^D);
4940 ! hxO^L=ixO^L-kr(idim,^D);
4941 ! jxO^L=ixO^L+kr(idim,^D);
4942 ! kxO^L=ixO^L+2*kr(idim,^D);
4943
4944 ! ! Interpolate to cell barycentre using sixth order central formula
4945 ! w(ixO^S,mag(idim))=(0.00390625d0/s%surface(ixO^S,idim))* &
4946 ! ( +3.0d0*ws(fxO^S,idim)*s%surfaceC(fxO^S,idim) &
4947 ! -25.0d0*ws(gxO^S,idim)*s%surfaceC(gxO^S,idim) &
4948 ! +150.0d0*ws(hxO^S,idim)*s%surfaceC(hxO^S,idim) &
4949 ! +150.0d0*ws(ixO^S,idim)*s%surfaceC(ixO^S,idim) &
4950 ! -25.0d0*ws(jxO^S,idim)*s%surfaceC(jxO^S,idim) &
4951 ! +3.0d0*ws(kxO^S,idim)*s%surfaceC(kxO^S,idim) )
4952 !end do
4953 end subroutine rmhd_face_to_center
4954
4955 !> calculate magnetic field from vector potential
4956 subroutine b_from_vector_potential(ixIs^L, ixI^L, ixO^L, ws, x)
4959 integer, intent(in) :: ixis^l, ixi^l, ixo^l
4960 double precision, intent(inout) :: ws(ixis^s,1:nws)
4961 double precision, intent(in) :: x(ixi^s,1:ndim)
4962 double precision :: adummy(ixis^s,1:3)
4963
4964 call b_from_vector_potentiala(ixis^l, ixi^l, ixo^l, ws, x, adummy)
4965 end subroutine b_from_vector_potential
4966
4967 subroutine rfactor_from_temperature_ionization(w,x,ixI^L,ixO^L,Rfactor)
4970 integer, intent(in) :: ixi^l, ixo^l
4971 double precision, intent(in) :: w(ixi^s,1:nw)
4972 double precision, intent(in) :: x(ixi^s,1:ndim)
4973 double precision, intent(out):: rfactor(ixi^s)
4974 double precision :: iz_h(ixo^s),iz_he(ixo^s)
4975
4976 call ionization_degree_from_temperature(ixi^l,ixo^l,w(ixi^s,te_),iz_h,iz_he)
4977 ! assume the first and second ionization of Helium have the same degree
4978 rfactor(ixo^s)=(1.d0+iz_h(ixo^s)+0.1d0*(1.d0+iz_he(ixo^s)*(1.d0+iz_he(ixo^s))))/(2.d0+3.d0*he_abundance)
4979 end subroutine rfactor_from_temperature_ionization
4980
4981 subroutine rfactor_from_constant_ionization(w,x,ixI^L,ixO^L,Rfactor)
4983 integer, intent(in) :: ixi^l, ixo^l
4984 double precision, intent(in) :: w(ixi^s,1:nw)
4985 double precision, intent(in) :: x(ixi^s,1:ndim)
4986 double precision, intent(out):: rfactor(ixi^s)
4987
4988 rfactor(ixo^s)=rr
4989 end subroutine rfactor_from_constant_ionization
4990end module mod_rmhd_phys
Module for including anisotropic flux limited diffusion (AFLD)-approximation in Radiation-hydrodynami...
Definition mod_afld.t:8
subroutine afld_get_diffcoef_central(w, wct, x, ixil, ixol)
Calculates cell-centered diffusion coefficient to be used in multigrid.
Definition mod_afld.t:684
subroutine, public get_afld_rad_force(qdt, ixil, ixol, wct, w, x, energy, qsourcesplit, active)
w[iw]=w[iw]+qdt*S[wCT,qtC,x] where S is the source based on wCT within ixO This subroutine handles th...
Definition mod_afld.t:141
subroutine, public afld_init(he_abundance, rhd_radiation_diffusion, afld_gamma)
Initialising FLD-module: Read opacities Initialise Multigrid adimensionalise kappa Add extra variable...
Definition mod_afld.t:93
subroutine, public afld_radforce_get_dt(w, ixil, ixol, dtnew, dxd, x)
Definition mod_afld.t:217
subroutine, public afld_get_radpress(w, x, ixil, ixol, rad_pressure, nth)
Calculate Radiation Pressure Returns Radiation Pressure as tensor.
Definition mod_afld.t:518
subroutine, public get_afld_energy_interact(qdt, ixil, ixol, wct, w, x, energy, qsourcesplit, active)
w[iw]=w[iw]+qdt*S[wCT,qtC,x] where S is the source based on wCT within ixO This subroutine handles th...
Definition mod_afld.t:244
Module to include CAK radiation line force in (magneto)hydrodynamic models Computes both the force fr...
subroutine cak_get_dt(w, ixil, ixol, dtnew, dxd, x)
Check time step for total radiation contribution.
subroutine cak_init(phys_gamma)
Initialize the module.
subroutine cak_add_source(qdt, ixil, ixol, wct, w, x, energy, qsourcesplit, active)
w[iw]=w[iw]+qdt*S[wCT,qtC,x] where S is the source based on wCT within ixO
subroutine, public mpistop(message)
Exit MPI-AMRVAC with an error message.
Module for physical and numeric constants.
double precision, parameter const_rad_a
subroutine reconstruct(ixil, ixcl, idir, q, ql, qr)
Reconstruct scalar q within ixO^L to 1/2 dx in direction idir Return both left and right reconstructe...
subroutine b_from_vector_potentiala(ixisl, ixil, ixol, ws, x, a)
calculate magnetic field from vector potential A at cell edges
subroutine add_convert_method(phys_convert_vars, nwc, dataset_names, file_suffix)
Definition mod_convert.t:59
Module for flux conservation near refinement boundaries.
Nicolas Moens Module for including flux limited diffusion (FLD)-approximation in Radiation-hydrodynam...
Definition mod_fld.t:9
subroutine, public get_fld_rad_force(qdt, ixil, ixol, wct, w, x, energy, qsourcesplit, active)
w[iw]=w[iw]+qdt*S[wCT,qtC,x] where S is the source based on wCT within ixO This subroutine handles th...
Definition mod_fld.t:146
subroutine, public fld_get_radpress(w, x, ixil, ixol, rad_pressure, nth)
Calculate Radiation Pressure Returns Radiation Pressure as tensor.
Definition mod_fld.t:456
subroutine, public fld_init(he_abundance, radiation_diffusion, energy_interact, r_gamma)
Initialising FLD-module: Read opacities Initialise Multigrid adimensionalise kappa Add extra variable...
Definition mod_fld.t:94
subroutine fld_get_diffcoef_central(w, wct, x, ixil, ixol)
Calculates cell-centered diffusion coefficient to be used in multigrid.
Definition mod_fld.t:719
character(len=8) fld_diff_scheme
Which method to solve diffusion part.
Definition mod_fld.t:35
subroutine, public fld_radforce_get_dt(w, ixil, ixol, dtnew, dxd, x)
Definition mod_fld.t:181
Module with basic grid data structures.
Definition mod_forest.t:2
type(tree_node_ptr), dimension(:,:), allocatable, save igrid_to_node
Array to go from an [igrid, ipe] index to a node pointer.
Definition mod_forest.t:32
subroutine, public get_divb(w, ixil, ixol, divb, nth_in)
Calculate div B within ixO.
integer, dimension(:), allocatable, public mag
Indices of the magnetic field.
Module with geometry-related routines (e.g., divergence, curl)
Definition mod_geometry.t:2
subroutine divvector(qvec, ixil, ixol, divq, nth_in)
integer coordinate
Definition mod_geometry.t:7
integer, parameter spherical
integer, parameter cylindrical
subroutine curlvector(qvec, ixil, ixol, curlvec, idirmin, idirmin0, ndir0, fourthorder)
Calculate curl of a vector qvec within ixL Options to employ standard second order CD evaluations use...
subroutine gradient(q, ixil, ixol, idir, gradq, nth_in)
subroutine gradientf(q, x, ixil, ixol, idir, gradq, nth_in, pm_in)
subroutine gradientl(q, ixil, ixol, idir, gradq)
This module contains definitions of global parameters and variables and some generic functions/subrou...
type(state), pointer block
Block pointer for using one block and its previous state.
double precision dtdiffpar
For resistive MHD, the time step is also limited by the diffusion time: .
character(len=std_len) typegrad
double precision unit_charge
Physical scaling factor for charge.
integer, parameter bc_noinflow
integer ixghi
Upper index of grid block arrays.
pure subroutine cross_product(ixil, ixol, a, b, axb)
Cross product of two vectors.
integer, dimension(3, 3, 3) lvc
Levi-Civita tensor.
double precision unit_time
Physical scaling factor for time.
double precision unit_density
Physical scaling factor for density.
double precision unit_opacity
Physical scaling factor for Opacity.
integer, parameter unitpar
file handle for IO
double precision unit_mass
Physical scaling factor for mass.
integer, dimension(3, 3) kr
Kronecker delta tensor.
integer, dimension(:, :), allocatable typeboundary
Array indicating the type of boundary condition per variable and per physical boundary.
double precision unit_numberdensity
Physical scaling factor for number density.
character(len=std_len) convert_type
Which format to use when converting.
double precision unit_pressure
Physical scaling factor for pressure.
integer, parameter ndim
Number of spatial dimensions for grid variables.
double precision unit_length
Physical scaling factor for length.
logical stagger_grid
True for using stagger grid.
double precision cmax_global
global fastest wave speed needed in fd scheme and glm method
logical use_particles
Use particles module or not.
character(len=std_len), dimension(:), allocatable par_files
Which par files are used as input.
integer icomm
The MPI communicator.
double precision bdip
amplitude of background dipolar, quadrupolar, octupolar, user's field
integer b0i
background magnetic field location indicator
integer mype
The rank of the current MPI task.
double precision, dimension(:), allocatable, parameter d
logical local_timestep
each cell has its own timestep or not
double precision dt
global time step
integer ndir
Number of spatial dimensions (components) for vector variables.
integer ixm
the mesh range of a physical block without ghost cells
integer ierrmpi
A global MPI error return code.
logical autoconvert
If true, already convert to output format during the run.
logical slab
Cartesian geometry or not.
integer, parameter bc_periodic
integer, parameter bc_special
boundary condition types
double precision unit_magneticfield
Physical scaling factor for magnetic field.
double precision unit_velocity
Physical scaling factor for velocity.
double precision c_norm
Normalised speed of light.
logical b0field
split magnetic field as background B0 field
double precision, dimension(:,:), allocatable rnode
Corner coordinates.
double precision unit_temperature
Physical scaling factor for temperature.
double precision unit_radflux
Physical scaling factor for radiation flux.
logical si_unit
Use SI units (.true.) or use cgs units (.false.)
double precision, dimension(:,:), allocatable dx
spatial steps for all dimensions at all levels
integer nghostcells
Number of ghost cells surrounding a grid.
integer, parameter sdim
starting dimension for electric field
logical phys_trac
Use TRAC for MHD or 1D HD.
logical need_global_cmax
need global maximal wave speed
logical convert
If true and restart_from_file is given, convert snapshots to other file formats.
logical fix_small_values
fix small values with average or replace methods
double precision, dimension(^nd) dxlevel
store unstretched cell size of current level
logical use_multigrid
Use multigrid (only available in 2D and 3D)
logical slab_uniform
uniform Cartesian geometry or not (stretched Cartesian)
integer max_blocks
The maximum number of grid blocks in a processor.
integer r_
Indices for cylindrical coordinates FOR TESTS, negative value when not used:
integer boundspeed
bound (left/min and right.max) speed of Riemann fan
integer, parameter unitconvert
integer number_equi_vars
number of equilibrium set variables, besides the mag field
integer, parameter ixglo
Lower index of grid block arrays (always 1)
Module for including gravity in (magneto)hydrodynamics simulations.
Definition mod_gravity.t:2
subroutine gravity_get_dt(w, ixil, ixol, dtnew, dxd, x)
Definition mod_gravity.t:87
subroutine gravity_init()
Initialize the module.
Definition mod_gravity.t:26
subroutine gravity_add_source(qdt, ixil, ixol, wct, wctprim, w, x, energy, rhov, qsourcesplit, active)
w[iw]=w[iw]+qdt*S[wCT,qtC,x] where S is the source based on wCT within ixO
Definition mod_gravity.t:43
module ionization degree - get ionization degree for given temperature
subroutine ionization_degree_from_temperature(ixil, ixol, te, iz_h, iz_he)
Module to couple the octree-mg library to AMRVAC. This file uses the VACPP preprocessor,...
type(mg_t) mg
Data structure containing the multigrid tree.
Module containing all the particle routines.
subroutine particles_init()
Initialize particle data and parameters.
This module defines the procedures of a physics module. It contains function pointers for the various...
Definition mod_physics.t:4
Radiation-magneto-hydrodynamics module.
subroutine, public get_current(w, ixil, ixol, idirmin, current)
Calculate idirmin and the idirmin:3 components of the common current array make sure that dxlevel(^D)...
integer, public, protected rmhd_trac_type
Which TRAC method is used.
character(len=8), public rmhd_pressure
In the case of no rmhd_energy, how to compute pressure.
subroutine, public rmhd_phys_init()
logical, public, protected rmhd_thermal_conduction
Whether thermal conduction is used.
double precision, public rmhd_gamma
The adiabatic index.
character(len=8), public rmhd_radiation_formalism
Formalism to treat radiation.
logical, public divbwave
Add divB wave in Roe solver.
integer, public, protected rmhd_trac_finegrid
Distance between two adjacent traced magnetic field lines (in finest cell size)
double precision, public, protected h_ion_fr
Ionization fraction of H H_ion_fr = H+/(H+ + H)
integer, dimension(2 *^nd), public, protected boundary_divbfix_skip
To skip * layer of ghost cells during divB=0 fix for boundary.
logical, public, protected rmhd_hyperbolic_thermal_conduction
Whether thermal conduction is used.
double precision, public, protected rr
logical, public rmhd_equi_thermal
double precision, public rmhd_etah
Hall resistivity.
logical, public, protected rmhd_radiation_diffusion
Treat radiation energy diffusion.
subroutine, public rmhd_face_to_center(ixol, s)
calculate cell-center values from face-center values
procedure(sub_get_pthermal), pointer, public rmhd_get_pthermal
integer, public, protected psi_
Indices of the GLM psi.
type(tc_fluid), allocatable, public tc_fl
type of fluid for thermal conduction
integer, public, protected c
Indices of the momentum density for the form of better vectorization.
subroutine, public b_from_vector_potential(ixisl, ixil, ixol, ws, x)
calculate magnetic field from vector potential
logical, public, protected rmhd_cak_force
Whether CAK radiation line force is activated.
logical, public, protected rmhd_radiation_force
Treat radiation fld_Rad_force.
logical, public, protected rmhd_glm
Whether GLM-MHD is used to control div B.
double precision, public, protected small_r_e
The smallest allowed radiation energy.
double precision, public rmhd_eta_hyper
The MHD hyper-resistivity.
logical, public clean_initial_divb
clean initial divB
integer, public, protected rmhd_n_tracer
Number of tracer species.
logical, public, protected rmhd_particles
Whether particles module is added.
integer, public, protected b
double precision, public kbmpmua4
kb/(m_p mu)* 1/a_rad**4,
integer, public, protected m
subroutine, public rmhd_get_trad(w, x, ixil, ixol, trad)
Calculates radiation temperature.
integer, public equi_rho0_
equi vars indices in the stateequi_vars array
double precision, public rmhd_adiab
The adiabatic constant.
subroutine, public rmhd_get_pthermal_plus_pradiation(w, x, ixil, ixol, pth_plus_prad)
Calculates the sum of the gas pressure and the max Prad tensor element.
integer, public, protected q_
Index of the heat flux q.
integer, public, protected tweight_
logical, public has_equi_rho0
whether split off equilibrium density
double precision, public rmhd_eta
The MHD resistivity.
integer, public, protected p_
Index of the gas pressure (-1 if not present) should equal e_.
subroutine, public get_normalized_divb(w, ixil, ixol, divb)
get dimensionless div B = |divB| * volume / area / |B|
integer, public, protected rho_
Index of the density (in the w array)
integer, public, protected c_
double precision function, dimension(ixo^s), public rmhd_mag_en_all(w, ixil, ixol)
Compute 2 times total magnetic energy.
type(te_fluid), allocatable, public te_fl_rmhd
type of fluid for thermal emission synthesis
logical, public, protected rmhd_gravity
Whether gravity is added.
integer, dimension(:), allocatable, public, protected mom
Indices of the momentum density.
logical, public, protected rmhd_glm_extended
Whether extended GLM-MHD is used with additional sources.
logical, public, protected rmhd_viscosity
Whether viscosity is added.
logical, public, protected rmhd_partial_ionization
Whether plasma is partially ionized.
integer, public, protected tcoff_
Index of the cutoff temperature for the TRAC method.
integer, public, protected e_
Index of the energy density (-1 if not present)
logical, public, protected rmhd_radiation_advection
Treat radiation advection.
double precision, public, protected he_ion_fr2
Ratio of number He2+ / number He+ + He2+ He_ion_fr2 = He2+/(He2+ + He+)
subroutine, public rmhd_get_rho(w, x, ixil, ixol, rho)
integer, dimension(:), allocatable, public, protected tracer
Indices of the tracers.
logical, public, protected rmhd_energy_interact
Treat radiation-gas energy interaction.
subroutine, public rmhd_get_tgas(w, x, ixil, ixol, tgas)
Calculates gas temperature.
character(len=std_len), public, protected type_ct
Method type of constrained transport.
procedure(sub_convert), pointer, public rmhd_to_conserved
double precision, public, protected he_abundance
Helium abundance over Hydrogen.
logical, public partial_energy
Whether an internal or hydrodynamic energy equation is used.
procedure(sub_convert), pointer, public rmhd_to_primitive
logical, public, protected rmhd_dump_full_vars
whether dump full variables (when splitting is used) in a separate dat file
logical, public, protected rmhd_trac
Whether TRAC method is used.
subroutine, public rmhd_clean_divb_multigrid(qdt, qt, active)
subroutine, public rmhd_set_mg_bounds
Set the boundaries for the diffusion of E.
subroutine, public rmhd_get_v(w, x, ixil, ixol, v)
Calculate v vector.
double precision, public hypertc_kappa
The thermal conductivity kappa in hyperbolic thermal conduction.
logical, public has_equi_pe0
whether split off equilibrium thermal pressure
subroutine, public rmhd_get_pradiation(w, x, ixil, ixol, prad, nth)
Calculate radiation pressure within ixO^L.
integer, public, protected te_
Indices of temperature.
logical, public, protected source_split_divb
Whether divB cleaning sources are added splitting from fluid solver.
integer, public, protected r_e
Index of the radiation energy.
procedure(sub_get_pthermal), pointer, public rmhd_get_temperature
character(len=std_len), public, protected typedivbfix
Method type to clean divergence of B.
logical, public, protected b0field_forcefree
B0 field is force-free.
double precision, public rmhd_glm_alpha
GLM-MHD parameter: ratio of the diffusive and advective time scales for div b taking values within [0...
integer, public, protected rmhd_divb_nth
Whether divB is computed with a fourth order approximation.
subroutine, public rmhd_ei_to_e(ixil, ixol, w, x)
Transform internal energy to total energy.
integer, public equi_pe0_
double precision, public, protected he_ion_fr
Ionization fraction of He He_ion_fr = (He2+ + He+)/(He2+ + He+ + He)
logical, public, protected rmhd_energy
Whether an energy equation is used.
logical, dimension(2 *^nd), public, protected boundary_divbfix
To control divB=0 fix for boundary.
double precision, public, protected rmhd_trac_mask
Height of the mask used in the TRAC method.
logical, public, protected eq_state_units
subroutine, public rmhd_e_to_ei(ixil, ixol, w, x)
Transform total energy to internal energy.
logical, public, protected rmhd_4th_order
MHD fourth order.
Module for handling problematic values in simulations, such as negative pressures.
subroutine, public small_values_average(ixil, ixol, w, x, w_flag, windex)
logical, public trace_small_values
trace small values in the source file using traceback flag of compiler
subroutine, public small_values_error(wprim, x, ixil, ixol, w_flag, subname)
logical, dimension(:), allocatable, public small_values_fix_iw
Whether to apply small value fixes to certain variables.
character(len=20), public small_values_method
How to handle small values.
Generic supertimestepping method 1) in amrvac.par in sts_list set the following parameters which have...
subroutine, public add_sts_method(sts_getdt, sts_set_sources, startvar, nflux, startwbc, nwbc, evolve_b)
subroutine which added programatically a term to be calculated using STS Params: sts_getdt function c...
subroutine, public set_conversion_methods_to_head(sts_before_first_cycle, sts_after_last_cycle)
Set the hooks called before the first cycle and after the last cycle in the STS update This method sh...
subroutine, public set_error_handling_to_head(sts_error_handling)
Set the hook of error handling in the STS update. This method is called before updating the BC....
subroutine, public sts_init()
Initialize sts module.
Thermal conduction for HD and MHD or RHD and RMHD or twofl (plasma-neutral) module Adaptation of mod_...
double precision function, public get_tc_dt_mhd(w, ixil, ixol, dxd, x, fl)
Get the explicut timestep for the TC (mhd implementation)
subroutine tc_init_params(phys_gamma)
subroutine, public sts_set_source_tc_mhd(ixil, ixol, w, x, wres, fix_conserve_at_step, my_dt, igrid, nflux, fl)
anisotropic thermal conduction with slope limited symmetric scheme Sharma 2007 Journal of Computation...
subroutine, public tc_get_mhd_params(fl, read_mhd_params)
Init TC coefficients: MHD case.
subroutine get_euv_image(qunit, fl)
subroutine get_sxr_image(qunit, fl)
subroutine get_euv_spectrum(qunit, fl)
subroutine get_whitelight_image(qunit, fl)
Module with all the methods that users can customize in AMRVAC.
procedure(rfactor), pointer usr_rfactor
procedure(special_resistivity), pointer usr_special_resistivity
procedure(set_equi_vars), pointer usr_set_equi_vars
procedure(special_mg_bc), pointer usr_special_mg_bc
procedure(set_electric_field), pointer usr_set_electric_field
The module add viscous source terms and check time step.
subroutine viscosity_add_source(qdt, ixil, ixol, wct, w, x, energy, qsourcesplit, active)
subroutine viscosity_init(phys_wider_stencil)
Initialize the module.
subroutine viscosity_get_dt(w, ixil, ixol, dtnew, dxd, x)
The data structure that contains information about a tree node/grid block.
Definition mod_forest.t:11