67 enumerator :: undefined=0, primitive=1, conservative=2
71 CLASS(constants_base),
ALLOCATABLE :: constants
74 REAL :: time,& !< simulation time
75 mu, & !< mean molecular weight
77 INTEGER :: vnum, & !< number of variables
78 pnum, & !< number of passive variables
79 vdim, & !< vector dimensions (1, 2 or 3)
83 xvelocity,xmomentum, &
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 &
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, &
105 REAL,
DIMENSION(:,:,:,:),
POINTER :: &
106 fradius, & !< distance to the origin face values
107 bcposvec, & !< curvilinear components of the position vector bary center values
111 REAL,
DIMENSION(:,:,:,:,:),
POINTER &
112 :: fcent, & !< centrifugal force
119 procedure(externalsources),
DEFERRED :: externalsources
120 procedure(enableoutput),
DEFERRED :: enableoutput
122 procedure(convert2primitive_all),
DEFERRED :: convert2primitive_all
123 procedure(convert2primitive_subset),
DEFERRED :: convert2primitive_subset
124 generic :: convert2primitive => &
125 convert2primitive_all, &
126 convert2primitive_subset
128 procedure(convert2conservative_all),
DEFERRED :: convert2conservative_all
129 procedure(convert2conservative_subset),
DEFERRED :: convert2conservative_subset
130 generic :: convert2conservative => &
131 convert2conservative_all, &
132 convert2conservative_subset
134 procedure(calcwavespeeds_center),
DEFERRED :: calcwavespeeds_center
135 procedure(calcwavespeeds_faces),
DEFERRED :: calcwavespeeds_faces
136 generic :: calculatewavespeeds => &
137 calcwavespeeds_center, &
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
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
155 procedure(geometricalsources),
DEFERRED :: geometricalsources
156 procedure(masks),
DEFERRED :: reflectionmasks
157 procedure(masks),
DEFERRED :: axismasks
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
180 SUBROUTINE enableoutput(this,Mesh,config,IO)
184 CLASS(physics_base),
INTENT(INOUT) :: this
185 CLASS(mesh_base),
INTENT(IN) :: Mesh
186 TYPE(Dict_TYP),
POINTER,
INTENT(IN) :: config, IO
191 CLASS(physics_base),
INTENT(IN) :: this
192 CLASS(marray_compound),
POINTER :: new_sv
193 INTEGER,
OPTIONAL,
INTENT(IN) :: flavour,num
195 PURE SUBROUTINE convert2primitive_all(this,cvar,pvar)
198 CLASS(marray_compound),
INTENT(INOUT) :: cvar,pvar
200 PURE SUBROUTINE convert2primitive_subset(this,i1,i2,j1,j2,k1,k2,cvar,pvar)
203 INTEGER,
INTENT(IN) :: i1,i2,j1,j2,k1,k2
204 CLASS(marray_compound),
INTENT(INOUT) :: cvar,pvar
206 PURE SUBROUTINE convert2conservative_all(this,pvar,cvar)
209 CLASS(marray_compound),
INTENT(INOUT) :: pvar,cvar
211 PURE SUBROUTINE convert2conservative_subset(this,i1,i2,j1,j2,k1,k2,pvar,cvar)
214 INTEGER,
INTENT(IN) :: i1,i2,j1,j2,k1,k2
215 CLASS(marray_compound),
INTENT(INOUT) :: pvar,cvar
217 PURE SUBROUTINE externalsources(this,accel,pvar,cvar,sterm)
220 CLASS(marray_base),
INTENT(IN) :: accel
221 CLASS(marray_compound),
INTENT(INOUT) :: pvar,cvar,sterm
223 PURE SUBROUTINE calcwavespeeds_center(this,Mesh,pvar,minwav,maxwav)
227 CLASS(marray_compound),
INTENT(INOUT) :: pvar
228 TYPE(marray_base),
INTENT(INOUT) :: minwav,maxwav
230 PURE SUBROUTINE calcwavespeeds_faces(this,Mesh,prim,cons,minwav,maxwav)
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
238 PURE SUBROUTINE calcfluxesx(this,Mesh,nmin,nmax,prim,cons,xfluxes)
242 INTEGER,
INTENT(IN) :: nmin,nmax
243 CLASS(marray_compound),
INTENT(INOUT) :: prim,cons,xfluxes
245 PURE SUBROUTINE calcfluxesy(this,Mesh,nmin,nmax,prim,cons,yfluxes)
249 INTEGER,
INTENT(IN) :: nmin,nmax
250 CLASS(marray_compound),
INTENT(INOUT) :: prim,cons,yfluxes
252 PURE SUBROUTINE calcfluxesz(this,Mesh,nmin,nmax,prim,cons,zfluxes)
256 INTEGER,
INTENT(IN) :: nmin,nmax
257 CLASS(marray_compound),
INTENT(INOUT) :: prim,cons,zfluxes
259 PURE SUBROUTINE addbackgroundvelocityx(this,Mesh,w,pvar,cvar)
263 REAL,
DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%KGMIN:Mesh%KGMAX), &
265 CLASS(marray_compound),
INTENT(INOUT) :: pvar,cvar
266 END SUBROUTINE addbackgroundvelocityx
267 PURE SUBROUTINE addbackgroundvelocityy(this,Mesh,w,pvar,cvar)
271 REAL,
DIMENSION(Mesh%JGMIN:Mesh%JGMAX,Mesh%KGMIN:Mesh%KGMAX), &
273 CLASS(marray_compound),
INTENT(INOUT) :: pvar,cvar
274 END SUBROUTINE addbackgroundvelocityy
275 PURE SUBROUTINE addbackgroundvelocityz(this,Mesh,w,pvar,cvar)
279 REAL,
DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%JGMIN:Mesh%JGMAX), &
281 CLASS(marray_compound),
INTENT(INOUT) :: pvar,cvar
282 END SUBROUTINE addbackgroundvelocityz
283 PURE SUBROUTINE subtractbackgroundvelocityx(this,Mesh,w,pvar,cvar)
287 REAL,
DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%KGMIN:Mesh%KGMAX), &
289 CLASS(marray_compound),
INTENT(INOUT) :: pvar,cvar
290 END SUBROUTINE subtractbackgroundvelocityx
291 PURE SUBROUTINE subtractbackgroundvelocityy(this,Mesh,w,pvar,cvar)
295 REAL,
DIMENSION(Mesh%JGMIN:Mesh%JGMAX,Mesh%KGMIN:Mesh%KGMAX), &
297 CLASS(marray_compound),
INTENT(INOUT) :: pvar,cvar
298 END SUBROUTINE subtractbackgroundvelocityy
299 PURE SUBROUTINE subtractbackgroundvelocityz(this,Mesh,w,pvar,cvar)
303 REAL,
DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%JGMIN:Mesh%JGMAX), &
305 CLASS(marray_compound),
INTENT(INOUT) :: pvar,cvar
306 END SUBROUTINE subtractbackgroundvelocityz
307 PURE SUBROUTINE geometricalsources(this,Mesh,pvar,cvar,sterm)
311 CLASS(marray_compound),
INTENT(INOUT) :: pvar,cvar,sterm
313 PURE SUBROUTINE addfargosources(this,Mesh,w,pvar,cvar,sterm)
317 REAL,
DIMENSION(Mesh%IGMIN:Mesh%IGMAX,Mesh%KGMIN:Mesh%KGMAX), &
319 CLASS(marray_compound),
INTENT(INOUT) :: pvar,cvar,sterm
320 END SUBROUTINE addfargosources
321 PURE SUBROUTINE masks(this,Mesh,reflX,reflY,reflZ)
325 LOGICAL,
DIMENSION(this%VNUM),
INTENT(OUT) :: reflx,refly,reflz
327 PURE SUBROUTINE calculatecharsystemx(this,Mesh,i1,i2,pvar,lambda,xvar)
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
337 PURE SUBROUTINE calculatecharsystemy(this,Mesh,j1,j2,pvar,lambda,xvar)
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
347 PURE SUBROUTINE calculatecharsystemz(this,Mesh,k1,k2,pvar,lambda,xvar)
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
357 PURE SUBROUTINE calculateboundarydatax(this,Mesh,i1,i2,xvar,pvar)
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
365 PURE SUBROUTINE calculateboundarydatay(this,Mesh,j1,j2,xvar,pvar)
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
373 PURE SUBROUTINE calculateboundarydataz(this,Mesh,k1,k2,xvar,pvar)
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
384 CLASS(physics_base),
INTENT(INOUT) :: this
413 si, cgs, geometrical, &
414 undefined, primitive, conservative
426 SUBROUTINE initphysics(this,Mesh,config,IO,problem,pname)
429 CLASS(physics_base),
INTENT(INOUT) :: this
430 CLASS(mesh_base),
INTENT(IN) :: Mesh
431 TYPE(Dict_TYP),
POINTER &
434 CHARACTER(LEN=32) :: pname
437 INTEGER :: err, valwrite
439 INTENT(IN) :: problem
441 CALL this%InitLogging(problem,pname)
444 IF (.NOT.mesh%Initialized()) &
445 CALL this%Error(
"InitPhysics",
"mesh module uninitialized")
448 CALL getattr(config,
"units", units, si)
449 CALL new_constants(this%constants, units)
454 CALL getattr(config,
"mu", this%mu, 0.029)
458 CALL getattr(config,
"advanced_wave_speeds", valwrite, 0)
459 IF (valwrite .EQ. 1)
THEN 460 this%advanced_wave_speeds = .true.
462 this%advanced_wave_speeds = .false.
475 CALL getattr(config,
"softening", this%eps, 1.0)
479 this%VDIM = mesh%NDIMS
480 IF (mesh%ROTSYM.GT.0) this%VDIM = this%VDIM + 1
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), &
495 CALL this%Error(
"InitPhysics",
"Unable to allocate memory.")
498 this%tmp1(:,:,:) = 0.
499 this%tmp2(:,:,:) = 0.
500 this%tmp3(:,:,:) = 0.
501 this%tmp4(:,:,:) = 0.
502 this%tmp5(:,:,:) = 0.
505 this%supports_absorbing = .false.
506 this%supports_farfield = .false.
509 this%transformed_xvelocity = .false.
510 this%transformed_yvelocity = .false.
511 this%transformed_zvelocity = .false.
522 CLASS(physics_base),
INTENT(INOUT) :: this
524 CALL this%Info(
" PHYSICS--> advection problem: " // trim(this%GetName()))
531 CLASS(physics_base),
INTENT(INOUT) :: this
533 IF (.NOT.this%Initialized()) &
534 CALL this%Error(
"ClosePhysics",
"not initialized")
536 DEALLOCATE(this%tmp,this%tmp1,this%tmp2,this%tmp3,this%tmp4,this%tmp5, &
537 this%pvarname,this%cvarname)
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
subroutine printconfiguration(this)
named integer constants for flavour of state vectors
subroutine finalize_base(this)
Destructor.
integer, parameter, public euler_isotherm
Dictionary for generic data types.
integer, parameter, public euler
constructor for constants class