Skip to content

Commit 5693224

Browse files
committed
fix some missing ones
1 parent b0fee45 commit 5693224

File tree

6 files changed

+21
-21
lines changed

6 files changed

+21
-21
lines changed

src/common/m_derived_types.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -188,7 +188,7 @@ module m_derived_types
188188
!! Identity (id) of the patch with which current patch is to get smoothed
189189

190190
real(wp) :: smooth_coeff !<
191-
!! Smoothing coefficient (coeff) adminstrating the size of the stencil of
191+
!! Smoothing coefficient (coeff) for the size of the stencil of
192192
!! cells across which boundaries of the current patch will be smeared out
193193

194194
real(wp), dimension(num_fluids_max) :: alpha_rho

src/common/m_helper.fpp

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -229,16 +229,16 @@ contains
229229
real(wp), intent(in) :: omega, peclet
230230
real(wp), intent(out) :: Re_trans, Im_trans
231231

232-
complex :: trans, c1, c2, c3
233-
complex :: imag = (0._wp, 1._wp)
232+
complex(wp) :: trans, c1, c2, c3
233+
complex(wp) :: imag = (0._wp, 1._wp)
234234
real(wp) :: f_transcoeff
235235

236236
c1 = imag*omega*peclet
237237
c2 = CSQRT(c1)
238238
c3 = (CEXP(c2) - CEXP(-c2))/(CEXP(c2) + CEXP(-c2)) ! TANH(c2)
239239
trans = ((c2/c3 - 1._wp)**(-1) - 3._wp/c1)**(-1) ! transfer function
240240

241-
Re_trans = dble(trans)
241+
Re_trans = trans
242242
Im_trans = aimag(trans)
243243

244244
end subroutine s_transcoeff
@@ -279,7 +279,7 @@ contains
279279
! phi = ln( R0 ) & return R0
280280
do ir = 1, nb
281281
phi(ir) = log(R0mn) &
282-
+ dble(ir - 1)*log(R0mx/R0mn)/dble(nb - 1)
282+
+ (ir - 1._wp)*log(R0mx/R0mn)/(nb - 1._wp)
283283
R0(ir) = exp(phi(ir))
284284
end do
285285
dphi = phi(2) - phi(1)

src/common/m_precision_select.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,7 @@ module m_precision_select
1919
integer, parameter :: sp = single_precision
2020
integer, parameter :: dp = double_precision
2121

22-
! Set the working precision (wp) to single or double precision
22+
! Set the working precision (wp) to single or double
2323
#ifdef MFC_SINGLE_PRECISION
2424
integer, parameter :: wp = single_precision ! Change to single_precision if needed
2525
#else

src/simulation/m_fftw.fpp

Lines changed: 13 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -51,9 +51,9 @@ module m_fftw
5151
#if defined(MFC_OpenACC)
5252
!$acc declare create(real_size, cmplx_size, x_size, batch_size, Nfq)
5353

54-
real(kind(0d0)), allocatable, target :: data_real_gpu(:)
55-
complex(kind(0d0)), allocatable, target :: data_cmplx_gpu(:)
56-
complex(kind(0d0)), allocatable, target :: data_fltr_cmplx_gpu(:)
54+
real(dp), allocatable, target :: data_real_gpu(:)
55+
complex(dp), allocatable, target :: data_cmplx_gpu(:)
56+
complex(dp), allocatable, target :: data_fltr_cmplx_gpu(:)
5757
!$acc declare create(data_real_gpu, data_cmplx_gpu, data_fltr_cmplx_gpu)
5858

5959
#if defined(__PGI)
@@ -146,7 +146,7 @@ contains
146146
do k = 1, sys_size
147147
do j = 0, m
148148
do l = 1, cmplx_size
149-
data_fltr_cmplx_gpu(l + j*cmplx_size + (k - 1)*cmplx_size*x_size) = (0d0, 0d0)
149+
data_fltr_cmplx_gpu(l + j*cmplx_size + (k - 1)*cmplx_size*x_size) = (0_dp, 0_dp)
150150
end do
151151
end do
152152
end do
@@ -198,7 +198,7 @@ contains
198198
do k = 1, sys_size
199199
do j = 0, m
200200
do l = 0, p
201-
data_real_gpu(l + j*real_size + 1 + (k - 1)*real_size*x_size) = data_real_gpu(l + j*real_size + 1 + (k - 1)*real_size*x_size)/real(real_size, kind(0d0))
201+
data_real_gpu(l + j*real_size + 1 + (k - 1)*real_size*x_size) = data_real_gpu(l + j*real_size + 1 + (k - 1)*real_size*x_size)/real(real_size, dp)
202202
q_cons_vf(k)%sf(j, 0, l) = data_real_gpu(l + j*real_size + 1 + (k - 1)*real_size*x_size)
203203
end do
204204
end do
@@ -210,7 +210,7 @@ contains
210210
do k = 1, sys_size
211211
do j = 0, m
212212
do l = 1, cmplx_size
213-
data_fltr_cmplx_gpu(l + j*cmplx_size + (k - 1)*cmplx_size*x_size) = (0d0, 0d0)
213+
data_fltr_cmplx_gpu(l + j*cmplx_size + (k - 1)*cmplx_size*x_size) = (0_dp, 0_dp)
214214
end do
215215
end do
216216
end do
@@ -233,7 +233,7 @@ contains
233233
#endif
234234
!$acc end host_data
235235

236-
Nfq = min(floor(2d0*real(i, kind(0d0))*pi), cmplx_size)
236+
Nfq = min(floor(2_dp*real(i, dp)*pi), cmplx_size)
237237
!$acc update device(Nfq)
238238

239239
!$acc parallel loop collapse(3) gang vector default(present)
@@ -258,7 +258,7 @@ contains
258258
do k = 1, sys_size
259259
do j = 0, m
260260
do l = 0, p
261-
data_real_gpu(l + j*real_size + 1 + (k - 1)*real_size*x_size) = data_real_gpu(l + j*real_size + 1 + (k - 1)*real_size*x_size)/real(real_size, kind(0d0))
261+
data_real_gpu(l + j*real_size + 1 + (k - 1)*real_size*x_size) = data_real_gpu(l + j*real_size + 1 + (k - 1)*real_size*x_size)/real(real_size, dp)
262262
q_cons_vf(k)%sf(j, i, l) = data_real_gpu(l + j*real_size + 1 + (k - 1)*real_size*x_size)
263263
end do
264264
end do
@@ -270,27 +270,27 @@ contains
270270
Nfq = 3
271271
do j = 0, m
272272
do k = 1, sys_size
273-
data_fltr_cmplx(:) = (0d0, 0d0)
273+
data_fltr_cmplx(:) = (0_dp, 0_dp)
274274
data_real(1:p + 1) = q_cons_vf(k)%sf(j, 0, 0:p)
275275
call fftw_execute_dft_r2c(fwd_plan, data_real, data_cmplx)
276276
data_fltr_cmplx(1:Nfq) = data_cmplx(1:Nfq)
277277
call fftw_execute_dft_c2r(bwd_plan, data_fltr_cmplx, data_real)
278-
data_real(:) = data_real(:)/real(real_size, kind(0d0))
278+
data_real(:) = data_real(:)/real(real_size, dp)
279279
q_cons_vf(k)%sf(j, 0, 0:p) = data_real(1:p + 1)
280280
end do
281281
end do
282282

283283
! Apply Fourier filter to additional rings
284284
do i = 1, fourier_rings
285-
Nfq = min(floor(2d0*real(i, kind(0d0))*pi), cmplx_size)
285+
Nfq = min(floor(2_dp*real(i, dp)*pi), cmplx_size)
286286
do j = 0, m
287287
do k = 1, sys_size
288-
data_fltr_cmplx(:) = (0d0, 0d0)
288+
data_fltr_cmplx(:) = (0_dp, 0_dp)
289289
data_real(1:p + 1) = q_cons_vf(k)%sf(j, i, 0:p)
290290
call fftw_execute_dft_r2c(fwd_plan, data_real, data_cmplx)
291291
data_fltr_cmplx(1:Nfq) = data_cmplx(1:Nfq)
292292
call fftw_execute_dft_c2r(bwd_plan, data_fltr_cmplx, data_real)
293-
data_real(:) = data_real(:)/real(real_size, kind(0d0))
293+
data_real(:) = data_real(:)/real(real_size, dp)
294294
q_cons_vf(k)%sf(j, i, 0:p) = data_real(1:p + 1)
295295
end do
296296
end do

src/simulation/m_rhs.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -899,7 +899,7 @@ contains
899899

900900
if (chemistry) then
901901
!$acc kernels
902-
rhs_vf(T_idx)%sf(:, :, :) = 0d0
902+
rhs_vf(T_idx)%sf(:, :, :) = 0.0_wp
903903
!$acc end kernels
904904

905905
if (chem_params%reactions) then

src/syscheck/syscheck.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -53,7 +53,7 @@ program syscheck
5353

5454
@:ACC(integer(acc_device_kind) :: devtype)
5555
@:ACC(integer :: i, num_devices)
56-
@:ACC(real(kind(0d0)), allocatable, dimension(:) :: arr)
56+
@:ACC(real(8), allocatable, dimension(:) :: arr)
5757
@:ACC(integer, parameter :: N = 100)
5858

5959
@:MPIC(call mpi_init(ierr))

0 commit comments

Comments
 (0)