Skip to content

Commit 3542ef2

Browse files
committed
asdf
1 parent f1383af commit 3542ef2

File tree

7 files changed

+30
-26
lines changed

7 files changed

+30
-26
lines changed

src/pre_process/m_data_output.fpp

Lines changed: 6 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -157,15 +157,10 @@ contains
157157
status = 'new'
158158
end if
159159

160-
checkboundary1: do i = 1, num_bc_patches
161-
if (bc_x%beg == -17 .or. bc_x%beg == -17 &
162-
.or. bc_y%beg == -17 .or. bc_y%end == -17 &
163-
.or. bc_z%beg == -17 .or. bc_z%end == -17 &
164-
.or. patch_bc(i)%type == -17) then
165-
call s_write_serial_boundary_condition_files(q_prim_vf, bc_type, t_step_dir)
166-
exit checkboundary1
167-
end if
168-
end do checkboundary1
160+
if (save_bc) then
161+
call s_write_serial_boundary_condition_files(q_prim_vf, bc_type, t_step_dir)
162+
end if
163+
169164
! x-coordinate direction
170165
file_loc = trim(t_step_dir)//'/x_cb.dat'
171166
open (1, FILE=trim(file_loc), FORM='unformatted', STATUS=status)
@@ -849,15 +844,9 @@ contains
849844
end if
850845
#endif
851846

852-
checkboundary2: do i = 1, num_bc_patches
853-
if (bc_x%beg == -17 .or. bc_x%beg == -17 &
854-
.or. bc_y%beg == -17 .or. bc_y%end == -17 &
855-
.or. bc_z%beg == -17 .or. bc_z%end == -17 &
856-
.or. patch_bc(i)%type == -17) then
857-
call s_write_parallel_boundary_condition_files(q_prim_vf, bc_type)
858-
exit checkboundary2
847+
if (save_bc) then
848+
call s_write_parallel_boundary_condition_files(q_prim_vf, bc_type)
859849
end if
860-
end do checkboundary2
861850

862851
end subroutine s_write_parallel_data_files
863852

src/pre_process/m_global_parameters.fpp

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -177,6 +177,7 @@ module m_global_parameters
177177
!! in the module m_derived_types.f90.
178178

179179
integer :: num_bc_patches !< Number of boundary condition patches
180+
logical :: save_bc !< whether or not to save BC data
180181
type(bc_patch_parameters), dimension(num_bc_patches_max) :: patch_bc
181182
!! Database of the boundary condition patch parameters for each of the patches
182183
!! employed in the configuration of the boundary conditions
@@ -422,6 +423,7 @@ contains
422423
end do
423424

424425
num_bc_patches = 0
426+
save_bc = .false.
425427

426428
do i = 1, num_bc_patches_max
427429
patch_bc(i)%geometry = dflt_int

src/pre_process/m_mpi_proxy.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -70,7 +70,7 @@ contains
7070
& 'qbmm', 'file_per_process', 'adv_n', 'ib' , 'cfl_adap_dt', &
7171
& 'cfl_const_dt', 'cfl_dt', 'surface_tension', &
7272
& 'hyperelasticity', 'pre_stress', 'elliptic_smoothing', 'viscous',&
73-
& 'bubbles_lagrange' ]
73+
& 'bubbles_lagrange', 'save_bc' ]
7474
call MPI_BCAST(${VAR}$, 1, MPI_LOGICAL, 0, MPI_COMM_WORLD, ierr)
7575
#:endfor
7676
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: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -178,6 +178,12 @@ contains
178178

179179
if (cfl_adap_dt .or. cfl_const_dt .or. rkck_adap_dt) cfl_dt = .true.
180180

181+
182+
if (any((/bc_x%beg, bc_x%end, bc_y%beg, bc_y%end, bc_z%beg, bc_z%end/) == -17) .or. &
183+
num_bc_patches > 0) then
184+
save_bc = .true.
185+
end if
186+
181187
else
182188
call s_mpi_abort('File pre_process.inp is missing. Exiting.')
183189
end if

src/simulation/m_global_parameters.fpp

Lines changed: 7 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -180,8 +180,9 @@ module m_global_parameters
180180
!#ifndef _CRAYFTN
181181
!$acc declare create(relax, relax_model, palpha_eps,ptgalpha_eps)
182182
!#endif
183-
183+
184184
integer :: num_bc_patches
185+
logical :: read_bc
185186
!> @name Boundary conditions (BC) in the x-, y- and z-directions, respectively
186187
!> @{
187188
type(int_bounds_info) :: bc_x, bc_y, bc_z
@@ -549,6 +550,7 @@ contains
549550
chem_params%gamma_method = 1
550551
551552
num_bc_patches = 0
553+
read_bc = .false.
552554
553555
bc_x%beg = dflt_int; bc_x%end = dflt_int
554556
bc_y%beg = dflt_int; bc_y%end = dflt_int
@@ -1171,12 +1173,12 @@ contains
11711173
@:ALLOCATE(x_cc(-buff_size:m + buff_size))
11721174
@:ALLOCATE(dx(-buff_size:m + buff_size))
11731175
1174-
if (n == 0) return;
1176+
if (n == 0) return;
11751177
@:ALLOCATE(y_cb(-1 - buff_size:n + buff_size))
11761178
@:ALLOCATE(y_cc(-buff_size:n + buff_size))
11771179
@:ALLOCATE(dy(-buff_size:n + buff_size))
11781180
1179-
if (p == 0) return;
1181+
if (p == 0) return;
11801182
@:ALLOCATE(z_cb(-1 - buff_size:p + buff_size))
11811183
@:ALLOCATE(z_cc(-buff_size:p + buff_size))
11821184
@:ALLOCATE(dz(-buff_size:p + buff_size))
@@ -1249,10 +1251,10 @@ contains
12491251
! Deallocating grid variables for the x-, y- and z-directions
12501252
@:DEALLOCATE(x_cb, x_cc, dx)
12511253
1252-
if (n == 0) return;
1254+
if (n == 0) return;
12531255
@:DEALLOCATE(y_cb, y_cc, dy)
12541256
1255-
if (p == 0) return;
1257+
if (p == 0) return;
12561258
@:DEALLOCATE(z_cb, z_cc, dz)
12571259
12581260
end subroutine s_finalize_global_parameters_module

src/simulation/m_mpi_proxy.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -137,7 +137,7 @@ contains
137137
& 'bc_z%grcbc_in', 'bc_z%grcbc_out', 'bc_z%grcbc_vel_out', &
138138
& 'cfl_adap_dt', 'cfl_const_dt', 'cfl_dt', 'surface_tension', &
139139
& 'viscous', 'shear_stress', 'bulk_stress', 'bubbles_lagrange', &
140-
& 'hyperelasticity', 'rkck_adap_dt' ]
140+
& 'hyperelasticity', 'rkck_adap_dt', 'read_bc' ]
141141
call MPI_BCAST(${VAR}$, 1, MPI_LOGICAL, 0, MPI_COMM_WORLD, ierr)
142142
#:endfor
143143

src/simulation/m_start_up.fpp

Lines changed: 7 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -211,6 +211,11 @@ contains
211211

212212
if (cfl_adap_dt .or. cfl_const_dt .or. rkck_adap_dt) cfl_dt = .true.
213213

214+
if (any((/bc_x%beg, bc_x%end, bc_y%beg, bc_y%end, bc_z%beg, bc_z%end/) == -17) .or. &
215+
num_bc_patches /= dflt_int) then
216+
read_bc = .true.
217+
endif
218+
214219
else
215220
call s_mpi_abort(trim(file_path)//' is missing. Exiting.')
216221
end if
@@ -281,7 +286,7 @@ contains
281286
call s_mpi_abort(trim(file_path)//' is missing. Exiting.')
282287
end if
283288

284-
if (num_bc_patches > 0) then
289+
if (read_bc) then
285290
call s_read_serial_boundary_condition_files(t_step_dir, bc_type)
286291
else
287292
call s_assign_default_bc_type(bc_type)
@@ -941,7 +946,7 @@ contains
941946

942947
deallocate (x_cb_glb, y_cb_glb, z_cb_glb)
943948

944-
if (num_bc_patches > 0) then
949+
if (read_bc) then
945950
call s_read_parallel_boundary_condition_files(bc_type)
946951
else
947952
call s_assign_default_bc_type(bc_type)

0 commit comments

Comments
 (0)