Skip to content

Commit

Permalink
format
Browse files Browse the repository at this point in the history
  • Loading branch information
sbryngelson committed Dec 26, 2024
1 parent 1cdc886 commit 7cc5443
Show file tree
Hide file tree
Showing 5 changed files with 12 additions and 16 deletions.
12 changes: 6 additions & 6 deletions src/post_process/m_start_up.f90
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@
!! MPI decomposition and I/O procedures
module m_start_up

! Dependencies
! Dependencies

use m_derived_types !< Definitions of the derived types

Expand Down Expand Up @@ -271,7 +271,7 @@ subroutine s_save_data(t_step, varname, pres, c, H)
end do
end if

! Adding the density to the formatted database file
! Adding the density to the formatted database file
if (rho_wrt &
.or. &
(model_eqns == 1 .and. (cons_vars_wrt .or. prim_vars_wrt))) then
Expand All @@ -283,7 +283,7 @@ subroutine s_save_data(t_step, varname, pres, c, H)

end if

! Adding the momentum to the formatted database file
! Adding the momentum to the formatted database file
do i = 1, E_idx - mom_idx%beg
if (mom_wrt(i) .or. cons_vars_wrt) then
q_sf = q_cons_vf(i + cont_idx%end)%sf(x_beg:x_end, y_beg:y_end, z_beg:z_end)
Expand All @@ -295,7 +295,7 @@ subroutine s_save_data(t_step, varname, pres, c, H)
end if
end do

! Adding the velocity to the formatted database file
! Adding the velocity to the formatted database file
do i = 1, E_idx - mom_idx%beg
if (vel_wrt(i) .or. prim_vars_wrt) then
q_sf = q_prim_vf(i + cont_idx%end)%sf(x_beg:x_end, y_beg:y_end, z_beg:z_end)
Expand Down Expand Up @@ -342,7 +342,7 @@ subroutine s_save_data(t_step, varname, pres, c, H)
end if
end do

! Adding the energy to the formatted database file
! Adding the energy to the formatted database file
if (E_wrt .or. cons_vars_wrt) then
q_sf = q_cons_vf(E_idx)%sf(x_beg:x_end, y_beg:y_end, z_beg:z_end)
write (varname, '(A)') 'E'
Expand All @@ -352,7 +352,7 @@ subroutine s_save_data(t_step, varname, pres, c, H)

end if

! Adding the elastic shear stresses to the formatted database file
! Adding the elastic shear stresses to the formatted database file
if (elasticity) then
do i = 1, stress_idx%end - stress_idx%beg + 1
if (prim_vars_wrt) then
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 @@ -387,7 +387,6 @@ contains
patch_icpp(patch_id)%pi_inf, &
patch_icpp(patch_id)%qv)
! Computing Mixture Variables of Smoothing Patch
if (model_eqns /= 4) then
Expand Down
1 change: 0 additions & 1 deletion src/pre_process/m_global_parameters.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,6 @@ module m_global_parameters

use m_thermochem, only: num_species


implicit none

! Logistics
Expand Down
12 changes: 6 additions & 6 deletions src/simulation/m_cbc.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -70,7 +70,7 @@ module m_cbc
real(wp), allocatable, dimension(:) :: ds !< Cell-width distribution in the s-direction
! CBC Coefficients
! CBC Coefficients
real(wp), allocatable, dimension(:, :) :: fd_coef_x !< Finite diff. coefficients x-dir
real(wp), allocatable, dimension(:, :) :: fd_coef_y !< Finite diff. coefficients y-dir
Expand Down Expand Up @@ -262,7 +262,7 @@ contains
! Allocating the cell-width distribution in the s-direction
@:ALLOCATE(ds(0:buff_size))
! Allocating/Computing CBC Coefficients in x-direction
! Allocating/Computing CBC Coefficients in x-direction
if (all((/bc_x%beg, bc_x%end/) <= -5) .and. all((/bc_x%beg, bc_x%end/) >= -13)) then
@:ALLOCATE(fd_coef_x(0:buff_size, -1:1))
Expand Down Expand Up @@ -707,7 +707,7 @@ contains
end do
end do
! PI4 of flux_rs_vf and flux_src_rs_vf at j = 1/2, 3/2
! PI4 of flux_rs_vf and flux_src_rs_vf at j = 1/2, 3/2
else
call s_convert_primitive_to_flux_variables(q_prim_rs${XYZ}$_vf, &
F_rs${XYZ}$_vf, &
Expand Down Expand Up @@ -756,12 +756,12 @@ contains
end if
! FD2 or FD4 of RHS at j = 0
! FD2 or FD4 of RHS at j = 0
!$acc parallel loop collapse(2) gang vector default(present) private(alpha_rho, vel, adv, mf, dvel_ds, dadv_ds, Re_cbc, dalpha_rho_ds,dvel_dt, dadv_dt, dalpha_rho_dt,L, lambda)
do r = is3%beg, is3%end
do k = is2%beg, is2%end
! Transferring the Primitive Variables
! Transferring the Primitive Variables
!$acc loop seq
do i = 1, contxe
alpha_rho(i) = q_prim_rs${XYZ}$_vf(0, k, r, i)
Expand Down Expand Up @@ -802,7 +802,7 @@ contains
! Compute mixture sound speed
call s_compute_speed_of_sound(pres, rho, gamma, pi_inf, H, adv, vel_K_sum, 0._wp, c)
! First-Order Spatial Derivatives of Primitive Variables
! First-Order Spatial Derivatives of Primitive Variables
!$acc loop seq
do i = 1, contxe
Expand Down
2 changes: 0 additions & 2 deletions src/simulation/m_weno.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,6 @@ module m_weno

use m_mpi_proxy


private; public :: s_initialize_weno_module, s_initialize_weno, s_finalize_weno_module, s_weno

!> @name The cell-average variables that will be WENO-reconstructed. Formerly, they
Expand Down Expand Up @@ -192,7 +191,6 @@ contains
@:ALLOCATE(v_rs_ws_y(is2_weno%beg:is2_weno%end, &
is1_weno%beg:is1_weno%end, is3_weno%beg:is3_weno%end, 1:sys_size))


! Allocating/Computing WENO Coefficients in z-direction
if (p == 0) return

Expand Down

0 comments on commit 7cc5443

Please sign in to comment.