Skip to content

Commit c4fabf7

Browse files
authored
Merge branch 'master' into master
2 parents 30c4f8f + db44da1 commit c4fabf7

35 files changed

+953
-1134
lines changed

.cursor/rules/mfc-agent-rules.mdc

Lines changed: 82 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,82 @@
1+
---
2+
description: Full MFC project rules – consolidated for Agent Mode
3+
alwaysApply: true
4+
---
5+
6+
# 0 Purpose & Scope
7+
Consolidated guidance for the MFC exascale, many-physics solver.
8+
Written primarily for Fortran/Fypp; the OpenACC and style sections matter only when
9+
`.fpp` / `.f90` files are in view.
10+
11+
---
12+
13+
# 1 Global Project Context (always)
14+
- **Project**: *MFC* is modern Fortran 2008+ generated with **Fypp**.
15+
- Sources `src/`, tests `tests/`, examples `examples/`.
16+
- Most sources are `.fpp`; CMake transpiles them to `.f90`.
17+
- **Fypp macros** live in `src/<subprogram>/include/` you should scan these first.
18+
`<subprogram>` ∈ {`simulation`,`common`,`pre_process`,`post_process`}.
19+
- Only `simulation` (+ its `common` calls) is GPU-accelerated via **OpenACC**.
20+
- Assume free-form Fortran 2008+, `implicit none`, explicit `intent`, and modern
21+
intrinsics.
22+
- Prefer `module … contains … subroutine foo()`; avoid `COMMON` blocks and
23+
file-level `include` files.
24+
- **Read the full codebase and docs *before* changing code.**
25+
Docs: <https://mflowcode.github.io/documentation/md_readme.html> and the respository root `README.md`.
26+
27+
### Incremental-change workflow
28+
1. Draft a step-by-step plan.
29+
2. After each step, build:
30+
```bash
31+
./mfc.sh build -t pre_process simulation -j $(nproc)
32+
```
33+
3. If it compiles, run focused tests:
34+
```bash
35+
./mfc.sh test -j $(nproc) -f EA8FA07E -t 9E2CA336
36+
```
37+
4. Roll back & fix if a step fails.
38+
39+
* Do not run ./mfc.sh test -j $(nproc) without any other arguments (it takes too long to run all tests).
40+
41+
---
42+
43+
# 2 Style & Naming Conventions (for \*.fpp / \*.f90)
44+
45+
* **Indent 2 spaces**; continuation lines align under `&`.
46+
* Lower-case keywords and intrinsics (`do`, `end subroutine`, …).
47+
* **Modules**: `m_<feature>` (e.g. `m_transport`).
48+
* **Public procedures**:
49+
* Subroutine → `s_<verb>_<noun>` (e.g. `s_compute_flux`)
50+
* Function → `f_<verb>_<noun>`
51+
* Private helpers stay in the module; avoid nested procedures.
52+
* **Size limits**: subroutine ≤ 500 lines, helper ≤ 150, function ≤ 100,
53+
module/file ≤ 1000.
54+
* ≤ 6 arguments per routine; otherwise pass a derived-type “params” struct.
55+
* No `goto` (except unavoidable legacy); no global state (`COMMON`, `save`).
56+
* Every variable: `intent(in|out|inout)` + appropriate `dimension` / `allocatable`
57+
/ `pointer`.
58+
* Use `s_mpi_abort(<msg>)` for errors, not `stop`.
59+
* Mark OpenACC-callable helpers that are called from OpenACC parallel loops immediately after declaration:
60+
```fortran
61+
subroutine s_flux_update(...)
62+
!$acc routine seq
63+
...
64+
end subroutine
65+
```
66+
67+
---
68+
69+
# 3 OpenACC Programming Guidelines (for kernels)
70+
71+
Wrap tight loops with
72+
73+
```fortran
74+
!$acc parallel loop gang vector default(present) reduction(...)
75+
```
76+
* Add `collapse(n)` to merge nested loops when safe.
77+
* Declare loop-local variables with `private(...)`.
78+
* Allocate large arrays with `managed` or move them into a persistent
79+
`!$acc enter data` region at start-up.
80+
* **Do not** place `stop` / `error stop` inside device code.
81+
* Must compile with Cray `ftn` and NVIDIA `nvfortran` for GPU offloading; also build CPU-only with
82+
GNU `gfortran` and Intel `ifx`/`ifort`.

.github/workflows/phoenix/bench.sh

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -8,8 +8,13 @@ if [ "$job_device" == "gpu" ]; then
88
device_opts="--gpu -g $gpu_ids"
99
fi
1010

11+
mkdir -p /storage/scratch1/6/sbryngelson3/mytmp_build
12+
export TMPDIR=/storage/scratch1/6/sbryngelson3/mytmp_build
13+
1114
if ["$job_device" == "gpu"]; then
1215
./mfc.sh bench --mem 12 -j $(nproc) -o "$job_slug.yaml" -- -c phoenix-bench $device_opts -n $n_ranks
1316
else
1417
./mfc.sh bench --mem 1 -j $(nproc) -o "$job_slug.yaml" -- -c phoenix-bench $device_opts -n $n_ranks
1518
fi
19+
20+
unset TMPDIR

CMakeLists.txt

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -135,13 +135,17 @@ if (CMAKE_Fortran_COMPILER_ID STREQUAL "GNU")
135135
if (CMAKE_BUILD_TYPE STREQUAL "Debug")
136136
add_compile_options(
137137
-Wall
138+
-Wextra
138139
-fcheck=all,no-array-temps
139140
-fbacktrace
140141
-fimplicit-none
141-
#-ffpe-trap=invalid,zero,denormal,overflow
142142
-fsignaling-nans
143143
-finit-real=snan
144144
-finit-integer=-99999999
145+
-Wintrinsic-shadow
146+
-Wunderflow
147+
-Wrealloc-lhs
148+
-Wsurprising
145149
)
146150
endif()
147151

misc/length-subroutines.sh

Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,29 @@
1+
#!/bin/bash
2+
3+
# Use gawk if available, otherwise fall back to awk
4+
if command -v gawk > /dev/null; then
5+
AWK_CMD="gawk"
6+
IGNORECASE_BLOCK='BEGIN { IGNORECASE = 1 }'
7+
else
8+
AWK_CMD="awk"
9+
IGNORECASE_BLOCK=''
10+
echo "Warning: gawk not found. Case-insensitive matching may not work as expected." >&2
11+
fi
12+
13+
find . -type f \( -name "*.f90" -o -name "*.fpp" \) | while read file; do
14+
"$AWK_CMD" "
15+
$IGNORECASE_BLOCK
16+
/^[ \t]*((pure|elemental|impure)[ \t]+)*subroutine[ \t]+[a-zA-Z_][a-zA-Z0-9_]*[ \t]*\\(/ {
17+
in_sub = 1
18+
match(\$0, /subroutine[ \t]+([a-zA-Z_][a-zA-Z0-9_]*)/, arr)
19+
sub_name = arr[1]
20+
start_line = NR
21+
next
22+
}
23+
/^[ \t]*end[ \t]+subroutine[ \t]*([a-zA-Z_][a-zA-Z0-9_]*)?[ \t]*\$/ && in_sub {
24+
end_line = NR
25+
print (end_line - start_line + 1) \"\t\" FILENAME \": \" sub_name
26+
in_sub = 0
27+
}
28+
" "$file"
29+
done | sort -nr | awk -F'\t' '{print $2 " : " $1 " lines"}' | head -20

src/common/m_boundary_common.fpp

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -142,7 +142,7 @@ contains
142142
case (BC_CHAR_SUP_OUTFLOW:BC_GHOST_EXTRAP)
143143
call s_ghost_cell_extrapolation(q_prim_vf, pb, mv, 2, -1, k, l)
144144
case (BC_AXIS)
145-
call s_axis(q_prim_vf, pb, mv, 2, -1, k, l)
145+
call s_axis(q_prim_vf, pb, mv, k, l)
146146
case (BC_REFLECTIVE)
147147
call s_symmetry(q_prim_vf, pb, mv, 2, -1, k, l)
148148
case (BC_PERIODIC)
@@ -713,15 +713,14 @@ contains
713713

714714
end subroutine s_periodic
715715

716-
pure subroutine s_axis(q_prim_vf, pb, mv, bc_dir, bc_loc, k, l)
716+
pure subroutine s_axis(q_prim_vf, pb, mv, k, l)
717717
#ifdef _CRAYFTN
718718
!DIR$ INLINEALWAYS s_axis
719719
#else
720720
!$acc routine seq
721721
#endif
722722
type(scalar_field), dimension(sys_size), intent(inout) :: q_prim_vf
723723
real(wp), dimension(idwbuff(1)%beg:, idwbuff(2)%beg:, idwbuff(3)%beg:, 1:, 1:), intent(inout) :: pb, mv
724-
integer, intent(in) :: bc_dir, bc_loc
725724
integer, intent(in) :: k, l
726725

727726
integer :: j, q, i

src/common/m_finite_differences.fpp

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -15,8 +15,7 @@ contains
1515
integer :: x, y, z !< Generic loop iterators
1616

1717
real(wp) :: divergence
18-
19-
!$acc parallel loop collapse(3) private(divergence)
18+
!$acc parallel loop collapse(3) gang vector default(present) private(divergence)
2019
do x = ix_s%beg, ix_s%end
2120
do y = iy_s%beg, iy_s%end
2221
do z = iz_s%beg, iz_s%end

src/common/m_mpi_common.fpp

Lines changed: 2 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -375,21 +375,17 @@ contains
375375
!! @param Rc_min_glb Global minimum Rc stability criterion
376376
impure subroutine s_mpi_reduce_stability_criteria_extrema(icfl_max_loc, &
377377
vcfl_max_loc, &
378-
ccfl_max_loc, &
379378
Rc_min_loc, &
380379
icfl_max_glb, &
381380
vcfl_max_glb, &
382-
ccfl_max_glb, &
383381
Rc_min_glb)
384382
385383
real(wp), intent(in) :: icfl_max_loc
386384
real(wp), intent(in) :: vcfl_max_loc
387-
real(wp), intent(in) :: ccfl_max_loc
388385
real(wp), intent(in) :: Rc_min_loc
389386
390387
real(wp), intent(out) :: icfl_max_glb
391388
real(wp), intent(out) :: vcfl_max_glb
392-
real(wp), intent(out) :: ccfl_max_glb
393389
real(wp), intent(out) :: Rc_min_glb
394390
395391
#ifdef MFC_SIMULATION
@@ -1178,7 +1174,8 @@ contains
11781174
#:endif
11791175
end if
11801176
#:endfor
1181-
1177+
p_send => buff_send(0)
1178+
p_recv => buff_recv(0)
11821179
! Send/Recv
11831180
#ifdef MFC_SIMULATION
11841181
#:for rdma_mpi in [False, True]

src/common/m_phase_change.fpp

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -143,7 +143,7 @@ contains
143143

144144
! Calling pT-equilibrium for either finishing phase-change module, or as an IC for the pTg-equilibrium
145145
! for this case, MFL cannot be either 0 or 1, so I chose it to be 2
146-
call s_infinite_pt_relaxation_k(j, k, l, 2, pS, p_infpT, rM, q_cons_vf, rhoe, TS)
146+
call s_infinite_pt_relaxation_k(j, k, l, 2, pS, p_infpT, q_cons_vf, rhoe, TS)
147147

148148
! check if pTg-equilibrium is required
149149
! NOTE that NOTHING else needs to be updated OTHER than the individual partial densities
@@ -164,7 +164,7 @@ contains
164164
q_cons_vf(vp + contxb - 1)%sf(j, k, l) = (1.0_wp - mixM)*rM
165165

166166
! calling pT-equilibrium for overheated vapor, which is MFL = 0
167-
call s_infinite_pt_relaxation_k(j, k, l, 0, pSOV, p_infOV, rM, q_cons_vf, rhoe, TSOV)
167+
call s_infinite_pt_relaxation_k(j, k, l, 0, pSOV, p_infOV, q_cons_vf, rhoe, TSOV)
168168

169169
! calculating Saturation temperature
170170
call s_TSat(pSOV, TSatOV, TSOV)
@@ -177,7 +177,7 @@ contains
177177
q_cons_vf(vp + contxb - 1)%sf(j, k, l) = mixM*rM
178178

179179
! calling pT-equilibrium for subcooled liquid, which is MFL = 1
180-
call s_infinite_pt_relaxation_k(j, k, l, 1, pSSL, p_infSL, rM, q_cons_vf, rhoe, TSSL)
180+
call s_infinite_pt_relaxation_k(j, k, l, 1, pSSL, p_infSL, q_cons_vf, rhoe, TSSL)
181181

182182
! calculating Saturation temperature
183183
call s_TSat(pSSL, TSatSL, TSSL)
@@ -281,7 +281,7 @@ contains
281281
!! @param q_cons_vf Cell-average conservative variables
282282
!! @param rhoe mixture energy
283283
!! @param TS equilibrium temperature at the interface
284-
pure subroutine s_infinite_pt_relaxation_k(j, k, l, MFL, pS, p_infpT, rM, q_cons_vf, rhoe, TS)
284+
pure subroutine s_infinite_pt_relaxation_k(j, k, l, MFL, pS, p_infpT, q_cons_vf, rhoe, TS)
285285

286286
#ifdef _CRAYFTN
287287
!DIR$ INLINEALWAYS s_infinite_pt_relaxation_k
@@ -293,7 +293,6 @@ contains
293293
integer, intent(in) :: j, k, l, MFL
294294
real(wp), intent(out) :: pS
295295
real(wp), dimension(num_fluids), intent(out) :: p_infpT
296-
real(wp), intent(in) :: rM
297296
type(scalar_field), dimension(sys_size), intent(in) :: q_cons_vf
298297
real(wp), intent(in) :: rhoe
299298
real(wp), intent(out) :: TS

src/common/m_variables_conversion.fpp

Lines changed: 13 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -92,11 +92,11 @@ contains
9292

9393
if (model_eqns == 1) then ! Gamma/pi_inf model
9494
call s_convert_mixture_to_mixture_variables(q_vf, i, j, k, &
95-
rho, gamma, pi_inf, qv, Re_K, G_K, G)
95+
rho, gamma, pi_inf, qv)
9696

9797
else if (bubbles_euler) then
9898
call s_convert_species_to_mixture_variables_bubbles(q_vf, i, j, k, &
99-
rho, gamma, pi_inf, qv, Re_K, G_K, G)
99+
rho, gamma, pi_inf, qv, Re_K)
100100
else
101101
! Volume fraction model
102102
call s_convert_species_to_mixture_variables(q_vf, i, j, k, &
@@ -207,7 +207,7 @@ contains
207207
!! @param pi_inf liquid stiffness
208208
!! @param qv fluid reference energy
209209
subroutine s_convert_mixture_to_mixture_variables(q_vf, i, j, k, &
210-
rho, gamma, pi_inf, qv, Re_K, G_K, G)
210+
rho, gamma, pi_inf, qv)
211211

212212
type(scalar_field), dimension(sys_size), intent(in) :: q_vf
213213
integer, intent(in) :: i, j, k
@@ -217,11 +217,6 @@ contains
217217
real(wp), intent(out), target :: pi_inf
218218
real(wp), intent(out), target :: qv
219219

220-
real(wp), optional, dimension(2), intent(out) :: Re_K
221-
222-
real(wp), optional, intent(out) :: G_K
223-
real(wp), optional, dimension(num_fluids), intent(in) :: G
224-
225220
! Transferring the density, the specific heat ratio function and the
226221
! liquid stiffness function, respectively
227222
rho = q_vf(1)%sf(i, j, k)
@@ -254,7 +249,7 @@ contains
254249
!! @param pi_inf liquid stiffness
255250
!! @param qv fluid reference energy
256251
subroutine s_convert_species_to_mixture_variables_bubbles(q_vf, j, k, l, &
257-
rho, gamma, pi_inf, qv, Re_K, G_K, G)
252+
rho, gamma, pi_inf, qv, Re_K)
258253

259254
type(scalar_field), dimension(sys_size), intent(in) :: q_vf
260255

@@ -266,8 +261,6 @@ contains
266261
real(wp), intent(out), target :: qv
267262

268263
real(wp), optional, dimension(2), intent(out) :: Re_K
269-
real(wp), optional, intent(out) :: G_K
270-
real(wp), optional, dimension(num_fluids), intent(in) :: G
271264

272265
integer :: i, q
273266
real(wp), dimension(num_fluids) :: alpha_rho_K, alpha_K
@@ -464,7 +457,7 @@ contains
464457

465458
pure subroutine s_convert_species_to_mixture_variables_acc(rho_K, &
466459
gamma_K, pi_inf_K, qv_K, &
467-
alpha_K, alpha_rho_K, Re_K, k, l, r, &
460+
alpha_K, alpha_rho_K, Re_K, &
468461
G_K, G)
469462
#ifdef _CRAYFTN
470463
!DIR$ INLINEALWAYS s_convert_species_to_mixture_variables_acc
@@ -481,8 +474,6 @@ contains
481474
real(wp), optional, intent(out) :: G_K
482475
real(wp), optional, dimension(num_fluids), intent(in) :: G
483476

484-
integer, intent(in) :: k, l, r
485-
486477
integer :: i, j !< Generic loop iterators
487478
real(wp) :: alpha_K_sum
488479

@@ -548,7 +539,7 @@ contains
548539

549540
pure subroutine s_convert_species_to_mixture_variables_bubbles_acc(rho_K, &
550541
gamma_K, pi_inf_K, qv_K, &
551-
alpha_K, alpha_rho_K, Re_K, k, l, r)
542+
alpha_K, alpha_rho_K, Re_K)
552543
#ifdef _CRAYFTN
553544
!DIR$ INLINEALWAYS s_convert_species_to_mixture_variables_bubbles_acc
554545
#else
@@ -561,7 +552,6 @@ contains
561552
!! Partial densities and volume fractions
562553

563554
real(wp), dimension(2), intent(out) :: Re_K
564-
integer, intent(in) :: k, l, r
565555

566556
integer :: i, j !< Generic loop iterators
567557

@@ -820,16 +810,12 @@ contains
820810
subroutine s_convert_conservative_to_primitive_variables(qK_cons_vf, &
821811
q_T_sf, &
822812
qK_prim_vf, &
823-
ibounds, &
824-
gm_alphaK_vf)
813+
ibounds)
825814

826815
type(scalar_field), dimension(sys_size), intent(in) :: qK_cons_vf
827816
type(scalar_field), intent(inout) :: q_T_sf
828817
type(scalar_field), dimension(sys_size), intent(inout) :: qK_prim_vf
829818
type(int_bounds_info), dimension(1:3), intent(in) :: ibounds
830-
type(scalar_field), &
831-
allocatable, optional, dimension(:), &
832-
intent(in) :: gm_alphaK_vf
833819

834820
real(wp), dimension(num_fluids) :: alpha_K, alpha_rho_K
835821
real(wp), dimension(2) :: Re_K
@@ -903,13 +889,13 @@ contains
903889
! If in simulation, use acc mixture subroutines
904890
if (elasticity) then
905891
call s_convert_species_to_mixture_variables_acc(rho_K, gamma_K, pi_inf_K, qv_K, alpha_K, &
906-
alpha_rho_K, Re_K, j, k, l, G_K, Gs)
892+
alpha_rho_K, Re_K, G_K, Gs)
907893
else if (bubbles_euler) then
908894
call s_convert_species_to_mixture_variables_bubbles_acc(rho_K, gamma_K, pi_inf_K, qv_K, &
909-
alpha_K, alpha_rho_K, Re_K, j, k, l)
895+
alpha_K, alpha_rho_K, Re_K)
910896
else
911897
call s_convert_species_to_mixture_variables_acc(rho_K, gamma_K, pi_inf_K, qv_K, &
912-
alpha_K, alpha_rho_K, Re_K, j, k, l)
898+
alpha_K, alpha_rho_K, Re_K)
913899
end if
914900
#else
915901
! If pre-processing, use non acc mixture subroutines
@@ -1510,13 +1496,13 @@ contains
15101496
if (elasticity) then
15111497
call s_convert_species_to_mixture_variables_acc(rho_K, gamma_K, pi_inf_K, qv_K, &
15121498
alpha_K, alpha_rho_K, Re_K, &
1513-
j, k, l, G_K, Gs)
1499+
G_K, Gs)
15141500
else if (bubbles_euler) then
15151501
call s_convert_species_to_mixture_variables_bubbles_acc(rho_K, gamma_K, &
1516-
pi_inf_K, qv_K, alpha_K, alpha_rho_K, Re_K, j, k, l)
1502+
pi_inf_K, qv_K, alpha_K, alpha_rho_K, Re_K)
15171503
else
15181504
call s_convert_species_to_mixture_variables_acc(rho_K, gamma_K, pi_inf_K, qv_K, &
1519-
alpha_K, alpha_rho_K, Re_K, j, k, l)
1505+
alpha_K, alpha_rho_K, Re_K)
15201506
end if
15211507

15221508
! Computing the energy from the pressure

0 commit comments

Comments
 (0)