Skip to content

Commit ca56a8f

Browse files
committed
clean merge
1 parent ac513a3 commit ca56a8f

File tree

11 files changed

+259
-261
lines changed

11 files changed

+259
-261
lines changed

src/common/m_helper_basic.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@ module m_helper_basic
1010

1111
implicit none
1212

13-
private;
13+
private;
1414
public :: f_approx_equal, &
1515
f_approx_in_array, &
1616
f_is_default, &

src/common/m_mpi_common.fpp

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1641,8 +1641,8 @@ contains
16411641
end if
16421642
16431643
@:ALLOCATE(neighbor_ranks(nidx(1)%beg:nidx(1)%end, &
1644-
nidx(2)%beg:nidx(2)%end, &
1645-
nidx(3)%beg:nidx(3)%end))
1644+
nidx(2)%beg:nidx(2)%end, &
1645+
nidx(3)%beg:nidx(3)%end))
16461646
16471647
do k = nidx(3)%beg, nidx(3)%end
16481648
do j = nidx(2)%beg, nidx(2)%end
@@ -1652,7 +1652,7 @@ contains
16521652
if (num_dims > 1) neighbor_coords(2) = proc_coords(2) + j
16531653
if (num_dims > 2) neighbor_coords(3) = proc_coords(3) + k
16541654
call MPI_CART_RANK(MPI_COMM_CART, neighbor_coords, &
1655-
neighbor_ranks(i, j, k), ierr)
1655+
neighbor_ranks(i, j, k), ierr)
16561656
end if
16571657
end do
16581658
end do

src/post_process/m_data_output.fpp

Lines changed: 88 additions & 89 deletions
Large diffs are not rendered by default.

src/post_process/m_global_parameters.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -180,7 +180,7 @@ module m_global_parameters
180180

181181
type(int_bounds_info), dimension(3) :: nidx
182182

183-
integer, allocatable, dimension(:,:,:) :: neighbor_ranks
183+
integer, allocatable, dimension(:, :, :) :: neighbor_ranks
184184
!! Neighbor ranks for lagrangian particle communication
185185

186186
integer, allocatable, dimension(:) :: start_idx !<

src/pre_process/m_global_parameters.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -195,7 +195,7 @@ module m_global_parameters
195195
196196
type(int_bounds_info), dimension(3) :: nidx
197197
198-
integer, allocatable, dimension(:,:,:) :: neighbor_ranks
198+
integer, allocatable, dimension(:, :, :) :: neighbor_ranks
199199
!! Neighbor ranks for lagrangian particle communication
200200
201201
integer, allocatable, dimension(:) :: start_idx !<

src/simulation/m_bubbles.fpp

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -566,15 +566,15 @@ contains
566566
if (lag_params%vel_model == 1) then
567567
do l = 1, num_dims
568568
vTemp = f_interpolate_velocity(fR, cell, l, q_prim_vf)
569-
fPos(l) = fPos(l) + h * vTemp
569+
fPos(l) = fPos(l) + h*vTemp
570570
fVel(l) = vTemp
571571
end do
572572
elseif (lag_params%vel_model == 2) then
573573
do l = 1, num_dims
574574
aTemp = f_get_acceleration(fPos(l), fR, fVel(l), fmass_n, fmass_v, &
575575
fRe, fRho, cell, l, q_prim_vf)
576-
fPos(l) = fPos(l) + h * fVel(l)
577-
fVel(l) = fVel(l) + h * aTemp
576+
fPos(l) = fPos(l) + h*fVel(l)
577+
fVel(l) = fVel(l) + h*aTemp
578578
end do
579579
end if
580580
end if

src/simulation/m_bubbles_EL.fpp

Lines changed: 67 additions & 68 deletions
Large diffs are not rendered by default.

src/simulation/m_bubbles_EL_kernels.fpp

Lines changed: 62 additions & 62 deletions
Original file line numberDiff line numberDiff line change
@@ -447,28 +447,28 @@ contains
447447
xi(1) = x_cc(cell(1) - 1)
448448
eta(1) = q_prim_vf(momxb)%sf(cell(1) - 1, cell(2), cell(3))
449449
xi(2) = x_cc(cell(1))
450-
eta(2) = q_prim_vf(momxb)%sf(cell(1) , cell(2), cell(3))
450+
eta(2) = q_prim_vf(momxb)%sf(cell(1), cell(2), cell(3))
451451
xi(3) = x_cc(cell(1) + 1)
452452
eta(3) = q_prim_vf(momxb)%sf(cell(1) + 1, cell(2), cell(3))
453453
elseif (i == 2) then
454454
xi(1) = y_cc(cell(2) - 1)
455455
eta(1) = q_prim_vf(momxb + 1)%sf(cell(1), cell(2) - 1, cell(3))
456456
xi(2) = y_cc(cell(2))
457-
eta(2) = q_prim_vf(momxb + 1)%sf(cell(1), cell(2) , cell(3))
457+
eta(2) = q_prim_vf(momxb + 1)%sf(cell(1), cell(2), cell(3))
458458
xi(3) = y_cc(cell(2) + 1)
459459
eta(3) = q_prim_vf(momxb + 1)%sf(cell(1), cell(2) + 1, cell(3))
460460
elseif (i == 3) then
461461
xi(1) = z_cc(cell(3) - 1)
462462
eta(1) = q_prim_vf(momxe)%sf(cell(1), cell(2), cell(3) - 1)
463463
xi(2) = z_cc(cell(3))
464-
eta(2) = q_prim_vf(momxe)%sf(cell(1), cell(2), cell(3) )
464+
eta(2) = q_prim_vf(momxe)%sf(cell(1), cell(2), cell(3))
465465
xi(3) = z_cc(cell(3) + 1)
466466
eta(3) = q_prim_vf(momxe)%sf(cell(1), cell(2), cell(3) + 1)
467-
endif
467+
end if
468468

469-
L(1) = ((pos - xi(2))*(pos - xi(3))) / ((xi(1) - xi(2))*(xi(1) - xi(3)))
470-
L(2) = ((pos - xi(1))*(pos - xi(3))) / ((xi(2) - xi(1))*(xi(2) - xi(3)))
471-
L(3) = ((pos - xi(1))*(pos - xi(2))) / ((xi(3) - xi(1))*(xi(3) - xi(2)))
469+
L(1) = ((pos - xi(2))*(pos - xi(3)))/((xi(1) - xi(2))*(xi(1) - xi(3)))
470+
L(2) = ((pos - xi(1))*(pos - xi(3)))/((xi(2) - xi(1))*(xi(2) - xi(3)))
471+
L(3) = ((pos - xi(1))*(pos - xi(2)))/((xi(3) - xi(1))*(xi(3) - xi(2)))
472472

473473
v = L(1)*eta(1) + L(2)*eta(2) + L(3)*eta(3)
474474
elseif (fd_order == 4) then
@@ -478,7 +478,7 @@ contains
478478
xi(2) = x_cc(cell(1) - 1)
479479
eta(2) = q_prim_vf(momxb)%sf(cell(1) - 1, cell(2), cell(3))
480480
xi(3) = x_cc(cell(1))
481-
eta(3) = q_prim_vf(momxb)%sf(cell(1) , cell(2), cell(3))
481+
eta(3) = q_prim_vf(momxb)%sf(cell(1), cell(2), cell(3))
482482
xi(4) = x_cc(cell(1) + 1)
483483
eta(4) = q_prim_vf(momxb)%sf(cell(1) + 1, cell(2), cell(3))
484484
xi(5) = x_cc(cell(1) + 2)
@@ -489,7 +489,7 @@ contains
489489
xi(2) = y_cc(cell(2) - 1)
490490
eta(2) = q_prim_vf(momxb + 1)%sf(cell(1), cell(2) - 1, cell(3))
491491
xi(3) = y_cc(cell(2))
492-
eta(3) = q_prim_vf(momxb + 1)%sf(cell(1), cell(2) , cell(3))
492+
eta(3) = q_prim_vf(momxb + 1)%sf(cell(1), cell(2), cell(3))
493493
xi(4) = y_cc(cell(2) + 1)
494494
eta(4) = q_prim_vf(momxb + 1)%sf(cell(1), cell(2) + 1, cell(3))
495495
xi(5) = y_cc(cell(2) + 2)
@@ -500,22 +500,22 @@ contains
500500
xi(2) = z_cc(cell(3) - 1)
501501
eta(2) = q_prim_vf(momxe)%sf(cell(1), cell(2), cell(3) - 1)
502502
xi(3) = z_cc(cell(3))
503-
eta(3) = q_prim_vf(momxe)%sf(cell(1), cell(2), cell(3) )
503+
eta(3) = q_prim_vf(momxe)%sf(cell(1), cell(2), cell(3))
504504
xi(4) = z_cc(cell(3) + 1)
505505
eta(4) = q_prim_vf(momxe)%sf(cell(1), cell(2), cell(3) + 1)
506506
xi(5) = z_cc(cell(3) + 2)
507507
eta(5) = q_prim_vf(momxe)%sf(cell(1), cell(2), cell(3) + 2)
508-
endif
508+
end if
509509

510-
L(1) = ((pos - xi(2))*(pos - xi(3))*(pos - xi(4))*(pos - xi(5))) / &
510+
L(1) = ((pos - xi(2))*(pos - xi(3))*(pos - xi(4))*(pos - xi(5)))/ &
511511
((xi(1) - xi(2))*(xi(1) - xi(3))*(xi(1) - xi(3))*(xi(2) - xi(5)))
512-
L(2) = ((pos - xi(1))*(pos - xi(3))*(pos - xi(4))*(pos - xi(5))) / &
512+
L(2) = ((pos - xi(1))*(pos - xi(3))*(pos - xi(4))*(pos - xi(5)))/ &
513513
((xi(2) - xi(1))*(xi(2) - xi(3))*(xi(2) - xi(3))*(xi(2) - xi(5)))
514-
L(3) = ((pos - xi(1))*(pos - xi(2))*(pos - xi(4))*(pos - xi(5))) / &
514+
L(3) = ((pos - xi(1))*(pos - xi(2))*(pos - xi(4))*(pos - xi(5)))/ &
515515
((xi(3) - xi(1))*(xi(3) - xi(2))*(xi(3) - xi(4))*(xi(3) - xi(5)))
516-
L(4) = ((pos - xi(1))*(pos - xi(2))*(pos - xi(3))*(pos - xi(4))) / &
516+
L(4) = ((pos - xi(1))*(pos - xi(2))*(pos - xi(3))*(pos - xi(4)))/ &
517517
((xi(4) - xi(1))*(xi(4) - xi(2))*(xi(4) - xi(3))*(xi(4) - xi(5)))
518-
L(5) = ((pos - xi(1))*(pos - xi(2))*(pos - xi(3))*(pos - xi(4))) / &
518+
L(5) = ((pos - xi(1))*(pos - xi(2))*(pos - xi(3))*(pos - xi(4)))/ &
519519
((xi(5) - xi(1))*(xi(5) - xi(2))*(xi(5) - xi(3))*(xi(5) - xi(4)))
520520

521521
v = L(1)*eta(1) + L(2)*eta(2) + L(3)*eta(3) + L(4)*eta(4) + L(5)*eta(5)
@@ -536,7 +536,7 @@ contains
536536
!! @param i Direction of the velocity (1: x, 2: y, 3: z)
537537
!! @param q_prim_vf Eulerian field with primitive variables
538538
!! @return a Acceleration of the bubble in direction i
539-
pure function f_get_acceleration(pos,rad,vel,mg,mv,Re,rho,cell,i,q_prim_vf) result(a)
539+
pure function f_get_acceleration(pos, rad, vel, mg, mv, Re, rho, cell, i, q_prim_vf) result(a)
540540
$:GPU_ROUTINE(parallelism='[seq]')
541541
real(wp), intent(in) :: pos, rad, vel, mg, mv, Re, rho
542542
integer, dimension(3), intent(in) :: cell
@@ -549,79 +549,79 @@ contains
549549

550550
if (fd_order == 2) then
551551
if (i == 1) then
552-
dp = (q_prim_vf(E_idx)%sf(cell(1) + 1,cell(2),cell(3)) - &
553-
q_prim_vf(E_idx)%sf(cell(1) - 1,cell(2),cell(3))) / &
554-
(x_cc(cell(1) + 1) - x_cc(cell(1) - 1))
552+
dp = (q_prim_vf(E_idx)%sf(cell(1) + 1, cell(2), cell(3)) - &
553+
q_prim_vf(E_idx)%sf(cell(1) - 1, cell(2), cell(3)))/ &
554+
(x_cc(cell(1) + 1) - x_cc(cell(1) - 1))
555555
elseif (i == 2) then
556-
dp = (q_prim_vf(E_idx)%sf(cell(1),cell(2) + 1,cell(3)) - &
557-
q_prim_vf(E_idx)%sf(cell(1),cell(2) - 1,cell(3))) / &
558-
(y_cc(cell(2) + 1) - y_cc(cell(2) - 1))
556+
dp = (q_prim_vf(E_idx)%sf(cell(1), cell(2) + 1, cell(3)) - &
557+
q_prim_vf(E_idx)%sf(cell(1), cell(2) - 1, cell(3)))/ &
558+
(y_cc(cell(2) + 1) - y_cc(cell(2) - 1))
559559
elseif (i == 3) then
560-
dp = (q_prim_vf(E_idx)%sf(cell(1),cell(2),cell(3) + 1) - &
561-
q_prim_vf(E_idx)%sf(cell(1),cell(2),cell(3) - 1)) / &
562-
(z_cc(cell(3) + 1) - z_cc(cell(3) - 1))
560+
dp = (q_prim_vf(E_idx)%sf(cell(1), cell(2), cell(3) + 1) - &
561+
q_prim_vf(E_idx)%sf(cell(1), cell(2), cell(3) - 1))/ &
562+
(z_cc(cell(3) + 1) - z_cc(cell(3) - 1))
563563
end if
564564
elseif (fd_order == 4) then
565565
if (i == 1) then
566566
xi(1) = x_cc(cell(1) - 1)
567-
eta(1) = (q_prim_vf(E_idx)%sf(cell(1) ,cell(2),cell(3)) - &
568-
q_prim_vf(E_idx)%sf(cell(1) - 2,cell(2),cell(3))) / &
569-
(x_cc(cell(1)) - x_cc(cell(1) - 2))
567+
eta(1) = (q_prim_vf(E_idx)%sf(cell(1), cell(2), cell(3)) - &
568+
q_prim_vf(E_idx)%sf(cell(1) - 2, cell(2), cell(3)))/ &
569+
(x_cc(cell(1)) - x_cc(cell(1) - 2))
570570
xi(2) = x_cc(cell(1))
571-
eta(2) = (q_prim_vf(E_idx)%sf(cell(1) + 1,cell(2),cell(3)) - &
572-
q_prim_vf(E_idx)%sf(cell(1) - 1,cell(2),cell(3))) / &
573-
(x_cc(cell(1) + 1) - x_cc(cell(1) - 1))
571+
eta(2) = (q_prim_vf(E_idx)%sf(cell(1) + 1, cell(2), cell(3)) - &
572+
q_prim_vf(E_idx)%sf(cell(1) - 1, cell(2), cell(3)))/ &
573+
(x_cc(cell(1) + 1) - x_cc(cell(1) - 1))
574574
xi(3) = x_cc(cell(1) + 1)
575-
eta(3) = (q_prim_vf(E_idx)%sf(cell(1) + 2,cell(2),cell(3)) - &
576-
q_prim_vf(E_idx)%sf(cell(1) ,cell(2),cell(3))) / &
577-
(x_cc(cell(1) + 2) - x_cc(cell(1)))
575+
eta(3) = (q_prim_vf(E_idx)%sf(cell(1) + 2, cell(2), cell(3)) - &
576+
q_prim_vf(E_idx)%sf(cell(1), cell(2), cell(3)))/ &
577+
(x_cc(cell(1) + 2) - x_cc(cell(1)))
578578
elseif (i == 2) then
579579
xi(1) = y_cc(cell(2) - 1)
580-
eta(1) = (q_prim_vf(E_idx)%sf(cell(1),cell(2) ,cell(3)) - &
581-
q_prim_vf(E_idx)%sf(cell(1),cell(2) - 2,cell(3))) / &
582-
(y_cc(cell(2)) - y_cc(cell(2) - 2))
580+
eta(1) = (q_prim_vf(E_idx)%sf(cell(1), cell(2), cell(3)) - &
581+
q_prim_vf(E_idx)%sf(cell(1), cell(2) - 2, cell(3)))/ &
582+
(y_cc(cell(2)) - y_cc(cell(2) - 2))
583583
xi(2) = y_cc(cell(2))
584-
eta(2) = (q_prim_vf(E_idx)%sf(cell(1),cell(2) + 1,cell(3)) - &
585-
q_prim_vf(E_idx)%sf(cell(1),cell(2) - 1,cell(3))) / &
586-
(y_cc(cell(2) + 1) - y_cc(cell(2) - 1))
584+
eta(2) = (q_prim_vf(E_idx)%sf(cell(1), cell(2) + 1, cell(3)) - &
585+
q_prim_vf(E_idx)%sf(cell(1), cell(2) - 1, cell(3)))/ &
586+
(y_cc(cell(2) + 1) - y_cc(cell(2) - 1))
587587
xi(3) = y_cc(cell(2) + 1)
588-
eta(3) = (q_prim_vf(E_idx)%sf(cell(1),cell(2) + 2,cell(3)) - &
589-
q_prim_vf(E_idx)%sf(cell(1),cell(2) ,cell(3))) / &
590-
(y_cc(cell(2) + 2) - y_cc(cell(2)))
588+
eta(3) = (q_prim_vf(E_idx)%sf(cell(1), cell(2) + 2, cell(3)) - &
589+
q_prim_vf(E_idx)%sf(cell(1), cell(2), cell(3)))/ &
590+
(y_cc(cell(2) + 2) - y_cc(cell(2)))
591591
elseif (i == 3) then
592592
xi(1) = z_cc(cell(3) - 1)
593-
eta(1) = (q_prim_vf(E_idx)%sf(cell(1),cell(2),cell(3) ) - &
594-
q_prim_vf(E_idx)%sf(cell(1),cell(2),cell(3) - 2)) / &
595-
(z_cc(cell(3)) - z_cc(cell(3) - 2))
593+
eta(1) = (q_prim_vf(E_idx)%sf(cell(1), cell(2), cell(3)) - &
594+
q_prim_vf(E_idx)%sf(cell(1), cell(2), cell(3) - 2))/ &
595+
(z_cc(cell(3)) - z_cc(cell(3) - 2))
596596
xi(2) = y_cc(cell(3))
597-
eta(2) = (q_prim_vf(E_idx)%sf(cell(1),cell(2),cell(3) + 1) - &
598-
q_prim_vf(E_idx)%sf(cell(1),cell(2),cell(3) - 1)) / &
599-
(z_cc(cell(3) + 1) - z_cc(cell(3) - 1))
597+
eta(2) = (q_prim_vf(E_idx)%sf(cell(1), cell(2), cell(3) + 1) - &
598+
q_prim_vf(E_idx)%sf(cell(1), cell(2), cell(3) - 1))/ &
599+
(z_cc(cell(3) + 1) - z_cc(cell(3) - 1))
600600
xi(3) = y_cc(cell(3) + 1)
601-
eta(3) = (q_prim_vf(E_idx)%sf(cell(1),cell(2),cell(3) + 2) - &
602-
q_prim_vf(E_idx)%sf(cell(1),cell(2),cell(3) )) / &
603-
(z_cc(cell(3) + 2) - z_cc(cell(3)))
601+
eta(3) = (q_prim_vf(E_idx)%sf(cell(1), cell(2), cell(3) + 2) - &
602+
q_prim_vf(E_idx)%sf(cell(1), cell(2), cell(3)))/ &
603+
(z_cc(cell(3) + 2) - z_cc(cell(3)))
604604
end if
605605

606-
L(1) = ((pos - xi(2))*(pos - xi(3))) / ((xi(1) - xi(2))*(xi(1) - xi(3)))
607-
L(2) = ((pos - xi(1))*(pos - xi(3))) / ((xi(2) - xi(1))*(xi(2) - xi(3)))
608-
L(3) = ((pos - xi(1))*(pos - xi(2))) / ((xi(3) - xi(1))*(xi(3) - xi(2)))
606+
L(1) = ((pos - xi(2))*(pos - xi(3)))/((xi(1) - xi(2))*(xi(1) - xi(3)))
607+
L(2) = ((pos - xi(1))*(pos - xi(3)))/((xi(2) - xi(1))*(xi(2) - xi(3)))
608+
L(3) = ((pos - xi(1))*(pos - xi(2)))/((xi(3) - xi(1))*(xi(3) - xi(2)))
609609

610610
dp = L(1)*eta(1) + L(2)*eta(2) + L(3)*eta(3)
611611
end if
612612

613-
vol = (4._wp/3._wp) * pi * rad**3._wp
614-
force = -1._wp * vol * dp
613+
vol = (4._wp/3._wp)*pi*rad**3._wp
614+
force = -1._wp*vol*dp
615615

616-
v_rel = vel - f_interpolate_velocity(pos,cell,i,q_prim_vf)
616+
v_rel = vel - f_interpolate_velocity(pos, cell, i, q_prim_vf)
617617

618618
if (lag_params%drag_model == 1) then ! Free slip Stokes drag
619-
force = force - (4._wp * pi * rad * v_rel) / Re
619+
force = force - (4._wp*pi*rad*v_rel)/Re
620620
else if (lag_params%drag_model == 2) then ! No slip Stokes drag
621-
force = force - (6._wp * pi * rad * v_rel) / Re
621+
force = force - (6._wp*pi*rad*v_rel)/Re
622622
end if
623623

624-
a = force / (mg + mv)
624+
a = force/(mg + mv)
625625

626626
end function f_get_acceleration
627627

src/simulation/m_global_parameters.fpp

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -252,9 +252,9 @@ module m_global_parameters
252252
integer, allocatable, dimension(:) :: proc_coords !<
253253
!! Processor coordinates in MPI_CART_COMM
254254

255-
type(int_bounds_info), dimension(3) :: nidx !< Indicies for neighboring processors
255+
type(int_bounds_info), dimension(3) :: nidx !< Indices for neighboring processors
256256

257-
integer, allocatable, dimension(:,:,:) :: neighbor_ranks
257+
integer, allocatable, dimension(:, :, :) :: neighbor_ranks
258258
!! Neighbor ranks for lagrangian particle communication
259259

260260
integer, allocatable, dimension(:) :: start_idx !<
@@ -1352,15 +1352,15 @@ contains
13521352
@:PREFER_GPU(x_cc)
13531353
@:PREFER_GPU(dx)
13541354
1355-
if (n == 0) return;
1355+
if (n == 0) return;
13561356
@:ALLOCATE(y_cb(-1 - buff_size:n + buff_size))
13571357
@:ALLOCATE(y_cc(-buff_size:n + buff_size))
13581358
@:ALLOCATE(dy(-buff_size:n + buff_size))
13591359
@:PREFER_GPU(y_cb)
13601360
@:PREFER_GPU(y_cc)
13611361
@:PREFER_GPU(dy)
13621362
1363-
if (p == 0) return;
1363+
if (p == 0) return;
13641364
@:ALLOCATE(z_cb(-1 - buff_size:p + buff_size))
13651365
@:ALLOCATE(z_cc(-buff_size:p + buff_size))
13661366
@:ALLOCATE(dz(-buff_size:p + buff_size))
@@ -1446,10 +1446,10 @@ contains
14461446
! Deallocating grid variables for the x-, y- and z-directions
14471447
@:DEALLOCATE(x_cb, x_cc, dx)
14481448
1449-
if (n == 0) return;
1449+
if (n == 0) return;
14501450
@:DEALLOCATE(y_cb, y_cc, dy)
14511451
1452-
if (p == 0) return;
1452+
if (p == 0) return;
14531453
@:DEALLOCATE(z_cb, z_cc, dz)
14541454
14551455
end subroutine s_finalize_global_parameters_module

0 commit comments

Comments
 (0)