Skip to content

Commit 68b2ad1

Browse files
committed
add viscous and surface_tension flags
1 parent 4759bd8 commit 68b2ad1

18 files changed

+166
-143
lines changed

src/common/m_mpi_common.fpp

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -245,7 +245,7 @@ contains
245245
MPI_DOUBLE_PRECISION, MPI_MAX, 0, &
246246
MPI_COMM_WORLD, ierr)
247247
248-
if (any(Re_size > 0)) then
248+
if (viscous) then
249249
call MPI_REDUCE(vcfl_max_loc, vcfl_max_glb, 1, &
250250
MPI_DOUBLE_PRECISION, MPI_MAX, 0, &
251251
MPI_COMM_WORLD, ierr)
@@ -258,7 +258,7 @@ contains
258258
259259
icfl_max_glb = icfl_max_loc
260260
261-
if (any(Re_size > 0)) then
261+
if (viscous) then
262262
vcfl_max_glb = vcfl_max_loc
263263
Rc_min_glb = Rc_min_loc
264264
end if

src/common/m_variables_conversion.fpp

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -340,7 +340,7 @@ contains
340340

341341
#ifdef MFC_SIMULATION
342342
! Computing the shear and bulk Reynolds numbers from species analogs
343-
if (any(Re_size > 0)) then
343+
if (viscous) then
344344
if (num_fluids == 1) then ! need to consider case with num_fluids >= 2
345345
do i = 1, 2
346346

@@ -530,7 +530,7 @@ contains
530530
G_K = max(0d0, G_K)
531531
end if
532532

533-
if (any(Re_size > 0)) then
533+
if (viscous) then
534534

535535
do i = 1, 2
536536
Re_K(i) = dflt_real
@@ -596,7 +596,7 @@ contains
596596
qv_K = qvs(1)
597597
end if
598598

599-
if (any(Re_size > 0)) then
599+
if (viscous) then
600600
if (num_fluids == 1) then ! need to consider case with num_fluids >= 2
601601

602602
do i = 1, 2
@@ -661,7 +661,7 @@ contains
661661

662662
#ifdef MFC_SIMULATION
663663

664-
if (any(Re_size > 0)) then
664+
if (viscous) then
665665
@:ALLOCATE_GLOBAL(Res(1:2, 1:maxval(Re_size)))
666666
do i = 1, 2
667667
do j = 1, Re_size(i)

src/post_process/m_checker.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -115,7 +115,7 @@ contains
115115

116116
!> Checks constraints on surface tension parameters (cf_wrt and sigma)
117117
subroutine s_check_inputs_surface_tension
118-
@:PROHIBIT(cf_wrt .and. f_is_default(sigma), &
118+
@:PROHIBIT(cf_wrt .and. .not. surface_tension, &
119119
"cf_wrt can only be enabled if the surface coefficient is set")
120120
end subroutine s_check_inputs_surface_tension
121121

src/post_process/m_global_parameters.fpp

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -275,6 +275,7 @@ module m_global_parameters
275275
!> @name surface tension coefficient
276276
!> @{
277277
real(kind(0d0)) :: sigma
278+
logical :: surface_tension
278279
!> #}
279280

280281
!> @name Index variables used for m_variables_conversion
@@ -397,6 +398,7 @@ contains
397398
poly_sigma = dflt_real
398399
sigR = dflt_real
399400
sigma = dflt_real
401+
surface_tension = .false.
400402
adv_n = .false.
401403

402404
end subroutine s_assign_default_values_to_user_inputs
@@ -534,7 +536,7 @@ contains
534536
sys_size = stress_idx%end
535537
end if
536538

537-
if (.not. f_is_default(sigma)) then
539+
if (surface_tension) then
538540
c_idx = sys_size + 1
539541
sys_size = c_idx
540542
end if
@@ -559,7 +561,7 @@ contains
559561
sys_size = internalEnergies_idx%end
560562
alf_idx = 1 ! dummy, cannot actually have a void fraction
561563

562-
if (.not. f_is_default(sigma)) then
564+
if (surface_tension) then
563565
c_idx = sys_size + 1
564566
sys_size = c_idx
565567
end if

src/post_process/m_start_up.f90

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -114,6 +114,8 @@ subroutine s_read_input_file
114114

115115
if (cfl_adap_dt .or. cfl_const_dt) cfl_dt = .true.
116116

117+
if (.not. f_is_default(sigma)) surface_tension = .true.
118+
117119
else
118120
call s_mpi_abort('File post_process.inp is missing. Exiting ...')
119121
end if

src/pre_process/m_assign_variables.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -663,7 +663,7 @@ contains
663663
end do
664664
end if
665665
666-
if (.not. f_is_default(sigma)) then
666+
if (surface_tension) then
667667
q_prim_vf(c_idx)%sf(j, k, l) = eta*patch_icpp(patch_id)%cf_val + &
668668
(1d0 - eta)*patch_icpp(smooth_patch_id)%cf_val
669669
end if

src/pre_process/m_global_parameters.fpp

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -228,6 +228,7 @@ module m_global_parameters
228228
!> @name Surface Tension Modeling
229229
!> @{
230230
real(kind(0d0)) :: sigma
231+
logical :: surface_tension
231232
!> @}
232233

233234
!> @name Index variables used for m_variables_conversion
@@ -400,6 +401,7 @@ contains
400401
Re_inv = dflt_real
401402
Web = dflt_real
402403
poly_sigma = dflt_real
404+
surface_tension = .false.
403405

404406
adv_n = .false.
405407

@@ -615,7 +617,7 @@ contains
615617
sys_size = stress_idx%end
616618
end if
617619

618-
if (.not. f_is_default(sigma)) then
620+
if (surface_tension) then
619621
c_idx = sys_size + 1
620622
sys_size = c_idx
621623
end if
@@ -639,7 +641,7 @@ contains
639641
internalEnergies_idx%end = adv_idx%end + num_fluids
640642
sys_size = internalEnergies_idx%end
641643

642-
if (.not. f_is_default(sigma)) then
644+
if (surface_tension) then
643645
c_idx = sys_size + 1
644646
sys_size = c_idx
645647
end if

src/pre_process/m_mpi_proxy.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -56,7 +56,7 @@ contains
5656
& 'perturb_flow', 'perturb_sph', 'mixlayer_vel_profile', &
5757
& 'mixlayer_perturb', 'bubbles', 'polytropic', 'polydisperse', &
5858
& 'qbmm', 'file_per_process', 'adv_n', 'ib' , 'cfl_adap_dt', &
59-
& 'cfl_const_dt', 'cfl_dt']
59+
& 'cfl_const_dt', 'cfl_dt', 'surface_tension']
6060
call MPI_BCAST(${VAR}$, 1, MPI_LOGICAL, 0, MPI_COMM_WORLD, ierr)
6161
#:endfor
6262
call MPI_BCAST(fluid_rho(1), num_fluids_max, MPI_LOGICAL, 0, MPI_COMM_WORLD, ierr)

src/pre_process/m_start_up.fpp

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -170,6 +170,8 @@ contains
170170

171171
if (cfl_adap_dt .or. cfl_const_dt) cfl_dt = .true.
172172

173+
if (.not. f_is_default(sigma)) surface_tension = .true.
174+
173175
else
174176
call s_mpi_abort('File pre_process.inp is missing. Exiting ...')
175177
end if

src/simulation/m_data_output.fpp

Lines changed: 15 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -148,15 +148,15 @@ contains
148148

149149
! Generating table header for the stability criteria to be outputted
150150
if (cfl_dt) then
151-
if (any(Re_size > 0)) then
151+
if (viscous) then
152152
write (1, '(A)') '==== Time-steps ====== dt ===== Time ======= ICFL '// &
153153
'Max ==== VCFL Max ====== Rc Min ======='
154154
else
155155
write (1, '(A)') '=========== Time-steps ============== dt ===== Time '// &
156156
'============== ICFL Max ============='
157157
end if
158158
else
159-
if (any(Re_size > 0)) then
159+
if (viscous) then
160160
write (1, '(A)') '==== Time-steps ====== Time ======= ICFL '// &
161161
'Max ==== VCFL Max ====== Rc Min ======='
162162
else
@@ -266,7 +266,7 @@ contains
266266
! Compute mixture sound speed
267267
call s_compute_speed_of_sound(pres, rho, gamma, pi_inf, H, alpha, vel_sum, 0d0, c)
268268

269-
if (any(Re_size > 0)) then
269+
if (viscous) then
270270
call s_compute_stability_from_dt(vel, c, rho, Re, j, k, l, icfl_sf, vcfl_sf, Rc_sf)
271271
else
272272
call s_compute_stability_from_dt(vel, c, rho, Re, j, k, l, icfl_sf)
@@ -282,13 +282,13 @@ contains
282282
#ifdef CRAY_ACC_WAR
283283
!$acc update host(icfl_sf)
284284

285-
if (any(Re_size > 0)) then
285+
if (viscous) then
286286
!$acc update host(vcfl_sf, Rc_sf)
287287
end if
288288

289289
icfl_max_loc = maxval(icfl_sf)
290290

291-
if (any(Re_size > 0)) then
291+
if (viscous) then
292292
vcfl_max_loc = maxval(vcfl_sf)
293293
Rc_min_loc = minval(Rc_sf)
294294
end if
@@ -297,7 +297,7 @@ contains
297297
icfl_max_loc = maxval(icfl_sf)
298298
!$acc end kernels
299299

300-
if (any(Re_size > 0)) then
300+
if (viscous) then
301301
!$acc kernels
302302
vcfl_max_loc = maxval(vcfl_sf)
303303
Rc_min_loc = minval(Rc_sf)
@@ -317,21 +317,21 @@ contains
317317
Rc_min_glb)
318318
else
319319
icfl_max_glb = icfl_max_loc
320-
if (any(Re_size > 0)) vcfl_max_glb = vcfl_max_loc
321-
if (any(Re_size > 0)) Rc_min_glb = Rc_min_loc
320+
if (viscous) vcfl_max_glb = vcfl_max_loc
321+
if (viscous) Rc_min_glb = Rc_min_loc
322322
end if
323323

324324
! Determining the stability criteria extrema over all the time-steps
325325
if (icfl_max_glb > icfl_max) icfl_max = icfl_max_glb
326326

327-
if (any(Re_size > 0)) then
327+
if (viscous) then
328328
if (vcfl_max_glb > vcfl_max) vcfl_max = vcfl_max_glb
329329
if (Rc_min_glb < Rc_min) Rc_min = Rc_min_glb
330330
end if
331331

332332
! Outputting global stability criteria extrema at current time-step
333333
if (proc_rank == 0) then
334-
if (any(Re_size > 0)) then
334+
if (viscous) then
335335
write (1, '(6X,I8,F10.6,6X,6X,F10.6,6X,F9.6,6X,F9.6,6X,F10.6)') &
336336
t_step, dt, t_step*dt, icfl_max_glb, &
337337
vcfl_max_glb, &
@@ -348,7 +348,7 @@ contains
348348
call s_mpi_abort('ICFL is greater than 1.0. Exiting ...')
349349
end if
350350

351-
if (any(Re_size > 0)) then
351+
if (viscous) then
352352
if (vcfl_max_glb /= vcfl_max_glb) then
353353
call s_mpi_abort('VCFL is NaN. Exiting ...')
354354
elseif (vcfl_max_glb > 1d0) then
@@ -1578,8 +1578,8 @@ contains
15781578
write (3, '(A)') ''
15791579

15801580
write (3, '(A,F9.6)') 'ICFL Max: ', icfl_max
1581-
if (any(Re_size > 0)) write (3, '(A,F9.6)') 'VCFL Max: ', vcfl_max
1582-
if (any(Re_size > 0)) write (3, '(A,F10.6)') 'Rc Min: ', Rc_min
1581+
if (viscous) write (3, '(A,F9.6)') 'VCFL Max: ', vcfl_max
1582+
if (viscous) write (3, '(A,F10.6)') 'Rc Min: ', Rc_min
15831583

15841584
call cpu_time(run_time)
15851585

@@ -1615,7 +1615,7 @@ contains
16151615
@:ALLOCATE_GLOBAL(icfl_sf(0:m, 0:n, 0:p))
16161616
icfl_max = 0d0
16171617

1618-
if (any(Re_size > 0)) then
1618+
if (viscous) then
16191619
@:ALLOCATE_GLOBAL(vcfl_sf(0:m, 0:n, 0:p))
16201620
@:ALLOCATE_GLOBAL(Rc_sf (0:m, 0:n, 0:p))
16211621

@@ -1652,7 +1652,7 @@ contains
16521652

16531653
! Deallocating the ICFL, VCFL, CCFL, and Rc stability criteria
16541654
@:DEALLOCATE_GLOBAL(icfl_sf)
1655-
if (any(Re_size > 0)) then
1655+
if (viscous) then
16561656
@:DEALLOCATE_GLOBAL(vcfl_sf, Rc_sf)
16571657
end if
16581658

0 commit comments

Comments
 (0)