@@ -34,8 +34,7 @@ module MOM_self_attr_load
34
34
real :: eta_prop
35
35
! < The partial derivative of eta_sal with the local value of eta [nondim].
36
36
real :: linear_scaling
37
- ! < A dimensional coefficient for scalar approximation SAL, equal to eta_prop * unit_convert
38
- ! ! [nondim or L2 Z-1 T-2 ~> m s-2 or R-1 ~> m3 kg-1 or L2 Z-1 T-2 R-1 ~> m4 s-2 kg-1]
37
+ ! < Dimensional coefficients for scalar SAL [nondim or Z T2 L-2 R-1 ~> m Pa-1]
39
38
type (sht_CS), allocatable :: sht
40
39
! < Spherical harmonic transforms (SHT) control structure
41
40
integer :: sal_sht_Nd
@@ -44,7 +43,7 @@ module MOM_self_attr_load
44
43
! < Reference bottom pressure scaled by Rho_0 and G_Earth[Z ~> m]
45
44
real , allocatable :: Love_scaling(:)
46
45
! < Dimensional coefficients for harmonic SAL, which are functions of Love numbers
47
- ! ! [nondim or L2 Z-1 T-2 ~> m s -2 or R-1 ~> m3 kg-1 or L2 Z-1 T-2 R-1 ~> m4 s-2 kg -1]
46
+ ! ! [nondim or Z T2 L -2 R-1 ~> m Pa -1]
48
47
real , allocatable :: Snm_Re(:), & ! < Real SHT coefficient for SHT SAL [Z ~> m]
49
48
Snm_Im(:) ! < Imaginary SHT coefficient for SHT SAL [Z ~> m]
50
49
end type SAL_CS
@@ -56,24 +55,22 @@ module MOM_self_attr_load
56
55
! > This subroutine calculates seawater self-attraction and loading based on either sea surface height (SSH) or bottom
57
56
! ! pressure anomaly. Note that the SAL calculation applies to all motions across the spectrum. Tidal-specific methods
58
57
! ! that assume periodicity, i.e. iterative and read-in SAL, are stored in MOM_tidal_forcing module.
59
- ! ! The input field is always assume to have the unit of [Z ~> m], which can be either SSH or total bottom pressure
60
- ! ! scaled by mean seawater density Rho_0 and earth gravity G_Earth. For spherical harmonics, the mean seawater density
61
- ! ! would be cancelled by the same parameter in Love number scalings. If total bottom pressure is used as input, bottom
62
- ! ! pressure anomaly is calculated in the subroutine by subtracting a reference pressure from the input bottom pressure.
58
+ ! ! The input field can be either SSH [Z ~> m] or total bottom pressure [R L2 T-2 ~> Pa]. If total bottom pressure is
59
+ ! ! used, bottom pressure anomaly is first calculated by subtracting a reference bottom pressure from an input file.
63
60
! ! The output field is expressed as geopotential height anomaly, and therefore has the unit of [Z ~> m].
64
61
subroutine calc_SAL (eta , eta_sal , G , CS , tmp_scale )
65
- type (ocean_grid_type), intent (in ) :: G ! < The ocean's grid structure.
62
+ type (ocean_grid_type), intent (in ) :: G ! < The ocean's grid structure.
66
63
real , dimension (SZI_(G),SZJ_(G)), intent (in ) :: eta ! < The sea surface height anomaly from
67
- ! ! a time-mean geoid or total bottom pressure scaled by mean density and earth gravity [Z ~> m ].
64
+ ! ! a time-mean geoid or total bottom pressure [Z ~> m] or [R L2 T-2 ~> Pa ].
68
65
real , dimension (SZI_(G),SZJ_(G)), intent (out ) :: eta_sal ! < The geopotential height anomaly from
69
66
! ! self-attraction and loading [Z ~> m].
70
67
type (SAL_CS), intent (inout ) :: CS ! < The control structure returned by a previous call to SAL_init.
71
68
real , optional , intent (in ) :: tmp_scale ! < A rescaling factor to temporarily convert eta
72
69
! ! to MKS units in reproducing sumes [m Z-1 ~> 1]
73
70
74
71
! Local variables
72
+ real , dimension (SZI_(G),SZJ_(G)) :: bpa ! SSH or bottom pressure anomaly [Z ~> m or R L2 T-2 ~> Pa]
75
73
integer :: n, m, l
76
- real , dimension (SZI_(G),SZJ_(G)) :: bpa ! [Z ~> m]
77
74
integer :: Isq, Ieq, Jsq, Jeq
78
75
integer :: i, j
79
76
@@ -90,7 +87,7 @@ subroutine calc_SAL(eta, eta_sal, G, CS, tmp_scale)
90
87
! use the scalar approximation and/or iterative tidal SAL
91
88
if (CS% use_sal_scalar .or. CS% use_tidal_sal_prev) then
92
89
do j= Jsq,Jeq+1 ; do i= Isq,Ieq+1
93
- eta_sal(i,j) = CS% eta_prop * bpa(i,j)
90
+ eta_sal(i,j) = CS% linear_scaling * bpa(i,j)
94
91
enddo ; enddo
95
92
96
93
! use the spherical harmonics method
@@ -132,21 +129,21 @@ end subroutine scalar_SAL_sensitivity
132
129
! > This subroutine calculates coefficients of the spherical harmonic modes for self-attraction and loading.
133
130
! ! The algorithm is based on the SAL implementation in MPAS-ocean, which was modified by Kristin Barton from
134
131
! ! routine written by K. Quinn (March 2010) and modified by M. Schindelegger (May 2017).
135
- subroutine calc_love_scaling (nlm , rhoW , rhoE , Love_scaling )
136
- integer , intent (in ) :: nlm ! < Maximum spherical harmonics degree [nondim]
137
- real , intent (in ) :: rhoW ! < The average density of sea water [R ~> kg m-3]
138
- real , intent (in ) :: rhoE ! < The average density of Earth [R ~> kg m-3]
139
- real , dimension (:), intent (out ) :: Love_scaling ! < Scaling factors for inverse spherical harmonic
140
- ! ! transforms [nondim]
132
+ subroutine calc_love_scaling (rhoW , rhoE , grav , CS )
133
+ real , intent (in ) :: rhoW ! < The average density of sea water [R ~> kg m-3]
134
+ real , intent (in ) :: rhoE ! < The average density of Earth [R ~> kg m-3]
135
+ real , intent (in ) :: grav ! < The gravitational acceleration [L2 Z-1 T-2 ~> m s-2]
136
+ type (SAL_CS), intent (inout ) :: CS ! < The control structure returned by a previous call to SAL_init.
141
137
142
138
! Local variables
143
139
real , dimension (:), allocatable :: HDat, LDat, KDat ! Love numbers converted in CF reference frames [nondim]
144
140
real :: H1, L1, K1 ! Temporary variables to store degree 1 Love numbers [nondim]
145
- integer :: n_tot ! Size of the stored Love numbers
141
+ integer :: n_tot ! Size of the stored Love numbers [nondim]
142
+ integer :: nlm ! Maximum spherical harmonics degree [nondim]
146
143
integer :: n, m, l
147
- real :: unit
148
144
149
145
n_tot = size (Love_Data, dim= 2 )
146
+ nlm = CS% sal_sht_Nd
150
147
151
148
if (nlm+1 > n_tot) call MOM_error(FATAL, " MOM_tidal_forcing " // &
152
149
" calc_love_scaling: maximum spherical harmonics degree is larger than " // &
@@ -165,7 +162,11 @@ subroutine calc_love_scaling(nlm, rhoW, rhoE, Love_scaling)
165
162
166
163
do m= 0 ,nlm ; do n= m,nlm
167
164
l = order2index(m,nlm)
168
- Love_scaling(l+ n- m) = (3.0 / real (2 * n+1 )) * (rhoW / rhoE) * (1.0 + KDat(n+1 ) - HDat(n+1 ))
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
169
170
enddo ; enddo
170
171
end subroutine calc_love_scaling
171
172
@@ -184,14 +185,12 @@ subroutine SAL_init(G, GV, US, param_file, CS)
184
185
real :: rhoE ! The average density of Earth [R ~> kg m-3].
185
186
character (len= 200 ) :: filename, ebot_ref_file, inputdir ! Strings for file/path
186
187
character (len= 200 ) :: ebot_ref_varname ! Variable name in file
187
- real :: I_g_rho ! The inverse of the density times the gravitational acceleration [Z T2 L-2 R-1 ~> m Pa-1]
188
188
logical :: calculate_sal= .false.
189
189
logical :: tides= .false. , use_tidal_sal_file= .false. , bq_sal_tides_bug= .false.
190
190
integer :: tides_answer_date= 99991203 ! Recover old answers with tides
191
191
real :: sal_scalar_value, tide_sal_scalar_value ! Scaling SAL factors [nondim]
192
-
193
192
integer :: isd, ied, jsd, jed
194
- integer :: i, j
193
+
195
194
isd = G% isd ; ied = G% ied ; jsd = G% jsd ; jed = G% jed
196
195
197
196
! Read all relevant parameters and write them to the model log.
@@ -230,10 +229,6 @@ subroutine SAL_init(G, GV, US, param_file, CS)
230
229
allocate (CS% ebot_ref(isd:ied, jsd:jed), source= 0.0 )
231
230
call MOM_read_data(filename, trim (ebot_ref_varname), CS% ebot_ref, G% Domain,&
232
231
scale= US% Pa_to_RL2_T2)
233
- I_g_rho = 1.0 / (GV% g_Earth * GV% Rho0)
234
- do j= jsd,jed ; do i= isd,ied
235
- CS% ebot_ref(i,j) = CS% ebot_ref(i,j) * I_g_rho
236
- enddo ; enddo
237
232
call pass_var(CS% ebot_ref, G% Domain)
238
233
endif
239
234
if (tides_answer_date<= 20230630 .and. CS% use_bpa) &
@@ -242,9 +237,9 @@ subroutine SAL_init(G, GV, US, param_file, CS)
242
237
call get_param(param_file, mdl, " SAL_SCALAR_APPROX" , CS% use_sal_scalar, &
243
238
" If true, use the scalar approximation to calculate self-attraction and " // &
244
239
" loading." , default= tides .and. (.not. use_tidal_sal_file))
245
- ! if (CS%use_sal_scalar .and. CS%use_bpa) &
246
- ! call MOM_error(WARNING, trim(mdl) // ", SAL_init: Using bottom pressure anomaly for scalar "//&
247
- ! "approximation SAL is unsubstantiated.")
240
+ if (CS% use_sal_scalar .and. CS% use_bpa) &
241
+ call MOM_error(WARNING, trim (mdl) // " , SAL_init: Using bottom pressure anomaly for scalar " // &
242
+ " approximation SAL is unsubstantiated." )
248
243
call get_param(param_file, ' ' , " TIDE_SAL_SCALAR_VALUE" , tide_sal_scalar_value, &
249
244
units= " m m-1" , default= 0.0 , do_not_log= .True. )
250
245
if (tide_sal_scalar_value/= 0.0 ) &
@@ -270,22 +265,29 @@ subroutine SAL_init(G, GV, US, param_file, CS)
270
265
default= 5517.0 , scale= US% kg_m3_to_R, do_not_log= (.not. CS% use_sal_sht))
271
266
272
267
! Set scaling coefficients for scalar approximation
273
- if (CS% use_sal_scalar .and. CS% use_tidal_sal_prev) then
274
- CS% eta_prop = 2.0 * sal_scalar_value
275
- elseif (CS% use_sal_scalar .or. CS% use_tidal_sal_prev) then
276
- CS% eta_prop = sal_scalar_value
268
+ if (CS% use_sal_scalar .or. CS% use_tidal_sal_prev) then
269
+ if (CS% use_sal_scalar .and. CS% use_tidal_sal_prev) then
270
+ CS% eta_prop = 2.0 * sal_scalar_value
271
+ else
272
+ CS% eta_prop = sal_scalar_value
273
+ endif
274
+ if (CS% use_bpa) then
275
+ CS% linear_scaling = CS% eta_prop / (GV% Rho0 * GV% g_Earth)
276
+ else
277
+ CS% linear_scaling = CS% eta_prop
278
+ endif
277
279
else
278
- CS% eta_prop = 0.0
280
+ CS% eta_prop = 0.0 ; CS % linear_scaling = 0.0
279
281
endif
280
282
281
283
! Set scaling coefficients for spherical harmonics
282
284
if (CS% use_sal_sht) then
283
285
lmax = calc_lmax(CS% sal_sht_Nd)
284
- allocate (CS% Snm_Re(lmax)); CS % Snm_Re(:) = 0.0
285
- allocate (CS% Snm_Im(lmax)); CS % Snm_Im(:) = 0.0
286
+ allocate (CS% Snm_Re(lmax), source = 0.0 )
287
+ allocate (CS% Snm_Im(lmax), source = 0.0 )
286
288
287
- allocate (CS% Love_scaling(lmax)); CS % Love_scaling(:) = 0.0
288
- call calc_love_scaling(CS % sal_sht_Nd, GV% Rho0, rhoE, CS % Love_scaling )
289
+ allocate (CS% Love_scaling(lmax), source = 0.0 )
290
+ call calc_love_scaling(GV% Rho0, rhoE, GV % g_Earth, CS )
289
291
290
292
allocate (CS% sht)
291
293
call spherical_harmonics_init(G, param_file, CS% sht)
0 commit comments