physics_base.f90
Go to the documentation of this file.
1 !#############################################################################
2 !# #
3 !# fosite - 3D hydrodynamical simulation program #
4 !# module: physics_base.f90 #
5 !# #
6 !# Copyright (C) 2007 - 2018 #
7 !# Tobias Illenseer <tillense@astrophysik.uni-kiel.de> #
8 !# Björn Sperling <sperling@astrophysik.uni-kiel.de> #
9 !# Manuel Jung <mjung@astrophysik.uni-kiel.de> #
10 !# Jannes Klee <jklee@astrophysik.uni-kiel.de> #
11 !# #
12 !# This program is free software; you can redistribute it and/or modify #
13 !# it under the terms of the GNU General Public License as published by #
14 !# the Free Software Foundation; either version 2 of the License, or (at #
15 !# your option) any later version. #
16 !# #
17 !# This program is distributed in the hope that it will be useful, but #
18 !# WITHOUT ANY WARRANTY; without even the implied warranty of #
19 !# MERCHANTABILITY OR FITNESS FOR A PARTICULAR PURPOSE, GOOD TITLE or #
20 !# NON INFRINGEMENT. See the GNU General Public License for more #
21 !# details. #
22 !# #
23 !# You should have received a copy of the GNU General Public License #
24 !# along with this program; if not, write to the Free Software #
25 !# Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. #
26 !# #
27 !#############################################################################
32 !----------------------------------------------------------------------------!
43 !----------------------------------------------------------------------------!
54 !----------------------------------------------------------------------------!
58  USE mesh_base_mod
59  USE marray_base_mod
61  USE common_dict
62  IMPLICIT NONE
63  !--------------------------------------------------------------------------!
64  PRIVATE
66  enum, bind(c)
67  enumerator :: undefined=0, primitive=1, conservative=2
68  END enum
69  TYPE, ABSTRACT, EXTENDS(logging_base) :: physics_base
71  CLASS(constants_base), ALLOCATABLE :: constants
74  REAL :: time,& !< simulation time
75  mu, & !< mean molecular weight
76  eps
77  INTEGER :: vnum, & !< number of variables
78  pnum, & !< number of passive variables
79  vdim, & !< vector dimensions (1, 2 or 3)
80  density,pressure, &
81  energy,sgspressure, &
82  sgsenergy, &
83  xvelocity,xmomentum, &
84  yvelocity,ymomentum,&
85  zvelocity,zmomentum
86  LOGICAL :: transformed_xvelocity
87  LOGICAL :: transformed_yvelocity
88  LOGICAL :: transformed_zvelocity
90  LOGICAL :: supports_absorbing
92  LOGICAL :: supports_farfield
94  LOGICAL :: advanced_wave_speeds
95  CHARACTER(LEN=16), DIMENSION(:), POINTER &
96  :: pvarname,cvarname
99  REAL, DIMENSION(:,:,:), POINTER :: &
100  bcradius, & !< distance to the origin bary center values
101  divposvec, & !< divergence of the position vector
102  bphi, & !< bary centered constant gravitational potential
103  tmp,tmp1,tmp2,tmp3, &
104  tmp4,tmp5
105  REAL, DIMENSION(:,:,:,:), POINTER :: &
106  fradius, & !< distance to the origin face values
107  bcposvec, & !< curvilinear components of the position vector bary center values
108  w => null(), &
109  fphi, &
110  hy
111  REAL, DIMENSION(:,:,:,:,:), POINTER &
112  :: fcent, & !< centrifugal force
113  fposvec
114 !------------------------------------------------------------!
115  CONTAINS
116  PROCEDURE :: initphysics
117  PROCEDURE :: printconfiguration
118  procedure(new_statevector), DEFERRED :: new_statevector
119  procedure(externalsources), DEFERRED :: externalsources
120  procedure(enableoutput), DEFERRED :: enableoutput
121  !------Convert2Primitve--------!
122  procedure(convert2primitive_all), DEFERRED :: convert2primitive_all
123  procedure(convert2primitive_subset), DEFERRED :: convert2primitive_subset
124  generic :: convert2primitive => &
125  convert2primitive_all, &
126  convert2primitive_subset
127  !------Convert2Conservative----!
128  procedure(convert2conservative_all), DEFERRED :: convert2conservative_all
129  procedure(convert2conservative_subset), DEFERRED :: convert2conservative_subset
130  generic :: convert2conservative => &
131  convert2conservative_all, &
132  convert2conservative_subset
133  !------Wavespeed Routines-----!
134  procedure(calcwavespeeds_center), DEFERRED :: calcwavespeeds_center
135  procedure(calcwavespeeds_faces), DEFERRED :: calcwavespeeds_faces
136  generic :: calculatewavespeeds => &
137  calcwavespeeds_center, &
138  calcwavespeeds_faces
139  !------Flux Routines-----------!
140  procedure(calcfluxesx), DEFERRED :: calcfluxesx
141  generic :: calculatefluxesx => calcfluxesx
142  procedure(calcfluxesy), DEFERRED :: calcfluxesy
143  generic :: calculatefluxesy => calcfluxesy
144  procedure(calcfluxesz), DEFERRED :: calcfluxesz
145  generic :: calculatefluxesz => calcfluxesz
146  !------Fargo Routines-----------!
147  procedure(addbackgroundvelocityx), DEFERRED :: addbackgroundvelocityx
148  procedure(subtractbackgroundvelocityx), DEFERRED :: subtractbackgroundvelocityx
149  procedure(addbackgroundvelocityy), DEFERRED :: addbackgroundvelocityy
150  procedure(subtractbackgroundvelocityy), DEFERRED :: subtractbackgroundvelocityy
151  procedure(addbackgroundvelocityz), DEFERRED :: addbackgroundvelocityz
152  procedure(subtractbackgroundvelocityz), DEFERRED :: subtractbackgroundvelocityz
153  procedure(addfargosources), DEFERRED :: addfargosources
154  !------Geometry Routines-------!
155  procedure(geometricalsources), DEFERRED :: geometricalsources
156  procedure(masks), DEFERRED :: reflectionmasks
157  procedure(masks), DEFERRED :: axismasks
158  !------Boundary Conditions-----!
159  ! absorbing boundaries
160  procedure(calculatecharsystemx), DEFERRED :: calculatecharsystemx
161  procedure(calculatecharsystemy), DEFERRED :: calculatecharsystemy
162  procedure(calculatecharsystemz), DEFERRED :: calculatecharsystemz
163  procedure(calculateboundarydatax), DEFERRED :: calculateboundarydatax
164  procedure(calculateboundarydatay), DEFERRED :: calculateboundarydatay
165  procedure(calculateboundarydataz), DEFERRED :: calculateboundarydataz
166  ! far field boundaries
167 ! PROCEDURE :: CalculatePrim2RiemannX
168 ! PROCEDURE :: CalculatePrim2RiemannY
169 ! PROCEDURE :: CalculateRiemann2PrimX
170 ! PROCEDURE :: CalculateRiemann2PrimY
171 ! PROCEDURE :: SGSSources
172 ! PROCEDURE :: CalculateSGSTensor
173 ! PROCEDURE :: GetSoundSpeed_adiabatic
174 
175  procedure(finalize), DEFERRED :: finalize
176  PROCEDURE :: finalize_base
177  END TYPE physics_base
178 
179  abstract INTERFACE
180  SUBROUTINE enableoutput(this,Mesh,config,IO)
182  IMPORT physics_base, mesh_base
183  IMPLICIT NONE
184  CLASS(physics_base), INTENT(INOUT) :: this
185  CLASS(mesh_base), INTENT(IN) :: Mesh
186  TYPE(Dict_TYP), POINTER, INTENT(IN) :: config, IO
187  END SUBROUTINE
188  SUBROUTINE new_statevector(this,new_sv,flavour,num)
189  IMPORT physics_base, marray_compound
190  IMPLICIT NONE
191  CLASS(physics_base), INTENT(IN) :: this
192  CLASS(marray_compound), POINTER :: new_sv
193  INTEGER, OPTIONAL, INTENT(IN) :: flavour,num
194  END SUBROUTINE
195  PURE SUBROUTINE convert2primitive_all(this,cvar,pvar)
196  IMPORT physics_base, marray_compound
197  CLASS(physics_base), INTENT(IN) :: this
198  CLASS(marray_compound), INTENT(INOUT) :: cvar,pvar
199  END SUBROUTINE
200  PURE SUBROUTINE convert2primitive_subset(this,i1,i2,j1,j2,k1,k2,cvar,pvar)
201  IMPORT physics_base, marray_compound
202  CLASS(physics_base), INTENT(IN) :: this
203  INTEGER, INTENT(IN) :: i1,i2,j1,j2,k1,k2
204  CLASS(marray_compound), INTENT(INOUT) :: cvar,pvar
205  END SUBROUTINE
206  PURE SUBROUTINE convert2conservative_all(this,pvar,cvar)
207  IMPORT physics_base, marray_compound
208  CLASS(physics_base), INTENT(IN) :: this
209  CLASS(marray_compound), INTENT(INOUT) :: pvar,cvar
210  END SUBROUTINE
211  PURE SUBROUTINE convert2conservative_subset(this,i1,i2,j1,j2,k1,k2,pvar,cvar)
212  IMPORT physics_base, marray_compound
213  CLASS(physics_base), INTENT(IN) :: this
214  INTEGER, INTENT(IN) :: i1,i2,j1,j2,k1,k2
215  CLASS(marray_compound), INTENT(INOUT) :: pvar,cvar
216  END SUBROUTINE
217  PURE SUBROUTINE externalsources(this,accel,pvar,cvar,sterm)
218  IMPORT physics_base, mesh_base, marray_base, marray_compound
219  CLASS(physics_base), INTENT(IN) :: this
220  CLASS(marray_base), INTENT(IN) :: accel
221  CLASS(marray_compound), INTENT(INOUT) :: pvar,cvar,sterm
222  END SUBROUTINE
223  PURE SUBROUTINE calcwavespeeds_center(this,Mesh,pvar,minwav,maxwav)
224  IMPORT physics_base,mesh_base,marray_base,marray_compound
225  CLASS(physics_base), INTENT(INOUT) :: this
226  CLASS(mesh_base), INTENT(IN) :: mesh
227  CLASS(marray_compound), INTENT(INOUT) :: pvar
228  TYPE(marray_base), INTENT(INOUT) :: minwav,maxwav
229  END SUBROUTINE
230  PURE SUBROUTINE calcwavespeeds_faces(this,Mesh,prim,cons,minwav,maxwav)
231  IMPORT physics_base,mesh_base,marray_base,marray_compound
232  CLASS(physics_base), INTENT(INOUT) :: this
233  CLASS(mesh_base), INTENT(IN) :: mesh
234  REAL, DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%JGMIN:Mesh%JGMAX,Mesh%KGMIN:Mesh%KGMAX,Mesh%NFACES,this%VNUM), &
235  INTENT(IN) :: prim,cons
236  TYPE(marray_base), INTENT(INOUT) :: minwav,maxwav
237  END SUBROUTINE
238  PURE SUBROUTINE calcfluxesx(this,Mesh,nmin,nmax,prim,cons,xfluxes)
239  IMPORT physics_base,mesh_base,marray_compound
240  CLASS(physics_base), INTENT(IN) :: this
241  CLASS(mesh_base), INTENT(IN) :: mesh
242  INTEGER, INTENT(IN) :: nmin,nmax
243  CLASS(marray_compound), INTENT(INOUT) :: prim,cons,xfluxes
244  END SUBROUTINE
245  PURE SUBROUTINE calcfluxesy(this,Mesh,nmin,nmax,prim,cons,yfluxes)
246  IMPORT physics_base,mesh_base,marray_compound
247  CLASS(physics_base), INTENT(IN) :: this
248  CLASS(mesh_base), INTENT(IN) :: mesh
249  INTEGER, INTENT(IN) :: nmin,nmax
250  CLASS(marray_compound), INTENT(INOUT) :: prim,cons,yfluxes
251  END SUBROUTINE
252  PURE SUBROUTINE calcfluxesz(this,Mesh,nmin,nmax,prim,cons,zfluxes)
253  IMPORT physics_base,mesh_base,marray_compound
254  CLASS(physics_base), INTENT(IN) :: this
255  CLASS(mesh_base), INTENT(IN) :: mesh
256  INTEGER, INTENT(IN) :: nmin,nmax
257  CLASS(marray_compound), INTENT(INOUT) :: prim,cons,zfluxes
258  END SUBROUTINE
259  PURE SUBROUTINE addbackgroundvelocityx(this,Mesh,w,pvar,cvar)
260  IMPORT physics_base,mesh_base,marray_compound
261  CLASS(physics_base), INTENT(INOUT) :: this
262  CLASS(mesh_base), INTENT(IN) :: mesh
263  REAL, DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%KGMIN:Mesh%KGMAX), &
264  INTENT(IN) :: w
265  CLASS(marray_compound), INTENT(INOUT) :: pvar,cvar
266  END SUBROUTINE addbackgroundvelocityx
267  PURE SUBROUTINE addbackgroundvelocityy(this,Mesh,w,pvar,cvar)
268  IMPORT physics_base,mesh_base,marray_compound
269  CLASS(physics_base), INTENT(INOUT) :: this
270  CLASS(mesh_base), INTENT(IN) :: mesh
271  REAL, DIMENSION(Mesh%JGMIN:Mesh%JGMAX,Mesh%KGMIN:Mesh%KGMAX), &
272  INTENT(IN) :: w
273  CLASS(marray_compound), INTENT(INOUT) :: pvar,cvar
274  END SUBROUTINE addbackgroundvelocityy
275  PURE SUBROUTINE addbackgroundvelocityz(this,Mesh,w,pvar,cvar)
276  IMPORT physics_base,mesh_base,marray_compound
277  CLASS(physics_base), INTENT(INOUT) :: this
278  CLASS(mesh_base), INTENT(IN) :: mesh
279  REAL, DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%JGMIN:Mesh%JGMAX), &
280  INTENT(IN) :: w
281  CLASS(marray_compound), INTENT(INOUT) :: pvar,cvar
282  END SUBROUTINE addbackgroundvelocityz
283  PURE SUBROUTINE subtractbackgroundvelocityx(this,Mesh,w,pvar,cvar)
284  IMPORT physics_base,mesh_base,marray_compound
285  CLASS(physics_base), INTENT(INOUT) :: this
286  CLASS(mesh_base), INTENT(IN) :: mesh
287  REAL, DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%KGMIN:Mesh%KGMAX), &
288  INTENT(IN) :: w
289  CLASS(marray_compound), INTENT(INOUT) :: pvar,cvar
290  END SUBROUTINE subtractbackgroundvelocityx
291  PURE SUBROUTINE subtractbackgroundvelocityy(this,Mesh,w,pvar,cvar)
292  IMPORT physics_base,mesh_base,marray_compound
293  CLASS(physics_base), INTENT(INOUT) :: this
294  CLASS(mesh_base), INTENT(IN) :: mesh
295  REAL, DIMENSION(Mesh%JGMIN:Mesh%JGMAX,Mesh%KGMIN:Mesh%KGMAX), &
296  INTENT(IN) :: w
297  CLASS(marray_compound), INTENT(INOUT) :: pvar,cvar
298  END SUBROUTINE subtractbackgroundvelocityy
299  PURE SUBROUTINE subtractbackgroundvelocityz(this,Mesh,w,pvar,cvar)
300  IMPORT physics_base,mesh_base,marray_compound
301  CLASS(physics_base), INTENT(INOUT) :: this
302  CLASS(mesh_base), INTENT(IN) :: mesh
303  REAL, DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%JGMIN:Mesh%JGMAX), &
304  INTENT(IN) :: w
305  CLASS(marray_compound), INTENT(INOUT) :: pvar,cvar
306  END SUBROUTINE subtractbackgroundvelocityz
307  PURE SUBROUTINE geometricalsources(this,Mesh,pvar,cvar,sterm)
308  IMPORT physics_base,mesh_base,marray_compound
309  CLASS(physics_base), INTENT(INOUT) :: this
310  CLASS(mesh_base), INTENT(IN) :: mesh
311  CLASS(marray_compound), INTENT(INOUT) :: pvar,cvar,sterm
312  END SUBROUTINE
313  PURE SUBROUTINE addfargosources(this,Mesh,w,pvar,cvar,sterm)
314  IMPORT physics_base,mesh_base,marray_compound
315  CLASS(physics_base), INTENT(IN) :: this
316  CLASS(mesh_base), INTENT(IN) :: mesh
317  REAL, DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%KGMIN:Mesh%KGMAX), &
318  INTENT(IN) :: w
319  CLASS(marray_compound), INTENT(INOUT) :: pvar,cvar,sterm
320  END SUBROUTINE addfargosources
321  PURE SUBROUTINE masks(this,Mesh,reflX,reflY,reflZ)
323  CLASS(physics_base), INTENT(IN) :: this
324  CLASS(mesh_base), INTENT(IN) :: mesh
325  LOGICAL, DIMENSION(this%VNUM), INTENT(OUT) :: reflx,refly,reflz
326  END SUBROUTINE
327  PURE SUBROUTINE calculatecharsystemx(this,Mesh,i1,i2,pvar,lambda,xvar)
328  IMPORT physics_base, mesh_base, marray_compound
329  !----------------------------------------------------------------------!
330  CLASS(physics_base), INTENT(IN) :: this
331  CLASS(mesh_base), INTENT(IN) :: mesh
332  INTEGER, INTENT(IN) :: i1,i2
333  CLASS(marray_compound), INTENT(INOUT) :: pvar
334  REAL,DIMENSION(Mesh%JMIN:Mesh%JMAX,Mesh%KMIN:Mesh%KMAX,this%VNUM), &
335  INTENT(OUT) :: lambda,xvar
336  END SUBROUTINE
337  PURE SUBROUTINE calculatecharsystemy(this,Mesh,j1,j2,pvar,lambda,xvar)
338  IMPORT physics_base, mesh_base, marray_compound
339  !----------------------------------------------------------------------!
340  CLASS(physics_base), INTENT(IN) :: this
341  CLASS(mesh_base), INTENT(IN) :: mesh
342  INTEGER, INTENT(IN) :: j1,j2
343  CLASS(marray_compound), INTENT(INOUT) :: pvar
344  REAL,DIMENSION(Mesh%IMIN:Mesh%IMAX,Mesh%KMIN:Mesh%KMAX,this%VNUM), &
345  INTENT(OUT) :: lambda,xvar
346  END SUBROUTINE
347  PURE SUBROUTINE calculatecharsystemz(this,Mesh,k1,k2,pvar,lambda,xvar)
348  IMPORT physics_base, mesh_base, marray_compound
349  !----------------------------------------------------------------------!
350  CLASS(physics_base), INTENT(IN) :: this
351  CLASS(mesh_base), INTENT(IN) :: mesh
352  INTEGER, INTENT(IN) :: k1,k2
353  CLASS(marray_compound), INTENT(INOUT) :: pvar
354  REAL,DIMENSION(Mesh%IMIN:Mesh%IMAX,Mesh%JMIN:Mesh%JMAX,this%VNUM), &
355  INTENT(OUT) :: lambda,xvar
356  END SUBROUTINE
357  PURE SUBROUTINE calculateboundarydatax(this,Mesh,i1,i2,xvar,pvar)
358  IMPORT physics_base, mesh_base, marray_compound
359  CLASS(physics_base), INTENT(IN) :: this
360  CLASS(mesh_base), INTENT(IN) :: mesh
361  INTEGER, INTENT(IN) :: i1,i2
362  REAL,DIMENSION(Mesh%JGMIN:Mesh%JGMAX,Mesh%KGMIN:Mesh%KGMAX,this%VNUM), INTENT(IN) :: xvar
363  CLASS(marray_compound), INTENT(INOUT) :: pvar
364  END SUBROUTINE
365  PURE SUBROUTINE calculateboundarydatay(this,Mesh,j1,j2,xvar,pvar)
366  IMPORT physics_base, mesh_base, marray_compound
367  CLASS(physics_base), INTENT(IN) :: this
368  CLASS(mesh_base), INTENT(IN) :: mesh
369  INTEGER, INTENT(IN) :: j1,j2
370  REAL,DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%KGMIN:Mesh%KGMAX,this%VNUM), INTENT(IN) :: xvar
371  CLASS(marray_compound), INTENT(INOUT) :: pvar
372  END SUBROUTINE
373  PURE SUBROUTINE calculateboundarydataz(this,Mesh,k1,k2,xvar,pvar)
374  IMPORT physics_base, mesh_base, marray_compound
375  CLASS(physics_base), INTENT(IN) :: this
376  CLASS(mesh_base), INTENT(IN) :: mesh
377  INTEGER, INTENT(IN) :: k1,k2
378  REAL,DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%JGMIN:Mesh%JGMAX,this%VNUM), INTENT(IN) :: xvar
379  CLASS(marray_compound), INTENT(INOUT) :: pvar
380  END SUBROUTINE
381  SUBROUTINE finalize(this)
383  IMPLICIT NONE
384  CLASS(physics_base),INTENT(INOUT) :: this
385  END SUBROUTINE
386 
387  END INTERFACE
388  !--------------------------------------------------------------------------!
389  ! flags for advection problems
390 ! INTEGER, PARAMETER :: EULER2D = 1
391  INTEGER, PARAMETER :: euler_isotherm = 16
393  INTEGER, PARAMETER :: euler = 17
395 ! INTEGER, PARAMETER :: EULER2D_ISOTHERM = 2
396 ! INTEGER, PARAMETER :: EULER3D_ROTSYM = 3
397 ! INTEGER, PARAMETER :: EULER3D_ROTAMT = 4
398 ! INTEGER, PARAMETER :: EULER3D_ROTSYMSGS = 5
399 ! INTEGER, PARAMETER :: EULER2D_SGS = 7
400 ! INTEGER, PARAMETER :: EULER3D_ROTAMTSGS = 8
401 ! INTEGER, PARAMETER :: EULER2D_ISOIAMT = 9
402 ! INTEGER, PARAMETER :: EULER2D_IAMT = 11
403 ! INTEGER, PARAMETER :: EULER2D_IAMROT = 12
404 ! INTEGER, PARAMETER :: EULER2D_ISOIAMROT = 13
405 ! INTEGER, PARAMETER :: EULER3D_ISOTHERM = 14
406 ! INTEGER, PARAMETER :: EULER3D = 15
407  !--------------------------------------------------------------------------!
408  PUBLIC :: &
409  ! types
410  physics_base, &
411  ! constants - flags for identification in dictionary by an integer
413  si, cgs, geometrical, &
414  undefined, primitive, conservative
415  !--------------------------------------------------------------------------!
416 
417 CONTAINS
418 
426  SUBROUTINE initphysics(this,Mesh,config,IO,problem,pname)
427  IMPLICIT NONE
428  !------------------------------------------------------------------------!
429  CLASS(physics_base), INTENT(INOUT) :: this
430  CLASS(mesh_base),INTENT(IN) :: Mesh
431  TYPE(Dict_TYP),POINTER &
432  :: config, IO
433  INTEGER :: problem
434  CHARACTER(LEN=32) :: pname
435  !------------------------------------------------------------------------!
436  INTEGER :: units
437  INTEGER :: err, valwrite
438  !------------------------------------------------------------------------!
439  INTENT(IN) :: problem
440  !------------------------------------------------------------------------!
441  CALL this%InitLogging(problem,pname)
442 
443  ! check initialization of Mesh
444  IF (.NOT.mesh%Initialized()) &
445  CALL this%Error("InitPhysics","mesh module uninitialized")
446 
447  ! units
448  CALL getattr(config, "units", units, si)
449  CALL new_constants(this%constants, units)
450 
451  !CALL GetAttr(config, "problem", problem)
452 
453  ! mean molecular weight
454  CALL getattr(config, "mu", this%mu, 0.029)
455 
456  ! enable advanced wave speed estimates (computationally more expensive)
457  ! uses Roe averages between cell boundaries
458  CALL getattr(config, "advanced_wave_speeds", valwrite, 0)
459  IF (valwrite .EQ. 1) THEN
460  this%advanced_wave_speeds = .true.
461  ELSE
462  this%advanced_wave_speeds = .false.
463  END IF
464 
465  ! softening parameter to smooth out singularity near center of rotation
466  ! (only necessary, if it's inside the computational domain)
467  ! set to 0.0 to disable
468  ! the softening length is the product of this parameter and the
469  ! size of the grid cell next to the center of rotation; thus a value larger
470  ! than 1.0 leads to larger softening whereas smaller values will
471  ! probably cause odd behaviour due to the 1/r singularity;
472  ! if the minimal r on the computational domain is larger than
473  ! the size of the associated grid cell, softening is disabled, because
474  ! the center of rotation lies outside of the computational domain
475  CALL getattr(config, "softening", this%eps, 1.0)
476 
477  ! determine physical vector dimensions based on dimimensionality of the grid
478  ! whether rotationa symmetry is assumed
479  this%VDIM = mesh%NDIMS
480  IF (mesh%ROTSYM.GT.0) this%VDIM = this%VDIM + 1
481 
482  ! set this to appropriate values in derived classes
483  this%VNUM = 0 ! number of hydrodynamical variables in state vector
484  this%PNUM = 0 ! number of passive scalars in state vector
485 
486  ! allocate memory for arrays common to all physics modules
487  ALLOCATE(this%tmp(mesh%IGMIN:mesh%IGMAX,mesh%JGMIN:mesh%JGMAX,mesh%KGMIN:mesh%KGMAX), &
488  this%tmp1(mesh%IGMIN:mesh%IGMAX,mesh%JGMIN:mesh%JGMAX,mesh%KGMIN:mesh%KGMAX), &
489  this%tmp2(mesh%IGMIN:mesh%IGMAX,mesh%JGMIN:mesh%JGMAX,mesh%KGMIN:mesh%KGMAX), &
490  this%tmp3(mesh%IGMIN:mesh%IGMAX,mesh%JGMIN:mesh%JGMAX,mesh%KGMIN:mesh%KGMAX), &
491  this%tmp4(mesh%IGMIN:mesh%IGMAX,mesh%JGMIN:mesh%JGMAX,mesh%KGMIN:mesh%KGMAX), &
492  this%tmp5(mesh%IGMIN:mesh%IGMAX,mesh%JGMIN:mesh%JGMAX,mesh%KGMIN:mesh%KGMAX), &
493  stat = err)
494  IF (err.NE.0) &
495  CALL this%Error("InitPhysics", "Unable to allocate memory.")
496 
497  this%tmp(:,:,:) = 0.
498  this%tmp1(:,:,:) = 0.
499  this%tmp2(:,:,:) = 0.
500  this%tmp3(:,:,:) = 0.
501  this%tmp4(:,:,:) = 0.
502  this%tmp5(:,:,:) = 0.
503 
504  ! disable absorbing and farfield boundary conditions by default
505  this%supports_absorbing = .false.
506  this%supports_farfield = .false.
507 
508  ! no background velocity subtracted (important for fargo advection)
509  this%transformed_xvelocity = .false.
510  this%transformed_yvelocity = .false.
511  this%transformed_zvelocity = .false.
512 
513  ! reset source term pointer
514  !NULLIFY(this%sources)
515 
516  this%time = -1.
517  END SUBROUTINE initphysics
518 
519  SUBROUTINE printconfiguration(this)
520  IMPLICIT NONE
521  !------------------------------------------------------------------------!
522  CLASS(physics_base), INTENT(INOUT) :: this
523  !------------------------------------------------------------------------!
524  CALL this%Info(" PHYSICS--> advection problem: " // trim(this%GetName()))
525  END SUBROUTINE printconfiguration
526 
528  SUBROUTINE finalize_base(this)
529  IMPLICIT NONE
530  !------------------------------------------------------------------------!
531  CLASS(physics_base), INTENT(INOUT) :: this
532  !------------------------------------------------------------------------!
533  IF (.NOT.this%Initialized()) &
534  CALL this%Error("ClosePhysics","not initialized")
535  ! deallocate pointer variables used in all physics modules
536  DEALLOCATE(this%tmp,this%tmp1,this%tmp2,this%tmp3,this%tmp4,this%tmp5, &
537  this%pvarname,this%cvarname)
538  END SUBROUTINE finalize_base
539 
540 END MODULE physics_base_mod
subroutine finalize(this)
Destructor of common class.
subroutine initphysics(this, Mesh, config, IO, problem, pname)
Initialization for the base physical object.
derived class for compound of mesh arrays
base class for mesh arrays
Definition: marray_base.f90:36
Basic fosite module.
common data structure
subroutine printconfiguration(this)
named integer constants for flavour of state vectors
subroutine finalize_base(this)
Destructor.
integer, parameter, public euler_isotherm
Basic physics module.
Dictionary for generic data types.
Definition: common_dict.f90:61
integer, parameter, public euler
constructor for constants class