Skip to content

Commit f0f3653

Browse files
committed
Finished first pass through pure subroutines
1 parent 883d78e commit f0f3653

File tree

11 files changed

+56
-56
lines changed

11 files changed

+56
-56
lines changed

src/common/m_variables_conversion.fpp

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -79,7 +79,7 @@ contains
7979
!! @param gamma Specific heat ratio function
8080
!! @param pi_inf Liquid stiffness function
8181
!! @param qv Fluid reference energy
82-
impure subroutine s_convert_to_mixture_variables(q_vf, i, j, k, &
82+
subroutine s_convert_to_mixture_variables(q_vf, i, j, k, &
8383
rho, gamma, pi_inf, qv, Re_K, G_K, G)
8484

8585
type(scalar_field), dimension(sys_size), intent(in) :: q_vf
@@ -205,7 +205,7 @@ contains
205205
!! @param gamma specific heat ratio function
206206
!! @param pi_inf liquid stiffness
207207
!! @param qv fluid reference energy
208-
impure subroutine s_convert_mixture_to_mixture_variables(q_vf, i, j, k, &
208+
subroutine s_convert_mixture_to_mixture_variables(q_vf, i, j, k, &
209209
rho, gamma, pi_inf, qv, Re_K, G_K, G)
210210

211211
type(scalar_field), dimension(sys_size), intent(in) :: q_vf
@@ -252,7 +252,7 @@ contains
252252
!! @param gamma specific heat ratio
253253
!! @param pi_inf liquid stiffness
254254
!! @param qv fluid reference energy
255-
impure subroutine s_convert_species_to_mixture_variables_bubbles(q_vf, j, k, l, &
255+
subroutine s_convert_species_to_mixture_variables_bubbles(q_vf, j, k, l, &
256256
rho, gamma, pi_inf, qv, Re_K, G_K, G)
257257

258258
type(scalar_field), dimension(sys_size), intent(in) :: q_vf
@@ -376,7 +376,7 @@ contains
376376
!! @param gamma specific heat ratio
377377
!! @param pi_inf liquid stiffness
378378
!! @param qv fluid reference energy
379-
impure subroutine s_convert_species_to_mixture_variables(q_vf, k, l, r, rho, &
379+
subroutine s_convert_species_to_mixture_variables(q_vf, k, l, r, rho, &
380380
gamma, pi_inf, qv, Re_K, G_K, G)
381381

382382
type(scalar_field), dimension(sys_size), intent(in) :: q_vf
@@ -816,7 +816,7 @@ contains
816816
!! @param ix Index bounds in first coordinate direction
817817
!! @param iy Index bounds in second coordinate direction
818818
!! @param iz Index bounds in third coordinate direction
819-
impure subroutine s_convert_conservative_to_primitive_variables(qK_cons_vf, &
819+
subroutine s_convert_conservative_to_primitive_variables(qK_cons_vf, &
820820
q_T_sf, &
821821
qK_prim_vf, &
822822
ibounds, &

src/simulation/m_mpi_proxy.fpp

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -55,7 +55,7 @@ contains
5555
!! available to the other processors. Then, the purpose of
5656
!! this subroutine is to distribute the user inputs to the
5757
!! remaining processors in the communicator.
58-
subroutine s_mpi_bcast_user_inputs()
58+
impure subroutine s_mpi_bcast_user_inputs()
5959
6060
#ifdef MFC_MPI
6161
@@ -213,7 +213,7 @@ contains
213213
!! in each of the coordinate directions, approximately the
214214
!! same number of cells, and then recomputing the affected
215215
!! global parameters.
216-
subroutine s_mpi_decompose_computational_domain
216+
impure subroutine s_mpi_decompose_computational_domain
217217
218218
#ifdef MFC_MPI
219219
@@ -586,7 +586,7 @@ contains
586586
!! directly from those of the cell-width distributions.
587587
!! @param mpi_dir MPI communication coordinate direction
588588
!! @param pbc_loc Processor boundary condition (PBC) location
589-
subroutine s_mpi_sendrecv_grid_variables_buffers(mpi_dir, pbc_loc)
589+
impure subroutine s_mpi_sendrecv_grid_variables_buffers(mpi_dir, pbc_loc)
590590
591591
integer, intent(in) :: mpi_dir
592592
integer, intent(in) :: pbc_loc
@@ -766,7 +766,7 @@ contains
766766
!> The goal of this procedure is to populate the buffers of
767767
!! the cell-average conservative variables by communicating
768768
!! with the neighboring processors.
769-
subroutine s_mpi_sendrecv_ib_buffers(ib_markers, gp_layers)
769+
impure subroutine s_mpi_sendrecv_ib_buffers(ib_markers, gp_layers)
770770
771771
type(integer_field), intent(inout) :: ib_markers
772772
integer, intent(in) :: gp_layers
@@ -1612,7 +1612,7 @@ contains
16121612
16131613
end subroutine s_mpi_sendrecv_ib_buffers
16141614
1615-
subroutine s_mpi_send_random_number(phi_rn, num_freq)
1615+
impure subroutine s_mpi_send_random_number(phi_rn, num_freq)
16161616
integer, intent(in) :: num_freq
16171617
real(wp), intent(inout), dimension(1:num_freq) :: phi_rn
16181618
#ifdef MFC_MPI

src/simulation/m_qbmm.fpp

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,7 @@ module m_qbmm
4343

4444
contains
4545

46-
subroutine s_initialize_qbmm_module
46+
impure subroutine s_initialize_qbmm_module
4747

4848
integer :: i1, i2, q, i, j
4949

@@ -411,7 +411,7 @@ contains
411411

412412
end subroutine s_initialize_qbmm_module
413413

414-
subroutine s_compute_qbmm_rhs(idir, q_cons_vf, q_prim_vf, rhs_vf, flux_n_vf, pb, rhs_pb, mv, rhs_mv)
414+
pure subroutine s_compute_qbmm_rhs(idir, q_cons_vf, q_prim_vf, rhs_vf, flux_n_vf, pb, rhs_pb, mv, rhs_mv)
415415

416416
integer, intent(in) :: idir
417417
type(scalar_field), dimension(sys_size), intent(in) :: q_cons_vf, q_prim_vf
@@ -679,7 +679,7 @@ contains
679679

680680
!Coefficient array for non-polytropic model (pb and mv values are accounted in wght_pb and wght_mv)
681681

682-
subroutine s_coeff_nonpoly(pres, rho, c, coeffs)
682+
pure subroutine s_coeff_nonpoly(pres, rho, c, coeffs)
683683
#ifdef _CRAYFTN
684684
!DIR$ INLINEALWAYS s_coeff_nonpoly
685685
#else
@@ -752,7 +752,7 @@ contains
752752
end subroutine s_coeff_nonpoly
753753

754754
!Coefficient array for polytropic model (pb for each R0 bin accounted for in wght_pb)
755-
subroutine s_coeff(pres, rho, c, coeffs)
755+
pure subroutine s_coeff(pres, rho, c, coeffs)
756756
#ifdef _CRAYFTN
757757
!DIR$ INLINEALWAYS s_coeff
758758
#else

src/simulation/m_rhs.fpp

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -172,7 +172,7 @@ contains
172172
!> The computation of parameters, the allocation of memory,
173173
!! the association of pointers and/or the execution of any
174174
!! other procedures that are necessary to setup the module.
175-
subroutine s_initialize_rhs_module
175+
impure subroutine s_initialize_rhs_module
176176

177177
integer :: i, j, k, l, id !< Generic loop iterators
178178

@@ -611,7 +611,7 @@ contains
611611

612612
end subroutine s_initialize_rhs_module
613613

614-
subroutine s_compute_rhs(q_cons_vf, q_T_sf, q_prim_vf, bc_type, rhs_vf, pb, rhs_pb, mv, rhs_mv, t_step, time_avg, stage)
614+
impure subroutine s_compute_rhs(q_cons_vf, q_T_sf, q_prim_vf, bc_type, rhs_vf, pb, rhs_pb, mv, rhs_mv, t_step, time_avg, stage)
615615

616616
type(scalar_field), dimension(sys_size), intent(inout) :: q_cons_vf
617617
type(scalar_field), intent(inout) :: q_T_sf
@@ -1753,7 +1753,7 @@ contains
17531753
!! purpose, this pressure is finally corrected using the
17541754
!! mixture-total-energy equation.
17551755
!! @param q_cons_vf Cell-average conservative variables
1756-
subroutine s_pressure_relaxation_procedure(q_cons_vf)
1756+
pure subroutine s_pressure_relaxation_procedure(q_cons_vf)
17571757

17581758
type(scalar_field), dimension(sys_size), intent(inout) :: q_cons_vf
17591759

@@ -2134,7 +2134,7 @@ contains
21342134
end subroutine s_reconstruct_cell_boundary_values_first_order
21352135

21362136
!> Module deallocation and/or disassociation procedures
2137-
subroutine s_finalize_rhs_module
2137+
impure subroutine s_finalize_rhs_module
21382138

21392139
integer :: i, j, l
21402140

src/simulation/m_riemann_solvers.fpp

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -202,7 +202,7 @@ contains
202202
!! For more information please refer to:
203203
!! 1) s_compute_cartesian_viscous_source_flux
204204
!! 2) s_compute_cylindrical_viscous_source_flux
205-
subroutine s_compute_viscous_source_flux(velL_vf, &
205+
pure subroutine s_compute_viscous_source_flux(velL_vf, &
206206
dvelL_dx_vf, &
207207
dvelL_dy_vf, &
208208
dvelL_dz_vf, &
@@ -3311,7 +3311,7 @@ contains
33113311
!> The computation of parameters, the allocation of memory,
33123312
!! the association of pointers and/or the execution of any
33133313
!! other procedures that are necessary to setup the module.
3314-
subroutine s_initialize_riemann_solvers_module
3314+
impure subroutine s_initialize_riemann_solvers_module
33153315
33163316
! Allocating the variables that will be utilized to formulate the
33173317
! left, right, and average states of the Riemann problem, as well
@@ -3956,7 +3956,7 @@ contains
39563956
!! @param ix Index bounds in first coordinate direction
39573957
!! @param iy Index bounds in second coordinate direction
39583958
!! @param iz Index bounds in third coordinate direction
3959-
subroutine s_compute_cylindrical_viscous_source_flux(velL_vf, &
3959+
pure subroutine s_compute_cylindrical_viscous_source_flux(velL_vf, &
39603960
dvelL_dx_vf, &
39613961
dvelL_dy_vf, &
39623962
dvelL_dz_vf, &
@@ -4483,7 +4483,7 @@ contains
44834483
!! @param ix Index bounds in first coordinate direction
44844484
!! @param iy Index bounds in second coordinate direction
44854485
!! @param iz Index bounds in third coordinate direction
4486-
subroutine s_compute_cartesian_viscous_source_flux(velL_vf, &
4486+
pure subroutine s_compute_cartesian_viscous_source_flux(velL_vf, &
44874487
dvelL_dx_vf, &
44884488
dvelL_dy_vf, &
44894489
dvelL_dz_vf, &
@@ -4968,7 +4968,7 @@ contains
49684968
!! @param ix Index bounds in first coordinate direction
49694969
!! @param iy Index bounds in second coordinate direction
49704970
!! @param iz Index bounds in third coordinate direction
4971-
subroutine s_finalize_riemann_solver(flux_vf, flux_src_vf, &
4971+
pure subroutine s_finalize_riemann_solver(flux_vf, flux_src_vf, &
49724972
flux_gsrc_vf, &
49734973
norm_dir, ix, iy, iz)
49744974
@@ -5127,7 +5127,7 @@ contains
51275127
end subroutine s_finalize_riemann_solver
51285128
51295129
!> Module deallocation and/or disassociation procedures
5130-
subroutine s_finalize_riemann_solvers_module
5130+
impure subroutine s_finalize_riemann_solvers_module
51315131
51325132
if (viscous) then
51335133
@:DEALLOCATE(Re_avg_rsx_vf)

src/simulation/m_sim_helpers.f90

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ module m_sim_helpers
2929
!! @param j x index
3030
!! @param k y index
3131
!! @param l z index
32-
subroutine s_compute_enthalpy(q_prim_vf, pres, rho, gamma, pi_inf, Re, H, alpha, vel, vel_sum, j, k, l)
32+
pure subroutine s_compute_enthalpy(q_prim_vf, pres, rho, gamma, pi_inf, Re, H, alpha, vel, vel_sum, j, k, l)
3333
#ifdef _CRAYFTN
3434
!DIR$ INLINEALWAYS s_compute_enthalpy
3535
#else
@@ -97,7 +97,7 @@ end subroutine s_compute_enthalpy
9797
!! @param icfl_sf cell centered inviscid cfl number
9898
!! @param vcfl_sf (optional) cell centered viscous cfl number
9999
!! @param Rc_sf (optional) cell centered Rc
100-
subroutine s_compute_stability_from_dt(vel, c, rho, Re_l, j, k, l, icfl_sf, vcfl_sf, Rc_sf)
100+
pure subroutine s_compute_stability_from_dt(vel, c, rho, Re_l, j, k, l, icfl_sf, vcfl_sf, Rc_sf)
101101
!$acc routine seq
102102
real(wp), intent(in), dimension(num_vels) :: vel
103103
real(wp), intent(in) :: c, rho
@@ -194,7 +194,7 @@ end subroutine s_compute_stability_from_dt
194194
!! @param j x coordinate
195195
!! @param k y coordinate
196196
!! @param l z coordinate
197-
subroutine s_compute_dt_from_cfl(vel, c, max_dt, rho, Re_l, j, k, l)
197+
pure subroutine s_compute_dt_from_cfl(vel, c, max_dt, rho, Re_l, j, k, l)
198198
!$acc routine seq
199199
real(wp), dimension(num_vels), intent(in) :: vel
200200
real(wp), intent(in) :: c, rho
@@ -268,9 +268,9 @@ subroutine s_compute_dt_from_cfl(vel, c, max_dt, rho, Re_l, j, k, l)
268268

269269
end subroutine s_compute_dt_from_cfl
270270

271-
subroutine s_assign_default_bc_type(bc_type)
271+
pure subroutine s_assign_default_bc_type(bc_type)
272272

273-
type(integer_field), dimension(1:num_dims, -1:1), intent(in) :: bc_type
273+
type(integer_field), dimension(1:num_dims, -1:1), intent(inout) :: bc_type
274274

275275
bc_type(1, -1)%sf(:, :, :) = bc_x%beg
276276
bc_type(1, 1)%sf(:, :, :) = bc_x%end

src/simulation/m_start_up.fpp

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -112,7 +112,7 @@ contains
112112

113113
!> Read data files. Dispatch subroutine that replaces procedure pointer.
114114
!! @param q_cons_vf Conservative variables
115-
subroutine s_read_data_files(q_cons_vf)
115+
impure subroutine s_read_data_files(q_cons_vf)
116116

117117
type(scalar_field), &
118118
dimension(sys_size), &
@@ -130,7 +130,7 @@ contains
130130
!> The purpose of this procedure is to first verify that an
131131
!! input file has been made available by the user. Provided
132132
!! that this is so, the input file is then read in.
133-
subroutine s_read_input_file
133+
impure subroutine s_read_input_file
134134

135135
! Relative path to the input file provided by the user
136136
character(LEN=name_len), parameter :: file_path = './simulation.inp'
@@ -228,7 +228,7 @@ contains
228228
!> The goal of this procedure is to verify that each of the
229229
!! user provided inputs is valid and that their combination
230230
!! constitutes a meaningful configuration for the simulation.
231-
subroutine s_check_input_file
231+
impure subroutine s_check_input_file
232232

233233
! Relative path to the current directory file in the case directory
234234
character(LEN=path_len) :: file_path
@@ -256,7 +256,7 @@ contains
256256
!! up the latter. This procedure also calculates the cell-
257257
!! width distributions from the cell-boundary locations.
258258
!! @param q_cons_vf Cell-averaged conservative variables
259-
subroutine s_read_serial_data_files(q_cons_vf)
259+
impure subroutine s_read_serial_data_files(q_cons_vf)
260260

261261
type(scalar_field), dimension(sys_size), intent(INOUT) :: q_cons_vf
262262

@@ -501,7 +501,7 @@ contains
501501
end subroutine s_read_serial_data_files
502502

503503
!! @param q_cons_vf Conservative variables
504-
subroutine s_read_parallel_data_files(q_cons_vf)
504+
impure subroutine s_read_parallel_data_files(q_cons_vf)
505505

506506
type(scalar_field), &
507507
dimension(sys_size), &
@@ -963,7 +963,7 @@ contains
963963
!! of the grid variables, which are constituted of the cell-
964964
!! boundary locations and cell-width distributions, based on
965965
!! the boundary conditions.
966-
subroutine s_populate_grid_variables_buffers
966+
impure subroutine s_populate_grid_variables_buffers
967967

968968
integer :: i !< Generic loop iterator
969969

@@ -1239,7 +1239,7 @@ contains
12391239

12401240
end subroutine s_initialize_internal_energy_equations
12411241

1242-
subroutine s_perform_time_step(t_step, time_avg, time_final, io_time_avg, io_time_final, proc_time, io_proc_time, file_exists, start, finish, nt)
1242+
impure subroutine s_perform_time_step(t_step, time_avg, time_final, io_time_avg, io_time_final, proc_time, io_proc_time, file_exists, start, finish, nt)
12431243
integer, intent(inout) :: t_step
12441244
real(wp), intent(inout) :: time_avg, time_final
12451245
real(wp), intent(inout) :: io_time_avg, io_time_final
@@ -1329,7 +1329,7 @@ contains
13291329

13301330
end subroutine s_perform_time_step
13311331

1332-
subroutine s_save_performance_metrics(t_step, time_avg, time_final, io_time_avg, io_time_final, proc_time, io_proc_time, file_exists, start, finish, nt)
1332+
impure subroutine s_save_performance_metrics(t_step, time_avg, time_final, io_time_avg, io_time_final, proc_time, io_proc_time, file_exists, start, finish, nt)
13331333

13341334
integer, intent(inout) :: t_step
13351335
real(wp), intent(inout) :: time_avg, time_final
@@ -1391,7 +1391,7 @@ contains
13911391

13921392
end subroutine s_save_performance_metrics
13931393

1394-
subroutine s_save_data(t_step, start, finish, io_time_avg, nt)
1394+
impure subroutine s_save_data(t_step, start, finish, io_time_avg, nt)
13951395
integer, intent(inout) :: t_step
13961396
real(wp), intent(inout) :: start, finish, io_time_avg
13971397
integer, intent(inout) :: nt
@@ -1460,7 +1460,7 @@ contains
14601460

14611461
end subroutine s_save_data
14621462

1463-
subroutine s_initialize_modules
1463+
impure subroutine s_initialize_modules
14641464

14651465
call s_initialize_global_parameters_module()
14661466
!Quadrature weights and nodes for polydisperse simulations
@@ -1558,7 +1558,7 @@ contains
15581558

15591559
end subroutine s_initialize_modules
15601560

1561-
subroutine s_initialize_mpi_domain
1561+
impure subroutine s_initialize_mpi_domain
15621562
integer :: ierr
15631563
#ifdef MFC_OpenACC
15641564
real(wp) :: starttime, endtime
@@ -1669,7 +1669,7 @@ contains
16691669
end if
16701670
end subroutine s_initialize_gpu_vars
16711671

1672-
subroutine s_finalize_modules
1672+
impure subroutine s_finalize_modules
16731673

16741674
call s_finalize_time_steppers_module()
16751675
if (hypoelasticity) call s_finalize_hypoelastic_module()

src/simulation/m_surface_tension.fpp

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ module m_surface_tension
4444

4545
contains
4646

47-
subroutine s_initialize_surface_tension_module
47+
impure subroutine s_initialize_surface_tension_module
4848

4949
@:ALLOCATE(c_divs(1:num_dims + 1))
5050

@@ -225,7 +225,7 @@ contains
225225

226226
end subroutine s_compute_capilary_source_flux
227227

228-
subroutine s_get_capilary(q_prim_vf, bc_type)
228+
impure subroutine s_get_capilary(q_prim_vf, bc_type)
229229

230230
type(scalar_field), dimension(sys_size), intent(in) :: q_prim_vf
231231
type(integer_field), dimension(1:num_dims, -1:1), intent(in) :: bc_type
@@ -376,7 +376,7 @@ contains
376376

377377
end subroutine s_reconstruct_cell_boundary_values_capillary
378378

379-
subroutine s_finalize_surface_tension_module
379+
impure subroutine s_finalize_surface_tension_module
380380

381381
do j = 1, num_dims
382382
@:DEALLOCATE(c_divs(j)%sf)

0 commit comments

Comments
 (0)