Skip to content

Commit 55d982d

Browse files
author
Xuzheng Tian
committed
Removed All Unnecessary Variables
1 parent 40164cf commit 55d982d

26 files changed

+104
-109
lines changed

src/common/m_boundary_common.fpp

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -77,7 +77,7 @@ contains
7777
real(wp), dimension(idwbuff(1)%beg:, idwbuff(2)%beg:, idwbuff(3)%beg:, 1:, 1:), intent(inout) :: pb, mv
7878
type(integer_field), dimension(1:num_dims, -1:1), intent(in) :: bc_type
7979

80-
integer :: bc_loc, bc_dir
80+
8181
integer :: k, l
8282

8383
! Population of Buffers in x-direction
@@ -249,7 +249,7 @@ contains
249249
integer, intent(in) :: bc_dir, bc_loc
250250
integer, intent(in) :: k, l
251251

252-
integer :: j, q, i
252+
integer :: j, i
253253

254254
if (qbmm .and. .not. polytropic) then
255255
call s_qbmm_extrapolation(pb, mv, bc_dir, bc_loc, k, l)
@@ -789,7 +789,7 @@ contains
789789
integer, intent(in) :: bc_dir, bc_loc
790790
integer, intent(in) :: k, l
791791

792-
integer :: j, q, i
792+
integer :: j, i
793793

794794
if (qbmm .and. .not. polytropic) then
795795
call s_qbmm_extrapolation(pb, mv, bc_dir, bc_loc, k, l)
@@ -888,7 +888,7 @@ contains
888888
integer, intent(in) :: bc_dir, bc_loc
889889
integer, intent(in) :: k, l
890890

891-
integer :: j, q, i
891+
integer :: j, i
892892

893893
if (qbmm .and. .not. polytropic) then
894894
call s_qbmm_extrapolation(pb, mv, bc_dir, bc_loc, k, l)
@@ -1023,7 +1023,7 @@ contains
10231023
integer, intent(in) :: bc_dir, bc_loc
10241024
integer, intent(in) :: k, l
10251025

1026-
integer :: j, i, q
1026+
integer :: j, i
10271027

10281028
#ifdef MFC_PRE_PROCESS
10291029
call s_ghost_cell_extrapolation(q_prim_vf, pb, mv, 1, -1, k, l)
@@ -1162,7 +1162,7 @@ contains
11621162
type(scalar_field), dimension(num_dims + 1), intent(inout) :: c_divs
11631163
type(integer_field), dimension(1:num_dims, -1:1), intent(in) :: bc_type
11641164

1165-
integer :: i, j, k, l
1165+
integer :: k, l
11661166

11671167
!< x-direction
11681168
if (bcxb >= 0) then
@@ -1290,7 +1290,7 @@ contains
12901290
integer, intent(in) :: bc_dir, bc_loc
12911291
integer, intent(in) :: k, l
12921292

1293-
integer :: j, i, q
1293+
integer :: j, i
12941294

12951295
if (bc_dir == 1) then !< x-direction
12961296
if (bc_loc == -1) then !bc_x%beg
@@ -1348,7 +1348,7 @@ contains
13481348
integer, intent(in) :: bc_dir, bc_loc
13491349
integer, intent(in) :: k, l
13501350

1351-
integer :: j, i, q
1351+
integer :: j, i
13521352

13531353
if (bc_dir == 1) then !< x-direction
13541354
if (bc_loc == -1) then !bc_x%beg
@@ -1430,7 +1430,7 @@ contains
14301430
integer, intent(in) :: bc_dir, bc_loc
14311431
integer, intent(in) :: k, l
14321432

1433-
integer :: j, i, q
1433+
integer :: j, i
14341434

14351435
if (bc_dir == 1) then !< x-direction
14361436
if (bc_loc == -1) then !bc_x%beg
@@ -1485,7 +1485,7 @@ contains
14851485
#ifdef MFC_MPI
14861486
integer :: dir, loc
14871487
integer, dimension(3) :: sf_start_idx, sf_extents_loc
1488-
integer :: ifile, ierr, data_size
1488+
integer :: ierr
14891489

14901490
do dir = 1, num_dims
14911491
do loc = -1, 1, 2

src/common/m_chemistry.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ contains
2828
type(int_bounds_info), dimension(1:3), intent(in) :: bounds
2929

3030
integer :: x, y, z, eqn
31-
real(wp) :: energy, mean_molecular_weight
31+
real(wp) :: energy
3232
real(wp), dimension(num_species) :: Ys
3333

3434
do z = bounds(3)%beg, bounds(3)%end

src/common/m_eigen_solver.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -225,7 +225,7 @@ subroutine corth(nm, nl, low, igh, ar, ai, ortr, orti)
225225
real(wp), dimension(igh), intent(out) :: ortr, orti
226226

227227
integer :: i, j, ml, ii, jj, la, mp, kp1, mll
228-
real(wp) :: f, g, h, fi, fr, scale, c
228+
real(wp) :: f, g, h, fi, fr, scale
229229

230230
mll = 6
231231

@@ -353,7 +353,7 @@ subroutine comqr2(nm, nl, low, igh, ortr, orti, hr, hi, wr, wi, zr, zi, ierr)
353353

354354
integer :: i, j, k, l, ml, en, ii, jj, ll, nn, ip1, itn, its, lp1, enm1, iend
355355
real(wp) :: si, sr, ti, tr, xi, xr, xxi, xxr, yi, yr, zzi, zzr, &
356-
norm, tst1, tst2, c, d
356+
norm, tst1, tst2, c
357357
!
358358
ierr = 0
359359
! initialize eigenvector matrix

src/common/m_helper.fpp

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -395,7 +395,6 @@ contains
395395
396396
integer :: i
397397
398-
real(wp), dimension(1:4) :: tmp
399398
400399
do i = 1, 3
401400
call s_transform_vec(triangle%v(i, :), matrix)

src/common/m_mpi_common.fpp

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -160,7 +160,7 @@ contains
160160
#ifdef MFC_MPI
161161
162162
! Generic loop iterator
163-
integer :: i, j, q, k, l
163+
integer :: i, j
164164
165165
!Altered system size for the lagrangian subgrid bubble model
166166
integer :: alt_sys
@@ -309,7 +309,7 @@ contains
309309
integer, intent(in) :: root ! Rank of the root process
310310
real(wp), allocatable, intent(out) :: gathered_vector(:) ! Gathered vector on the root process
311311
312-
integer :: i, offset, ierr
312+
integer :: i, ierr
313313
integer, allocatable :: recounts(:), displs(:)
314314
315315
#ifdef MFC_MPI
@@ -1076,7 +1076,7 @@ contains
10761076
type(scalar_field), dimension(num_dims + 1), intent(inout) :: c_divs_vf
10771077
integer, intent(in) :: mpi_dir, pbc_loc
10781078
1079-
integer :: i, j, k, l, r, q !< Generic loop iterators
1079+
integer :: i, j, k, l, r !< Generic loop iterators
10801080
10811081
integer :: buffer_counts(1:3), buffer_count
10821082

src/common/m_variables_conversion.fpp

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -846,15 +846,15 @@ contains
846846

847847
real(wp) :: rhoYks(1:num_species)
848848

849-
real(wp) :: vftmp, nR3, nbub_sc, R3tmp
849+
real(wp) :: vftmp, nbub_sc
850850

851851
real(wp) :: G_K
852852

853-
real(wp) :: pres, Yksum
853+
real(wp) :: pres
854854

855-
integer :: i, j, k, l, q !< Generic loop iterators
855+
integer :: i, j, k, l !< Generic loop iterators
856856

857-
real(wp) :: ntmp, T
857+
real(wp) :: T
858858
real(wp) :: pres_mag
859859

860860
real(wp) :: Ga ! Lorentz factor (gamma in relativity)
@@ -885,7 +885,7 @@ contains
885885

886886
!$acc parallel loop collapse(3) gang vector default(present) &
887887
!$acc private(alpha_K, alpha_rho_K, Re_K, nRtmp, rho_K, gamma_K, &
888-
!$acc pi_inf_K, qv_K, dyn_pres_K, R3tmp, rhoYks, B)
888+
!$acc pi_inf_K, qv_K, dyn_pres_K, rhoYks, B)
889889
do l = ibounds(3)%beg, ibounds(3)%end
890890
do k = ibounds(2)%beg, ibounds(2)%end
891891
do j = ibounds(1)%beg, ibounds(1)%end
@@ -1181,13 +1181,13 @@ contains
11811181
real(wp) :: pi_inf
11821182
real(wp) :: qv
11831183
real(wp) :: dyn_pres
1184-
real(wp) :: nbub, R3, vftmp, R3tmp
1184+
real(wp) :: nbub, R3tmp
11851185
real(wp), dimension(nb) :: Rtmp
11861186
real(wp) :: G
11871187
real(wp), dimension(2) :: Re_K
11881188

1189-
integer :: i, j, k, l, q !< Generic loop iterators
1190-
integer :: spec
1189+
integer :: i, j, k, l !< Generic loop iterators
1190+
11911191

11921192
real(wp), dimension(num_species) :: Ys
11931193
real(wp) :: e_mix, mix_mol_weight, T
@@ -1567,7 +1567,7 @@ contains
15671567

15681568
subroutine s_finalize_variables_conversion_module()
15691569

1570-
integer :: i !< Generic loop iterators
1570+
15711571

15721572
! Deallocating the density, the specific heat ratio function and the
15731573
! liquid stiffness function
@@ -1673,8 +1673,8 @@ contains
16731673
integer, intent(in) :: norm
16741674

16751675
real(wp) :: B2, term, disc
1676-
real(wp) :: term2
16771676

1677+
16781678
B2 = sum(B**2)
16791679

16801680
if (.not. relativity) then
@@ -1698,4 +1698,4 @@ contains
16981698
end subroutine s_compute_fast_magnetosonic_speed
16991699
#endif
17001700

1701-
end module m_variables_conversion
1701+
end module m_variables_conversion

src/post_process/m_data_input.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -278,7 +278,7 @@ subroutine s_read_parallel_data_files(t_step)
278278

279279
integer :: ifile, ierr, data_size
280280
integer, dimension(MPI_STATUS_SIZE) :: status
281-
real(wp) :: start, finish
281+
282282
integer(KIND=MPI_OFFSET_KIND) :: disp
283283
integer(KIND=MPI_OFFSET_KIND) :: m_MOK, n_MOK, p_MOK
284284
integer(KIND=MPI_OFFSET_KIND) :: WP_MOK, var_MOK, str_MOK

src/post_process/m_data_output.fpp

Lines changed: 13 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -859,8 +859,8 @@ contains
859859
860860
! Generic loop iterator
861861
integer :: i, j, k
862-
real(wp) :: start, finish
863862
863+
864864
! Silo-HDF5 Database Format
865865
866866
if (format == 1) then
@@ -1092,23 +1092,23 @@ contains
10921092
subroutine s_write_lag_bubbles_results(t_step)
10931093
10941094
integer, intent(in) :: t_step
1095-
character(len=len_trim(case_dir) + 2*name_len) :: t_step_dir
1095+
10961096
character(len=len_trim(case_dir) + 3*name_len) :: file_loc
1097-
logical :: dir_check
1098-
integer :: id, nlg_bubs
1097+
1098+
integer :: id
10991099
11001100
#ifdef MFC_MPI
11011101
real(wp), dimension(20) :: inputvals
1102-
real(wp) :: id_real, time_real
1102+
real(wp) :: time_real
11031103
integer, dimension(MPI_STATUS_SIZE) :: status
11041104
integer(KIND=MPI_OFFSET_KIND) :: disp
11051105
integer :: view
11061106
1107-
integer, dimension(3) :: cell
1108-
logical :: indomain, lg_bub_file, lg_bub_data, file_exist
1107+
1108+
logical :: lg_bub_file, file_exist
11091109
11101110
integer, dimension(2) :: gsizes, lsizes, start_idx_part
1111-
integer :: ifile, ireq, ierr, data_size, tot_data
1111+
integer :: ifile, ierr, tot_data
11121112
integer :: i
11131113
11141114
write (file_loc, '(A,I0,A)') 'lag_bubbles_mpi_io_', t_step, '.dat'
@@ -1196,12 +1196,11 @@ contains
11961196
subroutine s_write_intf_data_file(q_prim_vf)
11971197
11981198
type(scalar_field), dimension(sys_size), intent(IN) :: q_prim_vf
1199-
integer :: i, j, k, l, w, cent !< Generic loop iterators
1200-
integer :: ierr, counter, root !< number of data points extracted to fit shape to SH perturbations
1201-
real(wp), dimension(num_fluids) :: alpha, vol_fluid, xcom, ycom, zcom
1199+
integer :: i, j, k, l, cent !< Generic loop iterators
1200+
integer :: counter, root !< number of data points extracted to fit shape to SH perturbations
12021201
real(wp), parameter :: pi = 4._wp*tan(1._wp)
12031202
real(wp), allocatable :: x_td(:), y_td(:), x_d1(:), y_d1(:), y_d(:), x_d(:)
1204-
real(wp) :: axp, axm, ayp, aym, azm, azp, tgp, euc_d, thres, maxalph_loc, maxalph_glb
1203+
real(wp) :: axp, axm, ayp, aym, tgp, euc_d, thres, maxalph_loc, maxalph_glb
12051204
12061205
allocate (x_d1(m*n))
12071206
allocate (y_d1(m*n))
@@ -1290,10 +1289,10 @@ contains
12901289
real(wp) :: Elk, Egk, Elp, Egint, Vb, Vl, pres_av, Et
12911290
real(wp) :: rho, pres, dV, tmp, gamma, pi_inf, MaxMa, MaxMa_glb, maxvel, c, Ma, H
12921291
real(wp), dimension(num_vels) :: vel
1293-
real(wp), dimension(num_fluids) :: gammas, pi_infs, adv
1292+
real(wp), dimension(num_fluids) :: adv
12941293
integer :: i, j, k, l, s !looping indices
1295-
integer :: ierr, counter, root !< number of data points extracted to fit shape to SH perturbations
12961294
1295+
12971296
Egk = 0_wp
12981297
Elp = 0_wp
12991298
Egint = 0_wp

src/post_process/m_derived_variables.fpp

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -329,9 +329,9 @@ contains
329329
real(wp), dimension(ndim), intent(inout) :: b
330330
real(wp), dimension(ndim), intent(out) :: sol
331331

332-
integer, dimension(ndim) :: ipiv
333332

334-
integer :: nrhs, lda, ldb, info
333+
334+
335335
!EXTERNAL DGESV
336336

337337
integer :: i, j, k
@@ -491,7 +491,7 @@ contains
491491
real(wp), &
492492
dimension(1:3, 1:3) :: q_jacobian_sf, S, S2, O, O2
493493

494-
real(wp) :: trS, trS2, trO2, Q, IIS
494+
real(wp) :: trS, Q, IIS
495495
integer :: j, k, l, r, jj, kk !< Generic loop iterators
496496

497497
do l = -offset_z%beg, p + offset_z%end
@@ -585,8 +585,8 @@ contains
585585
!! The first position in the variable contains the maximum value and
586586
!! the second contains the rank of the processor on which it occurred.
587587
588-
real(wp) :: alpha_unadv !< Unadvected volume fraction
589588
589+
590590
integer :: i, j, k, l !< Generic loop iterators
591591
592592
! Computing Gradient Magnitude of Density

src/pre_process/m_assign_variables.fpp

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -111,15 +111,15 @@ contains
111111
type(scalar_field), dimension(1:sys_size), intent(inout) :: q_prim_vf
112112
integer, dimension(0:m, 0:n, 0:p), intent(inout) :: patch_id_fp
113113
114-
real(wp) :: rho !< density
115-
real(wp), dimension(int(E_idx - mom_idx%beg)) :: vel !< velocity
116-
real(wp) :: pres !< pressure
117-
real(wp) :: gamma !< specific heat ratio function
118-
real(wp) :: x_centroid, y_centroid
119-
real(wp) :: epsilon, beta
114+
115+
116+
117+
118+
119+
120120
real(wp) :: Ys(1:num_species)
121-
real(wp) :: mean_molecular_weight
122121
122+
123123
integer :: smooth_patch_id
124124
integer :: i !< generic loop operator
125125
@@ -308,14 +308,14 @@ contains
308308
real(wp) :: rcoord, theta, phi, xi_sph
309309
real(wp), dimension(3) :: xi_cart
310310
311-
real(wp), dimension(int(E_idx - mom_idx%beg)) :: vel !< velocity
312-
real(wp) :: pres !< pressure
313-
real(wp) :: x_centroid, y_centroid
314-
real(wp) :: epsilon, beta
311+
312+
313+
314+
315315
316316
real(wp) :: Ys(1:num_species)
317-
real(wp) :: mean_molecular_weight
318317
318+
319319
real(wp), dimension(sys_size) :: orig_prim_vf !<
320320
!! Vector to hold original values of cell for smoothing purposes
321321

0 commit comments

Comments
 (0)