MPI-AMRVAC  3.1
The MPI - Adaptive Mesh Refinement - Versatile Advection Code
mod_global_parameters.t
Go to the documentation of this file.
1 !> This module contains definitions of global parameters and variables and some
2 !> generic functions/subroutines used in AMRVAC.
3 !>
7  use mpi
8  use mod_constants
9  use mod_variables
10  use mod_basic_types
11 
12  implicit none
13  public
14 
15  ! Parameters
16  character(len=*), parameter :: undefined = 'undefined'
17 
18  !> The number of MPI tasks
19  integer :: npe
20 
21  !> The rank of the current MPI task
22  integer :: mype
23 
24  !> The MPI communicator
25  integer :: icomm
26 
27  !> A global MPI error return code
28  integer :: ierrmpi
29 
30  !> MPI file handle for logfile
31  integer :: log_fh
32  !> MPI type for block including ghost cells and its size
33  integer :: type_block, size_block
34  !> MPI type for block coarsened by 2, and for its children blocks
36  !> MPI type for staggered block coarsened by 2, and for its children blocks
37  integer :: type_coarse_block_stg(^nd,2^d&), type_sub_block_stg(^ND,2^D&)
38  !> MPI type for IO: block excluding ghost cells
40  !> MPI type for IO of staggered variables
42  !> MPI type for IO: cell corner (xc) or cell center (xcc) coordinates
44  !> MPI type for IO: cell corner (wc) or cell center (wcc) variables
46 
47 
48  ! geometry and domain setups
49 
50  !> the mesh range of a physical block without ghost cells
51  integer :: ixm^ll
52 
53  !> minimum and maximum domain boundaries for each dimension
54  double precision :: xprob^l
55 
56  !> Indices for cylindrical coordinates FOR TESTS, negative value when not used:
57  integer :: r_ = -1
58  integer :: phi_ = -1
59  integer :: z_ = -1
60 
61  !> Number of spatial dimensions for grid variables
62  integer, parameter :: ndim=^nd
63 
64  !> Number of spatial dimensions (components) for vector variables
65  integer :: ndir=ndim
66 
67  !> starting dimension for electric field
68  {^ifoned
69  integer, parameter :: sdim=3
70  }
71  {^iftwod
72  integer, parameter :: sdim=3
73  }
74  {^ifthreed
75  integer, parameter :: sdim=1
76  }
77 
78  !> Cartesian geometry or not
79  logical :: slab
80 
81  !> uniform Cartesian geometry or not (stretched Cartesian)
82  logical :: slab_uniform
83 
84  !> each cell has its own timestep or not
85  logical :: local_timestep = .false.
86 
87  !> number of grid blocks in domain per dimension, in array over levels
88  integer, dimension(:), allocatable :: ng^d
89  !> extent of grid blocks in domain per dimension, in array over levels
90  double precision, dimension(:), allocatable :: dg^d
91 
92  !> number of cells for each dimension in level-one mesh
93  integer :: domain_nx^d
94 
95  !> number of cells for each dimension in grid block excluding ghostcells
96  integer :: block_nx^d
97 
98  !> Lower index of grid block arrays (always 1)
99  integer, parameter :: {ixglo^d = 1|, }
100 
101  !> Upper index of grid block arrays
102  integer :: ixghi^d
103 
104  !> Lower index of stagger grid block arrays (always 0)
105  integer, parameter :: {ixgslo^d = 0|, }
106 
107  !> Upper index of stagger grid block arrays
108  integer :: ixgshi^d
109 
110  !> Number of ghost cells surrounding a grid
111  integer :: nghostcells = 2
112 
113  integer, parameter :: stretch_none = 0 !< No stretching
114  integer, parameter :: stretch_uni = 1 !< Unidirectional stretching from a side
115  integer, parameter :: stretch_symm = 2 !< Symmetric stretching around the center
116 
117  !> If true, adjust mod_geometry routines to account for grid stretching (but
118  !> the flux computation will not)
120  !> True if a dimension is stretched
121  logical :: stretched_dim(ndim)
122  !> What kind of stretching is used per dimension
123  integer :: stretch_type(ndim)
124  !> stretch factor between cells at AMR level 1, per dimension
125  double precision :: qstretch_baselevel(ndim)
126  !> (even) number of (symmetrically) stretched
127  !> blocks at AMR level 1, per dimension
129  !> (even) number of (symmetrically) stretched blocks per level and dimension
130  integer, allocatable :: nstretchedblocks(:,:)
131  !> physical extent of stretched border in symmetric stretching
132  double precision :: xstretch^d
133  !> Stretching factors and first cell size for each AMR level and dimension
134  double precision, allocatable :: qstretch(:,:), dxfirst(:,:), &
135  dxfirst_1mq(:,:), dxmid(:,:)
136 
137  !> grid hierarchy info (level and grid indices)
138  integer, parameter :: nodehi=^nd+1
139  integer, parameter :: plevel_=1
140  integer, parameter :: pig^d_=plevel_+^d
141 
142  integer, allocatable :: node(:,:)
143  integer, allocatable :: node_sub(:,:)
144 
145  !> grid location info (corner coordinates and grid spacing)
146  integer, parameter :: rnodehi=3*^nd
147  integer, parameter :: rpxmin0_=0
148  integer, parameter :: rpxmin^d_=rpxmin0_+^d
149  integer, parameter :: rpxmax0_=^nd
150  integer, parameter :: rpxmax^d_=rpxmax0_+^d
151  integer, parameter :: rpdx^d_=2*^nd+^d
152 
153  !> Corner coordinates
154  double precision, allocatable :: rnode(:,:)
155  double precision, allocatable :: rnode_sub(:,:)
156 
157  double precision, allocatable :: dx(:,:)
158  double precision :: dxlevel(ndim)
159 
160  ! IO related quantities
161 
162  !> Maximum number of saves that can be defined by tsave or itsave
163  integer, parameter :: nsavehi=100
164 
165  !> Number of output methods
166  integer, parameter :: nfile = 5
167 
168  !> index number of the latest existing data file
169  integer :: index_latest_data
170 
171  !> Names of the output methods
172  character(len=40), parameter :: output_names(nfile) = &
173  ['log ', 'normal ', 'slice ', 'collapsed', 'analysis ']
174 
175  !> User parameter file
176  character(len=std_len) :: usr_filename
177 
178  !> If collapse(DIM) is true, generate output integrated over DIM
179  logical :: collapse(ndim)
180 
181  !> Save output of type N on times tsave(:, N)
182  double precision :: tsave(nsavehi,nfile)
183 
184  double precision :: tsavelast(nfile)
185 
186  !> Repeatedly save output of type N when dtsave(N) simulation time has passed
187  double precision :: dtsave(nfile)
188 
189  !> Save output of type N on iterations itsave(:, N)
190  integer :: itsave(nsavehi,nfile)
191 
192  integer :: itsavelast(nfile)
193 
194  !> Repeatedly save output of type N when ditsave(N) time steps have passed
195  integer :: ditsave(nfile)
196 
197  integer :: isavet(nfile)
198 
199  integer :: isaveit(nfile)
200 
201  !> Start of read out (not counting specified read outs)
202  double precision :: tsavestart(nfile)
203 
204  !> The level at which to produce line-integrated / collapsed output
205  integer :: collapselevel
206 
207  !> Number of saved files of each type
208  integer :: n_saves(1:nfile)
209 
210  !> whether or not to save an output file
211  logical :: save_file(nfile)
212 
213  !> to monitor timeintegration loop at given wall-clock time intervals
214  double precision :: time_between_print
215 
216  !> accumulated wall-clock time spent on boundary conditions
217  double precision :: time_bc
218 
219  !> IO: snapshot and collapsed views output numbers/labels
221 
222  !> Constant indicating log output
223  integer, parameter :: filelog_ = 1
224 
225  !> Constant indicating regular output
226  integer, parameter :: fileout_ = 2
227 
228  !> Constant indicating slice output
229  integer, parameter :: fileslice_ = 3
230 
231  !> Constant indicating collapsed output
232  integer, parameter :: filecollapse_ = 4
233 
234  !> Constant indicating analysis output (see @ref analysis.md)
235  integer, parameter :: fileanalysis_ = 5
236 
237  !> Unit for standard input
238  integer, parameter :: unitstdin=5
239 
240  !> Unit for standard output
241  integer, parameter :: unitterm=6
242 
243  !> Unit for error messages
244  integer, parameter :: uniterr=6
245 
246  !> file handle for IO
247  integer, parameter :: unitpar=9
248  integer, parameter :: unitconvert=10
249  integer, parameter :: unitslice=11
250  integer, parameter :: unitsnapshot=12
251  integer, parameter :: unitcollapse=13
252  integer, parameter :: unitanalysis=14
253 
254  !> Number of auxiliary variables that are only included in output
255  integer :: nwauxio
256 
257  !> IO switches for conversion
258  logical :: nocartesian
259  logical, allocatable :: w_write(:)
260  logical, allocatable :: writelevel(:)
261  double precision :: writespshift(ndim,2)
263 
264  !> Which par files are used as input
265  character(len=std_len), allocatable :: par_files(:)
266 
267  !> Base file name for simulation output, which will be followed by a number
268  character(len=std_len) :: base_filename
269 
270  !> If not 'unavailable', resume from snapshot with this base file name
271  character(len=std_len) :: restart_from_file
272 
273  !> Which type of log to write: 'normal', 'special', 'regression_test'
274  character(len=std_len) :: typefilelog
275 
276  !> Resume from the snapshot with this index
277  integer :: snapshotini
278 
279  !> If true, restart a previous run from the latest snapshot
281 
282  !> If true and restart_from_file is given, convert snapshots to
283  !> other file formats
284  logical :: convert
285 
286  !> If true, already convert to output format during the run
287  logical :: autoconvert
288 
289  !> If true, convert from conservative to primitive variables in output
290  logical :: saveprim
291 
292  !> Which format to use when converting
293  !>
294  !> Options are: tecplot, tecplotCC, vtu, vtuCC, vtuB, vtuBCC,
295  !> tecplotmpi, tecplotCCmpi, vtumpi, vtuCCmpi, vtuBmpi, vtuBCCmpi, pvtumpi, pvtuCCmpi,
296  !> pvtuBmpi, pvtuBCCmpi, tecline, teclinempi, onegrid
297  character(len=std_len) :: convert_type
298 
299  character(len=std_len) :: collapse_type
300 
301  !> Conversion factors the primitive variables
302  double precision, allocatable :: w_convert_factor(:)
303 
304  double precision :: length_convert_factor
305 
306  !> Conversion factor for time unit
307  double precision :: time_convert_factor
308 
309  !> Stores the memory and load imbalance, used in printlog
310  double precision :: xload, xmemory
311 
312  !> Save a snapshot before crash a run met unphysical values
313  logical :: crash=.false.
314 
315  ! Physics factors
316 
317  !> Physical scaling factor for length
318  double precision :: unit_length=1.d0
319 
320  !> Physical scaling factor for time
321  double precision :: unit_time=1.d0
322 
323  !> Physical scaling factor for density
324  double precision :: unit_density=1.d0
325 
326  !> Physical scaling factor for velocity
327  double precision :: unit_velocity=1.d0
328 
329  !> Physical scaling factor for temperature
330  double precision :: unit_temperature=1.d0
331 
332  !> Physical scaling factor for pressure
333  double precision :: unit_pressure=1.d0
334 
335  !> Physical scaling factor for magnetic field
336  double precision :: unit_magneticfield=1.d0
337 
338  !> Physical scaling factor for number density
339  double precision :: unit_numberdensity=1.d0
340 
341  !> Physical scaling factor for charge
342  double precision :: unit_charge=1.d0
343 
344  !> Physical scaling factor for mass
345  double precision :: unit_mass=1.d0
346 
347  !> Normalised speed of light
348  double precision :: c_norm=1.d0
349 
350  !> Physical scaling factor for Opacity
351  double precision :: unit_opacity=1.d0
352 
353  !> Physical scaling factor for radiation flux
354  double precision :: unit_radflux=1.d0
355 
356  !> error handling
358 
359  !> amplitude of background dipolar, quadrupolar, octupolar, user's field
360  double precision :: bdip=0.d0
361  double precision :: bquad=0.d0
362  double precision :: boct=0.d0
363  double precision :: busr=0.d0
364 
365  !> check and optionally fix unphysical small values (density, gas pressure)
366  logical :: check_small_values=.true.
367  logical :: fix_small_values=.false.
368 
369  !> split magnetic field as background B0 field
370  ! TODO these should be moved in a different file
371  logical :: b0field=.false.
372  logical :: b0fieldalloccoarse=.false.
373 
374  ! number of equilibrium set variables, besides the mag field
375  integer :: number_equi_vars = 0
376 
377  !> Use SI units (.true.) or use cgs units (.false.)
378  logical :: si_unit=.false.
379 
380  !> Use TRAC (Johnston 2019 ApJL, 873, L22) for MHD or 1D HD
381  logical :: phys_trac=.false.
382  integer :: phys_trac_type=1
383  double precision :: phys_trac_mask
384 
385  !> Use particles module or not
386  logical :: use_particles=.false.
387 
388  !> Use multigrid (only available in 2D and 3D)
389  logical :: use_multigrid = .false.
390 
391  ! AMR switches
392 
393  !> The maximum number of grid blocks in a processor
394  integer :: max_blocks
395 
396  !> The maximum number of levels in the grid refinement
397  integer, parameter :: nlevelshi = 20
398 
399  !> Maximal number of AMR levels
400  integer :: refine_max_level
401 
402  !> Weights of variables used to calculate error for mesh refinement
403  double precision, allocatable :: w_refine_weight(:)
404 
405  !> Fix the AMR grid after this time
406  double precision :: tfixgrid
407 
408  !> Whether to apply flux conservation at refinement boundaries
409  logical :: fix_conserve_global = .true.
410 
411  !> Fix the AMR grid after this many time steps
412  integer :: itfixgrid
413 
414  !> Reconstruct the AMR grid once every ditregrid iteration(s)
415  integer :: ditregrid
416 
417  !> refinement: lohner estimate wavefilter setting
418  double precision, allocatable :: amr_wavefilter(:)
419 
420  integer :: refine_criterion
421  logical :: prolongprimitive=.false.
422  logical :: coarsenprimitive=.false.
423 
424  !> Error tolerance for refinement decision
425  double precision, allocatable :: refine_threshold(:)
426  double precision, allocatable :: derefine_ratio(:)
427 
428  !> If true, rebuild the AMR grid upon restarting
429  logical :: reset_grid
430  !> True for using stagger grid
431  logical :: stagger_grid=.false.
432  !> True for record electric field
433  logical :: record_electric_field=.false.
434 
435  !> Number of cells as buffer zone
436  integer :: nbufferx^d
437 
438  integer :: levmin
439  integer :: levmax
440  integer :: levmax_sub
441 
442  ! Miscellaneous
443 
444  !> problem switch allowing different setups in same usr_mod.t
445  integer :: iprob
446 
447  !> Kronecker delta tensor
448  integer :: kr(3,3)
449 
450  !> Levi-Civita tensor
451  integer :: lvc(3,3,3)
452 
453  ! Time integration aspects
454 
455  double precision :: dt
456 
457  logical :: time_advance
458 
459  !> The Courant (CFL) number used for the simulation
460  double precision :: courantpar
461 
462  !> How to compute the CFL-limited time step
463  integer :: type_courant=1
464  !> integer switchers for type courant
465  integer, parameter :: type_maxsum=1
466  integer, parameter :: type_summax=2
467  integer, parameter :: type_minimum=3
468 
469  !> If dtpar is positive, it sets the timestep dt, otherwise courantpar is used
470  !> to limit the time step based on the Courant condition.
471  double precision :: dtpar
472 
473  !> For resistive MHD, the time step is also limited by the diffusion time:
474  !> \f$ dt < dtdiffpar \times dx^2/eta \f$
475  double precision :: dtdiffpar
476 
477  !> The global simulation time
478  double precision :: global_time
479 
480  !> Start time for the simulation
481  double precision :: time_init
482 
483  !> End time for the simulation
484  double precision :: time_max
485 
486  !> Ending wall time (in hours) for the simulation
487  double precision :: wall_time_max
488 
489  !> Stop the simulation when the time step becomes smaller than this value
490  double precision :: dtmin
491 
492  !> Force timeloop exit when final dt < dtmin
493  logical :: final_dt_exit
494 
495  !> If true, reset iteration count and global_time to original values, and
496  !> start writing snapshots at index 0
497  logical :: reset_time
498 
499  !> If true, reset iteration count to 0
500  logical :: reset_it
501 
502  !> If true, allow final dt reduction for matching time_max on output
504 
505  !> If true, call initonegrid_usr upon restarting
506  logical :: firstprocess
507 
508  !> If true, wall time is up, modify snapshotnext for later overwrite
509  logical :: pass_wall_time
510 
511  !> If true, do H-correction to fix the carbuncle problem at grid-aligned shocks
512  logical :: h_correction=.false.
513 
514  !> Number of time steps taken
515  integer :: it
516 
517  !> Stop the simulation after this many time steps have been taken
518  integer :: it_max
519 
520  !> initial iteration count
521  integer :: it_init
522 
523  !> If > 1, then in the first slowsteps-1 time steps dt is reduced
524  !> by a factor \f$ 1 - (1- step/slowsteps)^2 \f$
525  integer :: slowsteps
526 
527  ! Method switches
528 
529  !> Index of the sub-step in a multi-step time integrator
530  integer :: istep
531 
532  !> How many sub-steps the time integrator takes
533  integer :: nstep
534 
535  !> Which flux scheme of spatial discretization to use (per grid level)
536  integer, allocatable :: flux_method(:)
537 
538  !> The spatial discretization for the predictor step when using a two
539  !> step PC method
540  integer, allocatable :: typepred1(:)
541 
542  !> flux schemes
543  integer, parameter :: fs_hll=1
544  integer, parameter :: fs_hllc=2
545  integer, parameter :: fs_hlld=3
546  integer, parameter :: fs_hllcd=4
547  integer, parameter :: fs_tvdlf=5
548  integer, parameter :: fs_tvdmu=6
549  integer, parameter :: fs_tvd=7
550  integer, parameter :: fs_hancock=8
551  integer, parameter :: fs_cd=9
552  integer, parameter :: fs_cd4=10
553  integer, parameter :: fs_fd=11
554  integer, parameter :: fs_source=12
555  integer, parameter :: fs_nul=13
556 
557  !> time stepper type
558  integer :: t_stepper=0
559  integer, parameter :: onestep=1
560  integer, parameter :: twostep=2
561  integer, parameter :: threestep=3
562  integer, parameter :: fourstep=4
563  integer, parameter :: fivestep=5
564 
565  !> time integrator method
566  integer :: t_integrator=0
567  integer, parameter :: forward_euler=1
568  integer, parameter :: predictor_corrector=2
569  integer, parameter :: ssprk3=3
570  integer, parameter :: ssprk4=4
571  integer, parameter :: ssprk5=5
572 
573  integer, parameter :: imex_euler=6
574  integer, parameter :: imex_sp=7
575  integer, parameter :: rk2_alf=8
576  integer, parameter :: ssprk2=9
577  integer, parameter :: imex_midpoint=10
578  integer, parameter :: imex_trapezoidal=11
579  integer, parameter :: imex_222=12
580 
581  integer, parameter :: rk3_bt=13
582  integer, parameter :: imex_ars3=14
583  integer, parameter :: imex_232=15
584  integer, parameter :: imex_cb3a=16
585 
586  integer, parameter :: rk4=17
587 
588  !> Type of slope limiter used for reconstructing variables on cell edges
589  integer, allocatable :: type_limiter(:)
590 
591  !> Type of slope limiter used for computing gradients or divergences, when
592  !> typegrad or typediv are set to 'limited'
593  integer, allocatable :: type_gradient_limiter(:)
594 
595  !> background magnetic field location indicator
596  integer :: b0i=0
597 
598  !> Limiter used for prolongation to refined grids and ghost cells
599  integer :: prolong_limiter=0
600 
601  !> Which type of entropy fix to use with Riemann-type solvers
602  character(len=std_len), allocatable :: typeentropy(:)
603 
604  !> Which type of TVD method to use
605  character(len=std_len) :: typetvd
606 
607  !> bound (left/min and right.max) speed of Riemann fan
608  integer :: boundspeed
609 
610  character(len=std_len) :: typeaverage
611  character(len=std_len) :: typedimsplit
612  character(len=std_len) :: geometry_name='default'
613  character(len=std_len) :: typepoly
614 
615  integer :: nxdiffusehllc
616  double precision, allocatable :: entropycoef(:)
617  double precision :: tvdlfeps
618  logical, allocatable :: loglimit(:), logflag(:)
619  logical :: flathllc,flatcd,flatsh
620  !> Use split or unsplit way to add user's source terms, default: unsplit
621  logical :: source_split_usr
622  !> if any normal source term is added in split fasion
623  logical :: any_source_split=.false.
624  logical :: dimsplit
625 
626  !> RK2(alfa) method parameters from Butcher tableau
627  double precision :: rk_a21,rk_b1,rk_b2
628  !> IMEX-222(lambda) one-parameter family of schemes
629  double precision :: imex222_lambda
630  !> SSPRK choice of methods (both threestep and fourstep, Shu-Osher 2N* implementation)
631  !> also fivestep SSPRK54
632  integer :: ssprk_order
636  !> RK3 Butcher table
637  integer :: rk3_switch
639  !> IMEX_ARS3 parameter ars_gamma
640  double precision :: ars_gamma
641  !> IMEX_232 choice and parameters
642  integer :: imex_switch
644  double precision :: imex_b3,imex_c2,imex_c3
645  !> IMEX_CB3a extra parameters
646  double precision :: imex_a22, imex_a33, imex_ha32
647  !> whether IMEX in use or not
648  logical :: use_imex_scheme
649 
650  character(len=std_len) :: typediv,typegrad
651 
652  !> global fastest wave speed needed in fd scheme and glm method
653  double precision :: cmax_global
654 
655  !> global fastest flow speed needed in glm method
656  double precision :: vmax_global
657 
658  !> global largest a2 for schmid scheme
659  double precision :: a2max_global(ndim)
660 
661  !> need global maximal wave speed
662  logical :: need_global_cmax=.false.
663 
664  !> global value for schmid scheme
665  logical :: need_global_a2max=.false.
666 
667  ! Boundary region parameters
668 
669  !> True for dimensions with periodic boundaries
670  logical :: periodb(ndim)
671 
672  !> Indicates whether there is a pole at a boundary
673  logical :: poleb(2,ndim)
674 
675  !> True for dimensions with aperiodic boundaries
676  logical :: aperiodb(ndim)
677 
678  !> True for save physical boundary cells in dat files
680 
681  !> True if a block has any physical boundary
682  logical, allocatable :: phyboundblock(:)
683 
684  !> Array indicating the type of boundary condition per variable and per
685  !> physical boundary
686  integer, allocatable :: typeboundary(:, :)
687  !> boundary condition types
688  integer, parameter :: bc_special=1
689  integer, parameter :: bc_cont=2
690  integer, parameter :: bc_symm=3
691  integer, parameter :: bc_asymm=4
692  integer, parameter :: bc_periodic=5
693  integer, parameter :: bc_aperiodic=6
694  integer, parameter :: bc_noinflow=7
695  integer, parameter :: bc_data=8
696  integer, parameter :: bc_character=9
697  integer, parameter :: bc_icarus=10
698 
699  !> whether copy values instead of interpolation in ghost cells of finer blocks
700  logical :: ghost_copy=.false.
701 
702  !> if there is an internal boundary
703  logical :: internalboundary
704 
705  !> Base file name for synthetic EUV emission output
706  character(len=std_len) :: filename_euv
707  !> wavelength for output
708  integer :: wavelength
709  !> times for enhancing spatial resolution for EUV image/spectra
710  double precision :: instrument_resolution_factor
711  !> use arcsec as length unit of images/spectra
713  !> Base file name for synthetic SXR emission output
714  character(len=std_len) :: filename_sxr
715  ! minimum and maximum energy of SXR (keV)
716  integer :: emin_sxr,emax_sxr
717  !> Base file name for synthetic white light
718  character(len=std_len) :: filename_whitelight
719  !> white light observation instrument
720  character(len=std_len) :: whitelight_instrument
721  !> the white light emission below it (unit=Rsun) is not visible
722  double precision :: r_occultor
723  !> direction of the line of sight (LOS)
724  double precision :: los_theta,los_phi
725  !> rotation of image
726  double precision :: image_rotate
727  !> where the is the origin (X=0,Y=0) of image
728  double precision :: x_origin(1:3)
729  !> big image
730  logical :: big_image
731  !> Base file name for synthetic EUV spectrum output
732  character(len=std_len) :: filename_spectrum
733  !> wave length for spectrum
734  integer :: spectrum_wl
735  !> spectral window
737  !> location of the slit
738  double precision :: location_slit
739  !> direction of the slit (for dat resolution only)
740  integer :: direction_slit
741  !> for spherical coordinate, region below it (unit=Rsun) is treated as not transparent
742  double precision :: r_opt_thick
743  !> resolution of the images
744  logical :: dat_resolution
745 
746  !> Block pointer for using one block and its previous state
747  type(state), pointer :: block
748 
749  !$OMP THREADPRIVATE(block,dxlevel,b0i)
750 
751 contains
752 
753  !> Cross product of two vectors
754  pure subroutine cross_product(ixI^L,ixO^L,a,b,axb)
755  integer, intent(in) :: ixi^l, ixo^l
756  double precision, intent(in) :: a(ixi^s,3), b(ixi^s,3)
757  double precision, intent(out) :: axb(ixi^s,3)
758 
759  axb(ixo^s,1)=a(ixo^s,2)*b(ixo^s,3)-a(ixo^s,3)*b(ixo^s,2)
760  axb(ixo^s,2)=a(ixo^s,3)*b(ixo^s,1)-a(ixo^s,1)*b(ixo^s,3)
761  axb(ixo^s,3)=a(ixo^s,1)*b(ixo^s,2)-a(ixo^s,2)*b(ixo^s,1)
762  end subroutine cross_product
763 
764 end module mod_global_parameters
Module with basic data types used in amrvac.
This module contains variables that describe the connectivity of the mesh and also data structures fo...
Module for physical and numeric constants.
Definition: mod_constants.t:2
This module contains definitions of global parameters and variables and some generic functions/subrou...
character(len=std_len), dimension(:), allocatable typeentropy
Which type of entropy fix to use with Riemann-type solvers.
double precision, dimension(nfile) tsavelast
double precision, dimension(:), allocatable w_convert_factor
Conversion factors the primitive variables.
type(state), pointer block
Block pointer for using one block and its previous state.
double precision xload
Stores the memory and load imbalance, used in printlog.
integer, parameter unitslice
integer nstep
How many sub-steps the time integrator takes.
logical h_correction
If true, do H-correction to fix the carbuncle problem at grid-aligned shocks.
integer it_max
Stop the simulation after this many time steps have been taken.
logical, dimension(ndim) aperiodb
True for dimensions with aperiodic boundaries.
logical internalboundary
if there is an internal boundary
double precision r_opt_thick
for spherical coordinate, region below it (unit=Rsun) is treated as not transparent
character(len=std_len) filename_sxr
Base file name for synthetic SXR emission output.
integer spectrum_wl
wave length for spectrum
logical nocartesian
IO switches for conversion.
integer, dimension(:), allocatable typepred1
The spatial discretization for the predictor step when using a two step PC method.
double precision dtdiffpar
For resistive MHD, the time step is also limited by the diffusion time: .
character(len=std_len) typegrad
integer ixgshi
Upper index of stagger grid block arrays.
logical reset_it
If true, reset iteration count to 0.
double precision unit_charge
Physical scaling factor for charge.
integer, parameter bc_noinflow
integer type_coarse_block
MPI type for block coarsened by 2, and for its children blocks.
integer, parameter fs_tvdlf
double precision small_pressure
integer ixghi
Upper index of grid block arrays.
integer, parameter stretch_uni
Unidirectional stretching from a side.
character(len=std_len) geometry_name
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.
logical activate_unit_arcsec
use arcsec as length unit of images/spectra
character(len=std_len) typepoly
integer, parameter fs_hlld
logical source_split_usr
Use split or unsplit way to add user's source terms, default: unsplit.
integer, parameter imex_euler
double precision unit_opacity
Physical scaling factor for Opacity.
integer domain_nx
number of cells for each dimension in level-one mesh
integer, parameter unitpar
file handle for IO
character(len=std_len) filename_spectrum
Base file name for synthetic EUV spectrum output.
logical, dimension(nfile) save_file
whether or not to save an output file
logical any_source_split
if any normal source term is added in split fasion
integer, parameter bc_asymm
logical resume_previous_run
If true, restart a previous run from the latest snapshot.
double precision global_time
The global simulation time.
integer type_block_xc_io
MPI type for IO: cell corner (xc) or cell center (xcc) coordinates.
integer, dimension(nsavehi, nfile) itsave
Save output of type N on iterations itsave(:, N)
double precision unit_mass
Physical scaling factor for mass.
logical use_imex_scheme
whether IMEX in use or not
integer istep
Index of the sub-step in a multi-step time integrator.
double precision time_max
End time for the simulation.
integer, dimension(3, 3) kr
Kronecker delta tensor.
integer, parameter threestep
double precision xstretch
physical extent of stretched border in symmetric stretching
logical, dimension(:), allocatable logflag
double precision time_init
Start time for the simulation.
logical stretch_uncentered
If true, adjust mod_geometry routines to account for grid stretching (but the flux computation will n...
double precision phys_trac_mask
logical firstprocess
If true, call initonegrid_usr upon restarting.
integer, parameter imex_232
integer snapshotini
Resume from the snapshot with this index.
double precision small_temperature
error handling
double precision xprob
minimum and maximum domain boundaries for each dimension
integer it
Number of time steps taken.
character(len=std_len) filename_euv
Base file name for synthetic EUV emission output.
logical, dimension(:), allocatable loglimit
double precision, dimension(:), allocatable dg
extent of grid blocks in domain per dimension, in array over levels
integer, parameter fivestep
integer, parameter bc_character
integer it_init
initial iteration count
integer, dimension(:, :), allocatable typeboundary
Array indicating the type of boundary condition per variable and per physical boundary.
integer ditregrid
Reconstruct the AMR grid once every ditregrid iteration(s)
logical saveprim
If true, convert from conservative to primitive variables in output.
double precision ars_gamma
IMEX_ARS3 parameter ars_gamma.
double precision unit_numberdensity
Physical scaling factor for number density.
integer, parameter fs_hllcd
character(len=std_len) filename_whitelight
Base file name for synthetic white light.
character(len=std_len) convert_type
Which format to use when converting.
double precision unit_pressure
Physical scaling factor for pressure.
integer, parameter type_maxsum
integer switchers for type courant
integer, parameter ndim
Number of spatial dimensions for grid variables.
integer itfixgrid
Fix the AMR grid after this many time steps.
integer, parameter filecollapse_
Constant indicating collapsed output.
integer prolong_limiter
Limiter used for prolongation to refined grids and ghost cells.
double precision, dimension(:), allocatable amr_wavefilter
refinement: lohner estimate wavefilter setting
double precision unit_length
Physical scaling factor for length.
integer, parameter nlevelshi
The maximum number of levels in the grid refinement.
double precision location_slit
location of the slit
logical save_physical_boundary
True for save physical boundary cells in dat files.
double precision vmax_global
global fastest flow speed needed in glm method
logical stagger_grid
True for using stagger grid.
double precision cmax_global
global fastest wave speed needed in fd scheme and glm method
double precision time_convert_factor
Conversion factor for time unit.
logical, dimension(:), allocatable phyboundblock
True if a block has any physical boundary.
integer, dimension(:,:), allocatable nstretchedblocks
(even) number of (symmetrically) stretched blocks per level and dimension
integer, parameter imex_ars3
integer, dimension(^nd, 2^d &) type_coarse_block_stg
MPI type for staggered block coarsened by 2, and for its children blocks.
integer, parameter bc_data
logical use_particles
Use particles module or not.
integer, parameter fs_tvdmu
character(len=std_len), dimension(:), allocatable par_files
Which par files are used as input.
integer icomm
The MPI communicator.
integer, dimension(:), allocatable ng
number of grid blocks in domain per dimension, in array over levels
logical reset_time
If true, reset iteration count and global_time to original values, and start writing snapshots at ind...
double precision bdip
amplitude of background dipolar, quadrupolar, octupolar, user's field
integer b0i
background magnetic field location indicator
integer, parameter imex_trapezoidal
integer, parameter nsavehi
Maximum number of saves that can be defined by tsave or itsave.
character(len=std_len) whitelight_instrument
white light observation instrument
integer mype
The rank of the current MPI task.
double precision dtpar
If dtpar is positive, it sets the timestep dt, otherwise courantpar is used to limit the time step ba...
integer, dimension(1:nfile) n_saves
Number of saved files of each type.
character(len=std_len) typediv
integer block_nx
number of cells for each dimension in grid block excluding ghostcells
integer type_block_io
MPI type for IO: block excluding ghost cells.
double precision, dimension(nfile) tsavestart
Start of read out (not counting specified read outs)
integer, dimension(nfile) ditsave
Repeatedly save output of type N when ditsave(N) time steps have passed.
integer, parameter plevel_
integer, dimension(2^d &) type_sub_block
logical, dimension(ndim) collapse
If collapse(DIM) is true, generate output integrated over DIM.
integer, parameter unitstdin
Unit for standard input.
integer, dimension(:), allocatable, parameter d
logical local_timestep
each cell has its own timestep or not
character(len=std_len) usr_filename
User parameter file.
logical need_global_a2max
global value for schmid scheme
logical ghost_copy
whether copy values instead of interpolation in ghost cells of finer blocks
double precision length_convert_factor
integer, parameter nodehi
grid hierarchy info (level and grid indices)
integer ndir
Number of spatial dimensions (components) for vector variables.
integer, parameter uniterr
Unit for error messages.
double precision imex222_lambda
IMEX-222(lambda) one-parameter family of schemes.
double precision courantpar
The Courant (CFL) number used for the simulation.
double precision wall_time_max
Ending wall time (in hours) for the simulation.
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.
integer, dimension(:), allocatable flux_method
Which flux scheme of spatial discretization to use (per grid level)
character(len=std_len) collapse_type
logical slab
Cartesian geometry or not.
integer slowsteps
If > 1, then in the first slowsteps-1 time steps dt is reduced by a factor .
integer ssprk_order
SSPRK choice of methods (both threestep and fourstep, Shu-Osher 2N* implementation) also fivestep SSP...
double precision image_rotate
rotation of image
double precision, dimension(:,:), allocatable qstretch
Stretching factors and first cell size for each AMR level and dimension.
integer, parameter bc_periodic
integer type_block_wc_io
MPI type for IO: cell corner (wc) or cell center (wcc) variables.
integer type_courant
How to compute the CFL-limited time step.
integer, parameter bc_special
boundary condition types
integer snapshotnext
IO: snapshot and collapsed views output numbers/labels.
double precision unit_magneticfield
Physical scaling factor for magnetic field.
integer, parameter unitanalysis
integer, parameter rk2_alf
logical, dimension(ndim) stretched_dim
True if a dimension is stretched.
logical dat_resolution
resolution of the images
double precision r_occultor
the white light emission below it (unit=Rsun) is not visible
integer, dimension(ndim) nstretchedblocks_baselevel
(even) number of (symmetrically) stretched blocks at AMR level 1, per dimension
integer npe
The number of MPI tasks.
integer nwauxio
Number of auxiliary variables that are only included in output.
double precision unit_velocity
Physical scaling factor for velocity.
integer index_latest_data
index number of the latest existing data file
integer, dimension(nfile) itsavelast
integer, parameter stretch_none
No stretching.
double precision, dimension(ndim) qstretch_baselevel
stretch factor between cells at AMR level 1, per dimension
double precision, dimension(ndim, 2) writespshift
integer imex_switch
IMEX_232 choice and parameters.
integer, parameter fs_hll
flux schemes
double precision time_between_print
to monitor timeintegration loop at given wall-clock time intervals
integer, parameter unitterm
Unit for standard output.
double precision, dimension(nfile) dtsave
Repeatedly save output of type N when dtsave(N) simulation time has passed.
logical, dimension(:), allocatable w_write
integer iprob
problem switch allowing different setups in same usr_mod.t
character(len=std_len) restart_from_file
If not 'unavailable', resume from snapshot with this base file name.
logical, dimension(ndim) periodb
True for dimensions with periodic boundaries.
double precision c_norm
Normalised speed of light.
logical b0field
split magnetic field as background B0 field
double precision, dimension(:,:), allocatable rnode
Corner coordinates.
integer, parameter filelog_
Constant indicating log output.
character(len=40), dimension(nfile), parameter output_names
Names of the output methods.
double precision unit_temperature
Physical scaling factor for temperature.
double precision unit_radflux
Physical scaling factor for radiation flux.
integer, dimension(:), allocatable type_limiter
Type of slope limiter used for reconstructing variables on cell edges.
integer, parameter imex_sp
logical final_dt_reduction
If true, allow final dt reduction for matching time_max on output.
integer, parameter bc_cont
logical si_unit
Use SI units (.true.) or use cgs units (.false.)
logical, dimension(:), allocatable writelevel
integer, parameter unitcollapse
integer, parameter fileout_
Constant indicating regular output.
double precision los_theta
direction of the line of sight (LOS)
integer, parameter type_summax
character(len=std_len) typetvd
Which type of TVD method to use.
integer nbufferx
Number of cells as buffer zone.
double precision, dimension(:), allocatable entropycoef
integer, parameter twostep
double precision time_bc
accumulated wall-clock time spent on boundary conditions
double precision, dimension(:,:), allocatable dx
integer, parameter rpxmax0_
integer type_block
MPI type for block including ghost cells and its size.
integer, parameter onestep
double precision rk_a21
RK2(alfa) method parameters from Butcher tableau.
integer, parameter predictor_corrector
double precision tfixgrid
Fix the AMR grid after this time.
integer, parameter bc_icarus
integer, parameter unitsnapshot
pure subroutine cross_product(ixIL, ixOL, a, b, axb)
Cross product of two vectors.
integer nghostcells
Number of ghost cells surrounding a grid.
double precision, dimension(:), allocatable w_refine_weight
Weights of variables used to calculate error for mesh refinement.
integer, parameter sdim
starting dimension for electric field
integer, parameter bc_symm
integer, parameter forward_euler
logical phys_trac
Use TRAC (Johnston 2019 ApJL, 873, L22) for MHD or 1D HD.
logical fix_conserve_global
Whether to apply flux conservation at refinement boundaries.
character(len=std_len) typedimsplit
character(len=std_len) typeaverage
character(len= *), parameter undefined
double precision, dimension(nsavehi, nfile) tsave
Save output of type N on times tsave(:, N)
double precision spectrum_window_max
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.
integer wavelength
wavelength for output
integer collapselevel
The level at which to produce line-integrated / collapsed output.
logical reset_grid
If true, rebuild the AMR grid upon restarting.
integer, dimension(ndim) stretch_type
What kind of stretching is used per dimension.
logical crash
Save a snapshot before crash a run met unphysical values.
integer t_stepper
time stepper type
double precision, dimension(:,:), allocatable rnode_sub
logical use_multigrid
Use multigrid (only available in 2D and 3D)
logical slab_uniform
uniform Cartesian geometry or not (stretched Cartesian)
integer, parameter fourstep
double precision, dimension(:), allocatable refine_threshold
Error tolerance for refinement decision.
character(len=std_len) base_filename
Base file name for simulation output, which will be followed by a number.
integer, parameter rnodehi
grid location info (corner coordinates and grid spacing)
double precision instrument_resolution_factor
times for enhancing spatial resolution for EUV image/spectra
double precision small_density
double precision spectrum_window_min
spectral window
double precision dtmin
Stop the simulation when the time step becomes smaller than this value.
integer refine_max_level
Maximal number of AMR levels.
integer, parameter fs_hllc
integer, parameter fileslice_
Constant indicating slice output.
double precision, dimension(:), allocatable derefine_ratio
integer, parameter nfile
Number of output methods.
integer max_blocks
The maximum number of grid blocks in a processor.
integer, parameter stretch_symm
Symmetric stretching around the center.
integer, parameter fileanalysis_
Constant indicating analysis output (see Writing a custom analysis subroutine)
integer r_
Indices for cylindrical coordinates FOR TESTS, negative value when not used:
integer rk3_switch
RK3 Butcher table.
integer, parameter rpxmin0_
integer, parameter bc_aperiodic
character(len=std_len) typefilelog
Which type of log to write: 'normal', 'special', 'regression_test'.
double precision imex_a22
IMEX_CB3a extra parameters.
integer direction_slit
direction of the slit (for dat resolution only)
integer type_block_io_stg
MPI type for IO of staggered variables.
logical, dimension(2, ndim) poleb
Indicates whether there is a pole at a boundary.
integer boundspeed
bound (left/min and right.max) speed of Riemann fan
logical pass_wall_time
If true, wall time is up, modify snapshotnext for later overwrite.
integer, parameter imex_cb3a
integer, parameter ixgslo
Lower index of stagger grid block arrays (always 0)
double precision, dimension(1:3) x_origin
where the is the origin (X=0,Y=0) of image
logical record_electric_field
True for record electric field.
integer, parameter imex_222
integer, parameter unitconvert
double precision, dimension(:,:), allocatable dxfirst
integer t_integrator
time integrator method
integer, parameter fs_hancock
logical final_dt_exit
Force timeloop exit when final dt < dtmin.
integer, dimension(nfile) isaveit
integer, dimension(:), allocatable type_gradient_limiter
Type of slope limiter used for computing gradients or divergences, when typegrad or typediv are set t...
integer, dimension(:,:), allocatable node
integer, dimension(:,:), allocatable node_sub
integer, parameter type_minimum
integer, parameter fs_source
double precision, dimension(ndim) dxlevel
integer, dimension(nfile) isavet
integer, parameter imex_midpoint
double precision, dimension(:,:), allocatable dxfirst_1mq
double precision, dimension(ndim) a2max_global
global largest a2 for schmid scheme
logical check_small_values
check and optionally fix unphysical small values (density, gas pressure)
double precision, dimension(:,:), allocatable dxmid
integer, parameter ixglo
Lower index of grid block arrays (always 1)
integer log_fh
MPI file handle for logfile.