Skip to content

Commit

Permalink
fixing precision
Browse files Browse the repository at this point in the history
  • Loading branch information
Diego Vaca committed Dec 21, 2024
2 parents 97e5af6 + d581949 commit af9371e
Show file tree
Hide file tree
Showing 22 changed files with 235 additions and 449 deletions.
2 changes: 1 addition & 1 deletion src/post_process/m_data_output.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -33,9 +33,9 @@ module m_data_output
s_open_energy_data_file, &
s_write_grid_to_formatted_database_file, &
s_write_variable_to_formatted_database_file, &
s_write_lag_bubbles_results, &
s_write_intf_data_file, &
s_write_energy_data_file, &
s_write_lag_bubbles_results, &
s_close_formatted_database_file, &
s_close_intf_data_file, &
s_close_energy_data_file, &
Expand Down
2 changes: 1 addition & 1 deletion src/post_process/m_mpi_proxy.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -170,7 +170,7 @@ contains
& 'prim_vars_wrt', 'c_wrt', 'qm_wrt','schlieren_wrt', 'bubbles_euler', 'qbmm', &
& 'polytropic', 'polydisperse', 'file_per_process', 'relax', 'cf_wrt', &
& 'adv_n', 'ib', 'cfl_adap_dt', 'cfl_const_dt', 'cfl_dt', &
& 'surface_tension', 'hyperelasticity', 'bubbles_lagrange', 'rkck_adap_dt' ]
& 'surface_tension', 'hyperelasticity', 'bubbles_lagrange', 'rkck_adap_dt']
call MPI_BCAST(${VAR}$, 1, MPI_LOGICAL, 0, MPI_COMM_WORLD, ierr)
#:endfor
Expand Down
10 changes: 2 additions & 8 deletions src/post_process/m_start_up.f90
Original file line number Diff line number Diff line change
Expand Up @@ -84,9 +84,8 @@ subroutine s_read_input_file
polydisperse, poly_sigma, file_per_process, relax, &
relax_model, cf_wrt, sigma, adv_n, ib, num_ibs, &
cfl_adap_dt, cfl_const_dt, t_save, t_stop, n_start, &
cfl_target, surface_tension, &
sim_data, hyperelasticity, &
bubbles_lagrange, rkck_adap_dt
cfl_target, surface_tension, bubbles_lagrange, rkck_adap_dt, &
sim_data, hyperelasticity

! Inquiring the status of the post_process.inp file
file_loc = 'post_process.inp'
Expand Down Expand Up @@ -715,11 +714,6 @@ subroutine s_save_data(t_step, varname, pres, c, H)
call s_write_lag_bubbles_results(t_step) !! Individual bubble evolution
end if

! if (proc_rank == 0 .and. sim_data) then
! close (211)
! close (251)
! end if

if (sim_data .and. proc_rank == 0) then
call s_close_intf_data_file()
call s_close_energy_data_file()
Expand Down
1 change: 0 additions & 1 deletion src/pre_process/m_assign_variables.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -517,7 +517,6 @@ contains
q_prim_vf(i + xibeg - 1)%sf(j, k, l) = eta*xi_cart(i) + &
(1_wp - eta)*orig_prim_vf(i + xibeg - 1)
end do
end if
if (mpp_lim .and. bubbles_euler) then
Expand Down
2 changes: 0 additions & 2 deletions src/simulation/m_global_parameters.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -1206,9 +1206,7 @@ contains
#:endif
!$acc enter data copyin(nb, R0ref, Ca, Web, Re_inv, weight, R0, V0, bubbles_euler, polytropic, polydisperse, qbmm, R0_type, ptil, bubble_model, thermal, poly_sigma)
!$acc enter data copyin(R_n, R_v, phi_vn, phi_nv, Pe_c, Tw, pv, M_n, M_v, k_n, k_v, pb0, mass_n0, mass_v0, Pe_T, Re_trans_T, Re_trans_c, Im_trans_T, Im_trans_c, omegaN, mul0, ss, gamma_v, mu_v, gamma_m, gamma_n, mu_n, gam)
!$acc enter data copyin(dir_idx, dir_flg, dir_idx_tau)
!$acc enter data copyin(relax, relax_model, palpha_eps,ptgalpha_eps)
Expand Down
8 changes: 4 additions & 4 deletions src/simulation/m_mpi_proxy.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -196,8 +196,8 @@ contains
& 'bc_y%grcbc_in', 'bc_y%grcbc_out', 'bc_y%grcbc_vel_out', &
& 'bc_z%grcbc_in', 'bc_z%grcbc_out', 'bc_z%grcbc_vel_out', &
& 'cfl_adap_dt', 'cfl_const_dt', 'cfl_dt', 'surface_tension', &
& 'viscous', 'shear_stress', 'bulk_stress', &
& 'hyperelasticity', 'bubbles_lagrange', 'rkck_adap_dt' ]
& 'viscous', 'shear_stress', 'bulk_stress', 'bubbles_lagrange', &
& 'hyperelasticity', 'rkck_adap_dt' ]
call MPI_BCAST(${VAR}$, 1, MPI_LOGICAL, 0, MPI_COMM_WORLD, ierr)
#:endfor
Expand Down Expand Up @@ -235,8 +235,8 @@ contains
& 'bc_x%pres_in','bc_x%pres_out','bc_y%pres_in','bc_y%pres_out', 'bc_z%pres_in','bc_z%pres_out', &
& 'x_domain%beg', 'x_domain%end', 'y_domain%beg', 'y_domain%end', &
& 'z_domain%beg', 'z_domain%end', 'x_a', 'x_b', 'y_a', 'y_b', 'z_a', &
& 'z_b', 't_stop', 't_save', 'cfl_target', 'rkck_tolerance' ]
call MPI_BCAST(${VAR}$, 1, MPI_DOUBLE_PRECISION, 0, MPI_COMM_WORLD, ierr)
& 'z_b', 't_stop', 't_save', 'cfl_target', 'rkck_tolerance']
call MPI_BCAST(${VAR}$, 1, mpi_p, 0, MPI_COMM_WORLD, ierr)
#:endfor
do i = 1, 3
Expand Down
7 changes: 3 additions & 4 deletions src/simulation/m_riemann_solvers.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -1717,11 +1717,10 @@ contains
end do
end do
!$acc end parallel loop
elseif (model_eqns == 2 .and. bubbles_euler) then
!$acc parallel loop collapse(3) gang vector default(present) private(R0_L, R0_R, V0_L, V0_R, &
!$acc P0_L, P0_R, pbw_L, pbw_R, vel_L, vel_R, rho_avg, alpha_L, alpha_R, h_avg, gamma_avg, &
!$acc s_L, s_R, s_S, nbub_L, nbub_R, ptilde_L, ptilde_R, vel_avg_rms, Re_L, Re_R, &
!$acc pcorr, zcoef, vel_L_tmp, vel_R_tmp)
!$acc parallel loop collapse(3) gang vector default(present) private(R0_L, R0_R, V0_L, V0_R, P0_L, P0_R, pbw_L, pbw_R, vel_L, vel_R, &
!$acc rho_avg, alpha_L, alpha_R, h_avg, gamma_avg, s_L, s_R, s_S, nbub_L, nbub_R, ptilde_L, ptilde_R, vel_avg_rms, Re_L, Re_R, pcorr, zcoef, vel_L_tmp, vel_R_tmp)
do l = is3%beg, is3%end
do k = is2%beg, is2%end
do j = is1%beg, is1%end
Expand Down
13 changes: 6 additions & 7 deletions src/simulation/m_start_up.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -170,11 +170,11 @@ contains
pi_fac, adv_n, adap_dt, bf_x, bf_y, bf_z, &
k_x, k_y, k_z, w_x, w_y, w_z, p_x, p_y, p_z, &
g_x, g_y, g_z, n_start, t_save, t_stop, &
cfl_adap_dt, cfl_const_dt, cfl_target, &
viscous, surface_tension, &
hyperelasticity, R0ref, &
cfl_adap_dt, cfl_const_dt, cfl_target, &
viscous, surface_tension, &
bubbles_lagrange, lag_params, &
rkck_adap_dt, rkck_tolerance
rkck_adap_dt, rkck_tolerance, &
hyperelasticity, R0ref

! Checking that an input file has been provided by the user. If it
! has, then the input file is read in, otherwise, simulation exits.
Expand Down Expand Up @@ -629,7 +629,7 @@ contains
NVARS_MOK = int(sys_size, MPI_OFFSET_KIND)

! Read the data for each variable
if ( bubbles_euler .or. elasticity ) then
if (bubbles_euler .or. elasticity) then

do i = 1, sys_size!adv_idx%end
var_MOK = int(i, MPI_OFFSET_KIND)
Expand Down Expand Up @@ -765,8 +765,7 @@ contains
NVARS_MOK = int(sys_size, MPI_OFFSET_KIND)

! Read the data for each variable
if ( bubbles_euler .or. elasticity ) then

if (bubbles_euler .or. elasticity) then
do i = 1, sys_size !adv_idx%end
var_MOK = int(i, MPI_OFFSET_KIND)
! Initial displacement to skip at beginning of file
Expand Down
62 changes: 31 additions & 31 deletions tests/18A29336/golden-metadata.txt

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

14 changes: 7 additions & 7 deletions tests/18A29336/golden.txt

Large diffs are not rendered by default.

Loading

0 comments on commit af9371e

Please sign in to comment.