Skip to content

Commit 2009896

Browse files
committed
Refactor Love_scaling calculation in SAL module
* Precalcualte a local field `coef_rhoE` to avoid in-loop division and if-blocks. The unit of coef_rhoE depends on use_bpa. * Fix a few unit description typos in SAL module and two other files.
1 parent 29e5b82 commit 2009896

File tree

3 files changed

+18
-11
lines changed

3 files changed

+18
-11
lines changed

src/core/MOM_open_boundary.F90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5443,7 +5443,7 @@ subroutine update_segment_tracer_reservoirs(G, GV, uhr, vhr, h, OBC, dt, Reg)
54435443
endif
54445444
I_scale = 1.0 ; if (segment%tr_Reg%Tr(m)%scale /= 0.0) I_scale = 1.0 / segment%tr_Reg%Tr(m)%scale
54455445
if (allocated(segment%tr_Reg%Tr(m)%tres)) then ; do k=1,nz
5446-
! Calculate weights. Both a and u_L are nodim. Adding them together has no meaning.
5446+
! Calculate weights. Both a and u_L are nondim. Adding them together has no meaning.
54475447
! However, since they cannot be both non-zero, adding them works like a switch.
54485448
! When InvLscale_out is 0 and outflow, only interior data is applied to reservoirs
54495449
! When InvLscale_in is 0 and inflow, only nudged data is applied to reservoirs

src/parameterizations/lateral/MOM_self_attr_load.F90

Lines changed: 16 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -38,12 +38,12 @@ module MOM_self_attr_load
3838
type(sht_CS), allocatable :: sht
3939
!< Spherical harmonic transforms (SHT) control structure
4040
integer :: sal_sht_Nd
41-
!< Maximum degree for spherical harmonic transforms [nodim]
41+
!< Maximum degree for spherical harmonic transforms [nondim]
4242
real, allocatable :: ebot_ref(:,:)
4343
!< Reference bottom pressure scaled by Rho_0 and G_Earth[Z ~> m]
4444
real, allocatable :: Love_scaling(:)
4545
!< Dimensional coefficients for harmonic SAL, which are functions of Love numbers
46-
!! [nondim or Z T2 L-2 R-1 ~> m Pa-1]
46+
!! [nondim] or [Z T2 L-2 R-1 ~> m Pa-1], depending on the value of use_ppa.
4747
real, allocatable :: Snm_Re(:), & !< Real SHT coefficient for SHT SAL [Z ~> m]
4848
Snm_Im(:) !< Imaginary SHT coefficient for SHT SAL [Z ~> m]
4949
end type SAL_CS
@@ -69,7 +69,7 @@ subroutine calc_SAL(eta, eta_sal, G, CS, tmp_scale)
6969
!! to MKS units in reproducing sumes [m Z-1 ~> 1]
7070

7171
! Local variables
72-
real, dimension(SZI_(G),SZJ_(G)) :: bpa ! SSH or bottom pressure anomaly [Z ~> m or R L2 T-2 ~> Pa]
72+
real, dimension(SZI_(G),SZJ_(G)) :: bpa ! SSH or bottom pressure anomaly [Z ~> m] or [R L2 T-2 ~> Pa]
7373
integer :: n, m, l
7474
integer :: Isq, Ieq, Jsq, Jeq
7575
integer :: i, j
@@ -136,6 +136,8 @@ subroutine calc_love_scaling(rhoW, rhoE, grav, CS)
136136
type(SAL_CS), intent(inout) :: CS !< The control structure returned by a previous call to SAL_init.
137137

138138
! Local variables
139+
real :: coef_rhoE ! A scaling coefficient of solid Earth density. coef_rhoE = rhoW / rhoE with USE_BPA=False
140+
! and coef_rhoE = 1.0 / (rhoE * grav) with USE_BPA=True. [nondim] or [Z T2 L-2 R-1 ~> m Pa-1]
139141
real, dimension(:), allocatable :: HDat, LDat, KDat ! Love numbers converted in CF reference frames [nondim]
140142
real :: H1, L1, K1 ! Temporary variables to store degree 1 Love numbers [nondim]
141143
integer :: n_tot ! Size of the stored Love numbers [nondim]
@@ -160,13 +162,16 @@ subroutine calc_love_scaling(rhoW, rhoE, grav, CS)
160162
KDat(2) = (-1.0 / 3.0) * H1 - (2.0 / 3.0) * L1 - 1.0
161163
endif
162164

165+
if (CS%use_bpa) then
166+
coef_rhoE = 1.0 / (rhoE * grav) ! [Z T2 L-2 R-1 ~> m Pa-1]
167+
else
168+
coef_rhoE = rhoW / rhoE ! [nondim]
169+
endif
170+
163171
do m=0,nlm ; do n=m,nlm
164-
l = order2index(m,nlm)
165-
if (CS%use_bpa) then
166-
CS%Love_scaling(l+n-m) = (3.0 / real(2*n+1)) * (1.0 / (rhoE * grav)) * (1.0 + KDat(n+1) - HDat(n+1))
167-
else
168-
CS%Love_scaling(l+n-m) = (3.0 / real(2*n+1)) * (rhoW / rhoE) * (1.0 + KDat(n+1) - HDat(n+1))
169-
endif
172+
l = order2index(m, nlm)
173+
! Love_scaling has the same as coef_rhoE.
174+
CS%Love_scaling(l+n-m) = (3.0 / real(2*n+1)) * coef_rhoE * (1.0 + KDat(n+1) - HDat(n+1))
170175
enddo ; enddo
171176
end subroutine calc_love_scaling
172177

@@ -315,6 +320,8 @@ end subroutine SAL_end
315320

316321
!> \namespace self_attr_load
317322
!!
323+
!! \section section_SAL Self attraction and loading
324+
!!
318325
!! This module contains methods to calculate self-attraction and loading (SAL) as a function of sea surface height or
319326
!! bottom pressure anomaly. SAL is primarily used for fast evolving processes like tides or storm surges, but the
320327
!! effect applies to all motions.

src/parameterizations/vertical/MOM_diapyc_energy_req.F90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -73,7 +73,7 @@ subroutine diapyc_energy_req_test(h_3d, dt, tv, G, GV, US, CS, Kd_int)
7373
Kd, & ! A column of diapycnal diffusivities at interfaces [H Z T-1 ~> m2 s-1 or kg m-1 s-1].
7474
h_top, h_bot ! Distances from the top or bottom [H ~> m or kg m-2].
7575
real :: dz_h_int ! The ratio of the vertical distances across the layers surrounding an interface
76-
! over the layer thicknesses [H Z-1 ~> nonodim or kg m-3]
76+
! over the layer thicknesses [H Z-1 ~> nondim or kg m-3]
7777
real :: ustar ! The local friction velocity [Z T-1 ~> m s-1]
7878
real :: absf ! The absolute value of the Coriolis parameter [T-1 ~> s-1]
7979
real :: htot ! The sum of the thicknesses [H ~> m or kg m-2].

0 commit comments

Comments
 (0)