Skip to content

Commit df5a933

Browse files
committed
fix precision
1 parent 20c062f commit df5a933

File tree

9 files changed

+26
-26
lines changed

9 files changed

+26
-26
lines changed

src/post_process/m_data_input.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -516,10 +516,10 @@ subroutine s_read_parallel_data_files(t_step)
516516
! Initial displacement to skip at beginning of file
517517
disp = m_MOK*max(MOK, n_MOK)*max(MOK, p_MOK)*WP_MOK*(var_MOK - 1)
518518

519-
call MPI_FILE_SET_VIEW(ifile, disp, MPI_DOUBLE_PRECISION, MPI_IO_DATA%view(sys_size + 1), &
519+
call MPI_FILE_SET_VIEW(ifile, disp, mpi_p, MPI_IO_DATA%view(sys_size + 1), &
520520
'native', mpi_info_int, ierr)
521521
call MPI_FILE_READ(ifile, MPI_IO_DATA%var(sys_size + 1)%sf, data_size, &
522-
MPI_DOUBLE_PRECISION, status, ierr)
522+
mpi_p, status, ierr)
523523
end if
524524

525525
call s_mpi_barrier()

src/post_process/m_data_output.fpp

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1076,7 +1076,7 @@ contains
10761076
end if
10771077
10781078
call MPI_BCAST(tot_data, 1, MPI_integer, 0, MPI_COMM_WORLD, ierr)
1079-
call MPI_BCAST(time_real, 1, MPI_DOUBLE_PRECISION, 0, MPI_COMM_WORLD, ierr)
1079+
call MPI_BCAST(time_real, 1, mpi_p, 0, MPI_COMM_WORLD, ierr)
10801080
10811081
gsizes(1) = tot_data
10821082
gsizes(2) = 21
@@ -1086,7 +1086,7 @@ contains
10861086
start_idx_part(2) = 0
10871087
10881088
call MPI_TYPE_CREATE_SUBARRAY(2, gsizes, lsizes, start_idx_part, &
1089-
MPI_ORDER_FORTRAN, MPI_DOUBLE_PRECISION, view, ierr)
1089+
MPI_ORDER_FORTRAN, mpi_p, view, ierr)
10901090
call MPI_TYPE_COMMIT(view, ierr)
10911091
10921092
write (file_loc, '(A,I0,A)') 'lag_bubbles_', t_step, '.dat'
@@ -1099,13 +1099,13 @@ contains
10991099
mpi_info_int, ifile, ierr)
11001100
11011101
disp = 0._wp
1102-
call MPI_FILE_SET_VIEW(ifile, disp, MPI_DOUBLE_PRECISION, view, &
1102+
call MPI_FILE_SET_VIEW(ifile, disp, mpi_p, view, &
11031103
'native', mpi_info_null, ierr)
11041104
11051105
allocate (MPI_IO_DATA_lg_bubbles(tot_data, 1:21))
11061106
11071107
call MPI_FILE_READ_ALL(ifile, MPI_IO_DATA_lg_bubbles, 21*tot_data, &
1108-
MPI_DOUBLE_PRECISION, status, ierr)
1108+
mpi_p, status, ierr)
11091109
11101110
write (file_loc, '(A,I0,A)') 'lag_bubbles_post_process_', t_step, '.dat'
11111111
file_loc = trim(case_dir)//'/lag_bubbles_post_process/'//trim(file_loc)

src/post_process/m_start_up.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -699,7 +699,7 @@ subroutine s_save_data(t_step, varname, pres, c, H)
699699
varname(:) = ' '
700700
end if
701701
end if
702-
702+
703703
! Adding the lagrangian subgrid variables to the formatted database file ---------
704704
if (bubbles_lagrange) then
705705
!! Void fraction field

src/pre_process/m_assign_variables.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -493,7 +493,7 @@ contains
493493
+ (1._wp - eta)*orig_prim_vf(i + stress_idx%beg - 1))
494494
end do
495495
end if
496-
496+
497497
! Elastic Shear Stress
498498
if (hyperelasticity) then
499499

src/simulation/m_bubbles_EE.fpp

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -427,7 +427,7 @@ contains
427427
real(wp), intent(out) :: h
428428

429429
real(wp) :: h0, h1 !< Time step size
430-
real(wp) :: d0, d1, d2 !< norms
430+
real(wp) :: d_0, d1, d2 !< norms
431431
real(wp), dimension(2) :: myR_tmp, myV_tmp, myA_tmp !< Bubble radius, radial velocity, and radial acceleration
432432

433433
! Determine the starting time step
@@ -438,13 +438,13 @@ contains
438438
fpb, fpbdot, alf, fntait, fBtait, &
439439
f_bub_adv_src, f_divu)
440440

441-
! Compute d0 = ||y0|| and d1 = ||f(x0,y0)||
442-
d0 = sqrt((myR_tmp(1)**2._wp + myV_tmp(1)**2._wp)/2._wp)
443-
d1 = sqrt((myV_tmp(1)**2._wp + myA_tmp(1)**2._wp)/2._wp)
444-
if (d0 < 1e-5_wp .or. d1 < 1e-5_wp) then
441+
! Compute d_0 = ||y0|| and d1 = ||f(x0,y0)||
442+
d_0 = sqrt((myR_tmp(1)**2._wp + myV_tmp(1)**2._wp)/2._wp)
443+
d_1 = sqrt((myV_tmp(1)**2._wp + myA_tmp(1)**2._wp)/2._wp)
444+
if (d_0 < 1e-5_wp .or. d1 < 1e-5_wp) then
445445
h0 = 1e-6_wp
446446
else
447-
h0 = 1e-2_wp*(d0/d1)
447+
h0 = 1e-2_wp*(d_0/d1)
448448
end if
449449

450450
! Evaluate f(x0+h0,y0+h0*f(x0,y0))

src/simulation/m_bubbles_EL.fpp

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -439,8 +439,8 @@ contains
439439
end if
440440

441441
call MPI_BCAST(tot_data, 1, MPI_INTEGER, 0, MPI_COMM_WORLD, ierr)
442-
call MPI_BCAST(mytime, 1, MPI_DOUBLE_PRECISION, 0, MPI_COMM_WORLD, ierr)
443-
call MPI_BCAST(dt, 1, MPI_DOUBLE_PRECISION, 0, MPI_COMM_WORLD, ierr)
442+
call MPI_BCAST(mytime, 1, mpi_p, 0, MPI_COMM_WORLD, ierr)
443+
call MPI_BCAST(dt, 1, mpi_p, 0, MPI_COMM_WORLD, ierr)
444444

445445
gsizes(1) = tot_data
446446
gsizes(2) = 21
@@ -450,7 +450,7 @@ contains
450450
start_idx_part(2) = 0
451451

452452
call MPI_type_CREATE_SUBARRAY(2, gsizes, lsizes, start_idx_part, &
453-
MPI_ORDER_FORTRAN, MPI_doUBLE_PRECISION, view, ierr)
453+
MPI_ORDER_FORTRAN, mpi_p, view, ierr)
454454
call MPI_type_COMMIT(view, ierr)
455455

456456
! Open the file to write all flow variables
@@ -462,11 +462,11 @@ contains
462462
call MPI_FILE_open(MPI_COMM_WORLD, file_loc, MPI_MODE_RDONLY, &
463463
mpi_info_int, ifile, ierr)
464464
disp = 0._wp
465-
call MPI_FILE_SET_VIEW(ifile, disp, MPI_doUBLE_PRECISION, view, &
465+
call MPI_FILE_SET_VIEW(ifile, disp, mpi_p, view, &
466466
'native', mpi_info_null, ierr)
467467
allocate (MPI_IO_DATA_lag_bubbles(tot_data, 1:21))
468468
call MPI_FILE_read_ALL(ifile, MPI_IO_DATA_lag_bubbles, 21*tot_data, &
469-
MPI_doUBLE_PRECISION, status, ierr)
469+
mpi_p, status, ierr)
470470
do i = 1, tot_data
471471
id = int(MPI_IO_DATA_lag_bubbles(i, 1))
472472
inputvals(1:20) = MPI_IO_DATA_lag_bubbles(i, 2:21)
@@ -1777,7 +1777,7 @@ contains
17771777
end if
17781778

17791779
call MPI_type_CREATE_SUBARRAY(2, gsizes, lsizes, start_idx_part, &
1780-
MPI_ORDER_FORTRAN, MPI_doUBLE_PRECISION, view, ierr)
1780+
MPI_ORDER_FORTRAN, mpi_p, view, ierr)
17811781
call MPI_type_COMMIT(view, ierr)
17821782

17831783
allocate (MPI_IO_DATA_lag_bubbles(1:max(1, bub_id), 1:21))
@@ -1795,7 +1795,7 @@ contains
17951795

17961796
disp = 0._wp
17971797

1798-
call MPI_FILE_SET_VIEW(ifile, disp, MPI_doUBLE_PRECISION, view, &
1798+
call MPI_FILE_SET_VIEW(ifile, disp, mpi_p, view, &
17991799
'native', mpi_info_null, ierr)
18001800

18011801
! Cycle through list
@@ -1834,7 +1834,7 @@ contains
18341834
end if
18351835

18361836
call MPI_FILE_write_ALL(ifile, MPI_IO_DATA_lag_bubbles, 21*max(1, bub_id), &
1837-
MPI_doUBLE_PRECISION, status, ierr)
1837+
mpi_p, status, ierr)
18381838

18391839
call MPI_FILE_CLOSE(ifile, ierr)
18401840

src/simulation/m_data_output.fpp

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -972,10 +972,10 @@ contains
972972
! Initial displacement to skip at beginning of file
973973
disp = m_MOK*max(MOK, n_MOK)*max(MOK, p_MOK)*WP_MOK*(var_MOK - 1)
974974

975-
call MPI_FILE_SET_VIEW(ifile, disp, MPI_DOUBLE_PRECISION, MPI_IO_DATA%view(sys_size + 1), &
975+
call MPI_FILE_SET_VIEW(ifile, disp, mpi_p, MPI_IO_DATA%view(sys_size + 1), &
976976
'native', mpi_info_int, ierr)
977977
call MPI_FILE_WRITE_ALL(ifile, MPI_IO_DATA%var(sys_size + 1)%sf, data_size, &
978-
MPI_DOUBLE_PRECISION, status, ierr)
978+
mpi_p, status, ierr)
979979
end if
980980

981981
call MPI_FILE_CLOSE(ifile, ierr)

src/simulation/m_riemann_solvers.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1717,7 +1717,7 @@ contains
17171717
end do
17181718
end do
17191719
!$acc end parallel loop
1720-
1720+
17211721
elseif (model_eqns == 2 .and. bubbles_euler) then
17221722
!$acc parallel loop collapse(3) gang vector default(present) private(R0_L, R0_R, V0_L, V0_R, P0_L, P0_R, pbw_L, pbw_R, vel_L, vel_R, &
17231723
!$acc rho_avg, alpha_L, alpha_R, h_avg, gamma_avg, s_L, s_R, s_S, nbub_L, nbub_R, ptilde_L, ptilde_R, vel_avg_rms, Re_L, Re_R, pcorr, zcoef, vel_L_tmp, vel_R_tmp)

src/simulation/m_time_steppers.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1232,7 +1232,7 @@ contains
12321232
@:DEALLOCATE(q_prim_vf(i)%sf)
12331233
end do
12341234
end if
1235-
1235+
12361236
if (hyperelasticity) then
12371237
do i = xibeg, xiend + 1
12381238
@:DEALLOCATE(q_prim_vf(i)%sf)

0 commit comments

Comments
 (0)