Skip to content

Commit

Permalink
add non-omp compatibility of [get_physical_tendencies]
Browse files Browse the repository at this point in the history
  • Loading branch information
cheny16 committed Oct 11, 2024
1 parent 1a56929 commit 91393ca
Showing 1 changed file with 13 additions and 1 deletion.
14 changes: 13 additions & 1 deletion source/physics.f90
Original file line number Diff line number Diff line change
Expand Up @@ -237,6 +237,7 @@ subroutine get_physical_tendencies(vor, div, t, q, phi, psl, utend, vtend, ttend

! Add tendencies due to surface fluxes

#ifdef _OPENMP
!$omp do schedule(static)
do k = 1, kx
if (k == kx) then
Expand All @@ -256,7 +257,18 @@ subroutine get_physical_tendencies(vor, div, t, q, phi, psl, utend, vtend, ttend
qtend(:,:,k) = qtend(:,:,k) + qt_pbl(:,:,k)
end do
!$omp end do

#else
ut_pbl(:,:,kx) = ut_pbl(:,:,kx) + ustr(:,:,3)*rps*grdsig(kx)
vt_pbl(:,:,kx) = vt_pbl(:,:,kx) + vstr(:,:,3)*rps*grdsig(kx)
tt_pbl(:,:,kx) = tt_pbl(:,:,kx) + shf(:,:,3)*rps*grdscp(kx)
qt_pbl(:,:,kx) = qt_pbl(:,:,kx) + evap(:,:,3)*rps*grdsig(kx)

utend = utend + ut_pbl
vtend = vtend + vt_pbl
ttend = ttend + tt_pbl
qtend = qtend + qt_pbl
#endif

! !$omp single
! !$omp task depend(out: ut_pbl)
! ut_pbl(:,:,kx) = ut_pbl(:,:,kx) + ustr(:,:,3)*rps*grdsig(kx)
Expand Down

0 comments on commit 91393ca

Please sign in to comment.