Skip to content

Commit

Permalink
Removal of ! ------ (MFlowCode#486)
Browse files Browse the repository at this point in the history
  • Loading branch information
okBrian authored Jun 23, 2024
1 parent 7827d8f commit fc85a76
Show file tree
Hide file tree
Showing 35 changed files with 462 additions and 460 deletions.
2 changes: 1 addition & 1 deletion src/common/m_helper.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -104,7 +104,7 @@ contains
end if
end subroutine s_compute_finite_difference_coefficients ! --------------
end subroutine s_compute_finite_difference_coefficients
!> Computes the bubble number density n from the primitive variables
!! @param vftmp is the void fraction
Expand Down
47 changes: 25 additions & 22 deletions src/common/m_mpi_common.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@ contains
!> The subroutine initializes the MPI execution environment
!! and queries both the number of processors which will be
!! available for the job and the local processor rank.
subroutine s_mpi_initialize ! ----------------------------------------
subroutine s_mpi_initialize
#ifndef MFC_MPI
Expand Down Expand Up @@ -58,9 +58,11 @@ contains
#endif
end subroutine s_mpi_initialize ! --------------------------------------
end subroutine s_mpi_initialize
subroutine s_initialize_mpi_data(q_cons_vf, ib_markers) ! --------------------------
!! @param q_cons_vf Conservative variables
!! @param ib_markers track if a cell is within the immersed boundary
subroutine s_initialize_mpi_data(q_cons_vf, ib_markers)
type(scalar_field), &
dimension(sys_size), &
Expand Down Expand Up @@ -188,7 +190,7 @@ contains
#endif
end subroutine s_initialize_mpi_data ! ---------------------------------
end subroutine s_initialize_mpi_data
subroutine mpi_bcast_time_step_values(proc_time, time_avg)
Expand Down Expand Up @@ -217,7 +219,7 @@ contains
!! @param icfl_max_glb Global maximum ICFL stability criterion
!! @param vcfl_max_glb Global maximum VCFL stability criterion
!! @param Rc_min_glb Global minimum Rc stability criterion
subroutine s_mpi_reduce_stability_criteria_extrema(icfl_max_loc, & ! --
subroutine s_mpi_reduce_stability_criteria_extrema(icfl_max_loc, &
vcfl_max_loc, &
ccfl_max_loc, &
Rc_min_loc, &
Expand Down Expand Up @@ -257,7 +259,7 @@ contains
#endif
#endif
end subroutine s_mpi_reduce_stability_criteria_extrema ! ---------------
end subroutine s_mpi_reduce_stability_criteria_extrema
!> The following subroutine takes the input local variable
!! from all processors and reduces to the sum of all
Expand All @@ -266,7 +268,7 @@ contains
!! @param var_loc Some variable containing the local value which should be
!! reduced amongst all the processors in the communicator.
!! @param var_glb The globally reduced value
subroutine s_mpi_allreduce_sum(var_loc, var_glb) ! ---------------------
subroutine s_mpi_allreduce_sum(var_loc, var_glb)
real(kind(0d0)), intent(in) :: var_loc
real(kind(0d0)), intent(out) :: var_glb
Expand All @@ -279,7 +281,7 @@ contains
#endif
end subroutine s_mpi_allreduce_sum ! -----------------------------------
end subroutine s_mpi_allreduce_sum
!> The following subroutine takes the input local variable
!! from all processors and reduces to the minimum of all
Expand All @@ -288,7 +290,7 @@ contains
!! @param var_loc Some variable containing the local value which should be
!! reduced amongst all the processors in the communicator.
!! @param var_glb The globally reduced value
subroutine s_mpi_allreduce_min(var_loc, var_glb) ! ---------------------
subroutine s_mpi_allreduce_min(var_loc, var_glb)
real(kind(0d0)), intent(in) :: var_loc
real(kind(0d0)), intent(out) :: var_glb
Expand All @@ -301,7 +303,7 @@ contains
#endif
end subroutine s_mpi_allreduce_min ! -----------------------------------
end subroutine s_mpi_allreduce_min
!> The following subroutine takes the input local variable
!! from all processors and reduces to the maximum of all
Expand All @@ -310,7 +312,7 @@ contains
!! @param var_loc Some variable containing the local value which should be
!! reduced amongst all the processors in the communicator.
!! @param var_glb The globally reduced value
subroutine s_mpi_allreduce_max(var_loc, var_glb) ! ---------------------
subroutine s_mpi_allreduce_max(var_loc, var_glb)
real(kind(0d0)), intent(in) :: var_loc
real(kind(0d0)), intent(out) :: var_glb
Expand All @@ -323,15 +325,15 @@ contains
#endif
end subroutine s_mpi_allreduce_max ! -----------------------------------
end subroutine s_mpi_allreduce_max
!> The following subroutine takes the inputted variable and
!! determines its minimum value on the entire computational
!! domain. The result is stored back into inputted variable.
!! @param var_loc holds the local value to be reduced among
!! all the processors in communicator. On output, the variable holds
!! the minimum value, reduced amongst all of the local values.
subroutine s_mpi_reduce_min(var_loc) ! ---------------------------------
subroutine s_mpi_reduce_min(var_loc)
real(kind(0d0)), intent(inout) :: var_loc
Expand All @@ -352,7 +354,7 @@ contains
#endif
end subroutine s_mpi_reduce_min ! --------------------------------------
end subroutine s_mpi_reduce_min
!> The following subroutine takes the first element of the
!! 2-element inputted variable and determines its maximum
Expand All @@ -366,7 +368,7 @@ contains
!! On output, this variable holds the maximum value, reduced amongst
!! all of the local values, and the process rank to which the value
!! belongs.
subroutine s_mpi_reduce_maxloc(var_loc) ! ------------------------------
subroutine s_mpi_reduce_maxloc(var_loc)
real(kind(0d0)), dimension(2), intent(inout) :: var_loc
Expand All @@ -388,10 +390,11 @@ contains
#endif
end subroutine s_mpi_reduce_maxloc ! -----------------------------------
end subroutine s_mpi_reduce_maxloc
!> The subroutine terminates the MPI execution environment.
subroutine s_mpi_abort(prnt) ! ---------------------------------------------
!! @param prnt error message to be printed
subroutine s_mpi_abort(prnt)
character(len=*), intent(in), optional :: prnt
Expand All @@ -412,10 +415,10 @@ contains
#endif
end subroutine s_mpi_abort ! -------------------------------------------
end subroutine s_mpi_abort
!>Halts all processes until all have reached barrier.
subroutine s_mpi_barrier ! -------------------------------------------
subroutine s_mpi_barrier
#ifdef MFC_MPI
Expand All @@ -424,10 +427,10 @@ contains
#endif
end subroutine s_mpi_barrier ! -----------------------------------------
end subroutine s_mpi_barrier
!> The subroutine finalizes the MPI execution environment.
subroutine s_mpi_finalize ! ------------------------------------------
subroutine s_mpi_finalize
#ifdef MFC_MPI
Expand All @@ -436,6 +439,6 @@ contains
#endif
end subroutine s_mpi_finalize ! ----------------------------------------
end subroutine s_mpi_finalize
end module m_mpi_common
23 changes: 12 additions & 11 deletions src/common/m_phase_change.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -28,18 +28,19 @@ module m_phase_change

implicit none

private; public :: s_initialize_phasechange_module, &
s_relaxation_solver, &
s_infinite_relaxation_k, &
s_finalize_relaxation_solver_module
private;
public :: s_initialize_phasechange_module, &
s_relaxation_solver, &
s_infinite_relaxation_k, &
s_finalize_relaxation_solver_module

!> @name Abstract interface for creating function pointers
!> @{
abstract interface

!> @name Abstract subroutine for the infinite relaxation solver
!> @{
subroutine s_abstract_relaxation_solver(q_cons_vf) ! -------
subroutine s_abstract_relaxation_solver(q_cons_vf)
import :: scalar_field, sys_size
type(scalar_field), dimension(sys_size), intent(inout) :: q_cons_vf
end subroutine
Expand Down Expand Up @@ -86,14 +87,14 @@ contains
D = ((gs_min(lp) - 1.0d0)*cvs(lp)) &
/((gs_min(vp) - 1.0d0)*cvs(vp))

end subroutine s_initialize_phasechange_module !-------------------------------
end subroutine s_initialize_phasechange_module

!> This subroutine is created to activate either the pT- (N fluids) or the
!! pTg-equilibrium (2 fluids for g-equilibrium)
!! model, also considering mass depletion, depending on the incoming
!! state conditions.
!! @param q_cons_vf Cell-average conservative variables
subroutine s_infinite_relaxation_k(q_cons_vf) ! ----------------
subroutine s_infinite_relaxation_k(q_cons_vf)

type(scalar_field), dimension(sys_size), intent(inout) :: q_cons_vf
real(kind(0.0d0)) :: pS, pSOV, pSSL !< equilibrium pressure for mixture, overheated vapor, and subcooled liquid
Expand Down Expand Up @@ -283,7 +284,7 @@ contains
end do
end do

end subroutine s_infinite_relaxation_k ! ----------------
end subroutine s_infinite_relaxation_k

!> This auxiliary subroutine is created to activate the pT-equilibrium for N fluids
!! @param j generic loop iterator for x direction
Expand Down Expand Up @@ -387,7 +388,7 @@ contains
! common temperature
TS = (rhoe + pS - mQ)/mCP

end subroutine s_infinite_pt_relaxation_k ! -----------------------
end subroutine s_infinite_pt_relaxation_k

!> This auxiliary subroutine is created to activate the pTg-equilibrium for N fluids under pT
!! and 2 fluids under pTg-equilibrium. There is a final common p and T during relaxation
Expand Down Expand Up @@ -510,7 +511,7 @@ contains
! common temperature
TS = (rhoe + pS - mQ)/mCP
end subroutine s_infinite_ptg_relaxation_k ! -----------------------
end subroutine s_infinite_ptg_relaxation_k
!> This auxiliary subroutine corrects the partial densities of the REACTING fluids in case one of them is negative
!! but their sum is positive. Inert phases are not corrected at this moment
Expand Down Expand Up @@ -782,7 +783,7 @@ contains
end subroutine s_TSat

!> This subroutine finalizes the phase change module
subroutine s_finalize_relaxation_solver_module()
subroutine s_finalize_relaxation_solver_module
end subroutine

#endif
Expand Down
24 changes: 12 additions & 12 deletions src/common/m_variables_conversion.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -216,7 +216,7 @@ contains
qv_sf(i, j, k) = qv
#endif

end subroutine s_convert_mixture_to_mixture_variables ! ----------------
end subroutine s_convert_mixture_to_mixture_variables

!> This procedure is used alongside with the gamma/pi_inf
!! model to transfer the density, the specific heat ratio
Expand Down Expand Up @@ -341,7 +341,7 @@ contains
qv_sf(j, k, l) = qv
#endif

end subroutine s_convert_species_to_mixture_variables_bubbles ! ----------------
end subroutine s_convert_species_to_mixture_variables_bubbles

!> This subroutine is designed for the volume fraction model
!! and provided a set of either conservative or primitive
Expand Down Expand Up @@ -440,7 +440,7 @@ contains
qv_sf(k, l, r) = qv
#endif

end subroutine s_convert_species_to_mixture_variables ! ----------------
end subroutine s_convert_species_to_mixture_variables

subroutine s_convert_species_to_mixture_variables_acc(rho_K, &
gamma_K, pi_inf_K, qv_K, &
Expand Down Expand Up @@ -523,7 +523,7 @@ contains
end if
#endif

end subroutine s_convert_species_to_mixture_variables_acc ! ----------------
end subroutine s_convert_species_to_mixture_variables_acc

subroutine s_convert_species_to_mixture_variables_bubbles_acc(rho_K, &
gamma_K, pi_inf_K, qv_K, &
Expand Down Expand Up @@ -596,7 +596,7 @@ contains
!> The computation of parameters, the allocation of memory,
!! the association of pointers and/or the execution of any
!! other procedures that are necessary to setup the module.
subroutine s_initialize_variables_conversion_module ! ----------------
subroutine s_initialize_variables_conversion_module

integer :: i, j

Expand Down Expand Up @@ -752,7 +752,7 @@ contains
s_convert_to_mixture_variables => &
s_convert_species_to_mixture_variables
end if
end subroutine s_initialize_variables_conversion_module ! --------------
end subroutine s_initialize_variables_conversion_module

!Initialize mv at the quadrature nodes based on the initialized moments and sigma
subroutine s_initialize_mv(qK_cons_vf, mv)
Expand Down Expand Up @@ -1014,7 +1014,7 @@ contains
end do
!$acc end parallel loop

end subroutine s_convert_conservative_to_primitive_variables ! ---------
end subroutine s_convert_conservative_to_primitive_variables

!> The following procedure handles the conversion between
!! the primitive variables and the conservative variables.
Expand Down Expand Up @@ -1175,7 +1175,7 @@ contains
end if
#endif

end subroutine s_convert_primitive_to_conservative_variables ! ---------
end subroutine s_convert_primitive_to_conservative_variables

!> The following subroutine handles the conversion between
!! the primitive variables and the Eulerian flux variables.
Expand All @@ -1185,7 +1185,7 @@ contains
!! @param ix Index bounds in the first coordinate direction
!! @param iy Index bounds in the second coordinate direction
!! @param iz Index bounds in the third coordinate direction
subroutine s_convert_primitive_to_flux_variables(qK_prim_vf, & ! ------
subroutine s_convert_primitive_to_flux_variables(qK_prim_vf, &
FK_vf, &
FK_src_vf, &
is1, is2, is3, s2b, s3b)
Expand Down Expand Up @@ -1309,9 +1309,9 @@ contains
end do
#endif

end subroutine s_convert_primitive_to_flux_variables ! -----------------
end subroutine s_convert_primitive_to_flux_variables

subroutine s_finalize_variables_conversion_module ! ------------------
subroutine s_finalize_variables_conversion_module

! Deallocating the density, the specific heat ratio function and the
! liquid stiffness function
Expand All @@ -1335,6 +1335,6 @@ contains
! computing the mixture/species variables to the mixture variables
s_convert_to_mixture_variables => null()

end subroutine s_finalize_variables_conversion_module ! ----------------
end subroutine s_finalize_variables_conversion_module

end module m_variables_conversion
Loading

0 comments on commit fc85a76

Please sign in to comment.