MOM6
MOM_EOS_TEOS10.F90
1 !> The equation of state using the TEOS10 expressions
3 
4 ! This file is part of MOM6. See LICENSE.md for the license.
5 
6 !***********************************************************************
7 !* The subroutines in this file implement the equation of state for *
8 !* sea water using the TEOS10 functions *
9 !***********************************************************************
10 
11 use gsw_mod_toolbox, only : gsw_sp_from_sr, gsw_pt_from_ct
12 use gsw_mod_toolbox, only : gsw_rho, gsw_specvol
13 use gsw_mod_toolbox, only : gsw_rho_first_derivatives, gsw_specvol_first_derivatives
14 use gsw_mod_toolbox, only : gsw_rho_second_derivatives
15 !use gsw_mod_toolbox, only : gsw_sr_from_sp, gsw_ct_from_pt
16 
17 implicit none ; private
18 
19 public calculate_compress_teos10, calculate_density_teos10, calculate_spec_vol_teos10
21 public calculate_specvol_derivs_teos10
23 public gsw_sp_from_sr, gsw_pt_from_ct
24 
25 !> Compute the in situ density of sea water ([kg m-3]), or its anomaly with respect to
26 !! a reference density, from absolute salinity (g/kg), conservative temperature (in deg C),
27 !! and pressure [Pa], using the TEOS10 expressions.
29  module procedure calculate_density_scalar_teos10, calculate_density_array_teos10
30 end interface calculate_density_teos10
31 
32 !> Compute the in situ specific volume of sea water (in [m3 kg-1]), or an anomaly with respect
33 !! to a reference specific volume, from absolute salinity (in g/kg), conservative temperature
34 !! (in deg C), and pressure [Pa], using the TEOS10 expressions.
36  module procedure calculate_spec_vol_scalar_teos10, calculate_spec_vol_array_teos10
37 end interface calculate_spec_vol_teos10
38 
39 !> For a given thermodynamic state, return the derivatives of density with conservative temperature
40 !! and absolute salinity, using the TEOS10 expressions.
42  module procedure calculate_density_derivs_scalar_teos10, calculate_density_derivs_array_teos10
44 
45 !> For a given thermodynamic state, return the second derivatives of density with various combinations
46 !! of conservative temperature, absolute salinity, and pressure, using the TEOS10 expressions.
48  module procedure calculate_density_second_derivs_scalar_teos10, calculate_density_second_derivs_array_teos10
50 
51 real, parameter :: pa2db = 1.e-4 !< The conversion factor from Pa to dbar.
52 
53 contains
54 
55 !> This subroutine computes the in situ density of sea water (rho in
56 !! [kg m-3]) from absolute salinity (S [g kg-1]), conservative temperature
57 !! (T [degC]), and pressure [Pa]. It uses the expression from the
58 !! TEOS10 website.
59 subroutine calculate_density_scalar_teos10(T, S, pressure, rho, rho_ref)
60  real, intent(in) :: T !< Conservative temperature [degC].
61  real, intent(in) :: S !< Absolute salinity [g kg-1].
62  real, intent(in) :: pressure !< pressure [Pa].
63  real, intent(out) :: rho !< In situ density [kg m-3].
64  real, optional, intent(in) :: rho_ref !< A reference density [kg m-3].
65 
66  ! Local variables
67  real, dimension(1) :: T0, S0, pressure0
68  real, dimension(1) :: rho0
69 
70  t0(1) = t
71  s0(1) = s
72  pressure0(1) = pressure
73 
74  call calculate_density_array_teos10(t0, s0, pressure0, rho0, 1, 1, rho_ref)
75  rho = rho0(1)
76 
77 end subroutine calculate_density_scalar_teos10
78 
79 !> This subroutine computes the in situ density of sea water (rho in
80 !! [kg m-3]) from absolute salinity (S [g kg-1]), conservative temperature
81 !! (T [degC]), and pressure [Pa]. It uses the expression from the
82 !! TEOS10 website.
83 subroutine calculate_density_array_teos10(T, S, pressure, rho, start, npts, rho_ref)
84  real, dimension(:), intent(in) :: T !< Conservative temperature [degC].
85  real, dimension(:), intent(in) :: S !< Absolute salinity [g kg-1]
86  real, dimension(:), intent(in) :: pressure !< pressure [Pa].
87  real, dimension(:), intent(out) :: rho !< in situ density [kg m-3].
88  integer, intent(in) :: start !< the starting point in the arrays.
89  integer, intent(in) :: npts !< the number of values to calculate.
90  real, optional, intent(in) :: rho_ref !< A reference density [kg m-3].
91 
92  ! Local variables
93  real :: zs, zt, zp
94  integer :: j
95 
96  do j=start,start+npts-1
97  !Conversions
98  zs = s(j) !gsw_sr_from_sp(S(j)) !Convert practical salinity to absolute salinity
99  zt = t(j) !gsw_ct_from_pt(S(j),T(j)) !Convert potantial temp to conservative temp
100  zp = pressure(j)* pa2db !Convert pressure from Pascal to decibar
101 
102  if (s(j) < -1.0e-10) then !Can we assume safely that this is a missing value?
103  rho(j) = 1000.0
104  else
105  rho(j) = gsw_rho(zs,zt,zp)
106  endif
107  if (present(rho_ref)) rho(j) = rho(j) - rho_ref
108  enddo
109 end subroutine calculate_density_array_teos10
110 
111 !> This subroutine computes the in situ specific volume of sea water (specvol in
112 !! [m3 kg-1]) from absolute salinity (S [g kg-1]), conservative temperature (T [degC])
113 !! and pressure [Pa], using the TEOS10 equation of state.
114 !! If spv_ref is present, specvol is an anomaly from spv_ref.
115 subroutine calculate_spec_vol_scalar_teos10(T, S, pressure, specvol, spv_ref)
116  real, intent(in) :: T !< Conservative temperature [degC].
117  real, intent(in) :: S !< Absolute salinity [g kg-1]
118  real, intent(in) :: pressure !< pressure [Pa].
119  real, intent(out) :: specvol !< in situ specific volume [m3 kg-1].
120  real, optional, intent(in) :: spv_ref !< A reference specific volume [m3 kg-1].
121 
122  ! Local variables
123  real, dimension(1) :: T0, S0, pressure0, spv0
124 
125  t0(1) = t ; s0(1) = s ; pressure0(1) = pressure
126 
127  call calculate_spec_vol_array_teos10(t0, s0, pressure0, spv0, 1, 1, spv_ref)
128  specvol = spv0(1)
129 end subroutine calculate_spec_vol_scalar_teos10
130 
131 
132 !> This subroutine computes the in situ specific volume of sea water (specvol in
133 !! [m3 kg-1]) from absolute salinity (S [g kg-1]), conservative temperature (T [degC])
134 !! and pressure [Pa], using the TEOS10 equation of state.
135 !! If spv_ref is present, specvol is an anomaly from spv_ref.
136 subroutine calculate_spec_vol_array_teos10(T, S, pressure, specvol, start, npts, spv_ref)
137  real, dimension(:), intent(in) :: T !< Conservative temperature relative to the surface
138  !! [degC].
139  real, dimension(:), intent(in) :: S !< salinity [g kg-1].
140  real, dimension(:), intent(in) :: pressure !< pressure [Pa].
141  real, dimension(:), intent(out) :: specvol !< in situ specific volume [m3 kg-1].
142  integer, intent(in) :: start !< the starting point in the arrays.
143  integer, intent(in) :: npts !< the number of values to calculate.
144  real, optional, intent(in) :: spv_ref !< A reference specific volume [m3 kg-1].
145 
146  ! Local variables
147  real :: zs, zt, zp
148  integer :: j
149 
150  do j=start,start+npts-1
151  !Conversions
152  zs = s(j) !gsw_sr_from_sp(S(j)) !Convert practical salinity to absolute salinity
153  zt = t(j) !gsw_ct_from_pt(S(j),T(j)) !Convert potantial temp to conservative temp
154  zp = pressure(j)* pa2db !Convert pressure from Pascal to decibar
155 
156  if (s(j) < -1.0e-10) then
157  specvol(j) = 0.001 !Can we assume safely that this is a missing value?
158  else
159  specvol(j) = gsw_specvol(zs,zt,zp)
160  endif
161  if (present(spv_ref)) specvol(j) = specvol(j) - spv_ref
162  enddo
163 
164 end subroutine calculate_spec_vol_array_teos10
165 
166 !> For a given thermodynamic state, calculate the derivatives of density with conservative
167 !! temperature and absolute salinity, using the TEOS10 expressions.
168 subroutine calculate_density_derivs_array_teos10(T, S, pressure, drho_dT, drho_dS, start, npts)
169  real, intent(in), dimension(:) :: T !< Conservative temperature [degC].
170  real, intent(in), dimension(:) :: S !< Absolute salinity [g kg-1].
171  real, intent(in), dimension(:) :: pressure !< pressure [Pa].
172  real, intent(out), dimension(:) :: drho_dT !< The partial derivative of density with conservative
173  !! temperature [kg m-3 degC-1].
174  real, intent(out), dimension(:) :: drho_dS !< The partial derivative of density with absolute salinity,
175  !! [kg m-3 (g/kg)-1].
176  integer, intent(in) :: start !< The starting point in the arrays.
177  integer, intent(in) :: npts !< The number of values to calculate.
178 
179  ! Local variables
180  real :: zs, zt, zp
181  integer :: j
182 
183  do j=start,start+npts-1
184  !Conversions
185  zs = s(j) !gsw_sr_from_sp(S(j)) !Convert practical salinity to absolute salinity
186  zt = t(j) !gsw_ct_from_pt(S(j),T(j)) !Convert potantial temp to conservative temp
187  zp = pressure(j)* pa2db !Convert pressure from Pascal to decibar
188  if (s(j) < -1.0e-10) then ; !Can we assume safely that this is a missing value?
189  drho_dt(j) = 0.0 ; drho_ds(j) = 0.0
190  else
191  call gsw_rho_first_derivatives(zs, zt, zp, drho_dsa=drho_ds(j), drho_dct=drho_dt(j))
192  endif
193  enddo
194 
195 end subroutine calculate_density_derivs_array_teos10
196 
197 !> For a given thermodynamic state, calculate the derivatives of density with conservative
198 !! temperature and absolute salinity, using the TEOS10 expressions.
199 subroutine calculate_density_derivs_scalar_teos10(T, S, pressure, drho_dT, drho_dS)
200  real, intent(in) :: T !< Conservative temperature [degC]
201  real, intent(in) :: S !< Absolute Salinity [g kg-1]
202  real, intent(in) :: pressure !< pressure [Pa].
203  real, intent(out) :: drho_dT !< The partial derivative of density with conservative
204  !! temperature [kg m-3 degC-1].
205  real, intent(out) :: drho_dS !< The partial derivative of density with absolute salinity,
206  !! [kg m-3 (g/kg)-1].
207 
208  ! Local variables
209  real :: zs, zt, zp
210  !Conversions
211  zs = s !gsw_sr_from_sp(S) !Convert practical salinity to absolute salinity
212  zt = t !gsw_ct_from_pt(S,T) !Convert potantial temp to conservative temp
213  zp = pressure* pa2db !Convert pressure from Pascal to decibar
214  if (s < -1.0e-10) return !Can we assume safely that this is a missing value?
215  call gsw_rho_first_derivatives(zs, zt, zp, drho_dsa=drho_ds, drho_dct=drho_dt)
216 end subroutine calculate_density_derivs_scalar_teos10
217 
218 !> For a given thermodynamic state, calculate the derivatives of specific volume with conservative
219 !! temperature and absolute salinity, using the TEOS10 expressions.
220 subroutine calculate_specvol_derivs_teos10(T, S, pressure, dSV_dT, dSV_dS, start, npts)
221  real, intent(in), dimension(:) :: t !< Conservative temperature [degC].
222  real, intent(in), dimension(:) :: s !< Absolute salinity [g kg-1].
223  real, intent(in), dimension(:) :: pressure !< pressure [Pa].
224  real, intent(out), dimension(:) :: dsv_dt !< The partial derivative of specific volume with
225  !! conservative temperature [m3 kg-1 degC-1].
226  real, intent(out), dimension(:) :: dsv_ds !< The partial derivative of specific volume with
227  !! absolute salinity [m3 kg-1 (g/kg)-1].
228  integer, intent(in) :: start !< The starting point in the arrays.
229  integer, intent(in) :: npts !< The number of values to calculate.
230 
231  ! Local variables
232  real :: zs, zt, zp
233  integer :: j
234 
235  do j=start,start+npts-1
236  !Conversions
237  zs = s(j) !gsw_sr_from_sp(S(j)) !Convert practical salinity to absolute salinity
238  zt = t(j) !gsw_ct_from_pt(S(j),T(j)) !Convert potantial temp to conservative temp
239  zp = pressure(j)* pa2db !Convert pressure from Pascal to decibar
240  if (s(j) < -1.0e-10) then ; !Can we assume safely that this is a missing value?
241  dsv_dt(j) = 0.0 ; dsv_ds(j) = 0.0
242  else
243  call gsw_specvol_first_derivatives(zs,zt,zp, v_sa=dsv_ds(j), v_ct=dsv_dt(j))
244  endif
245  enddo
246 
247 end subroutine calculate_specvol_derivs_teos10
248 
249 !> Calculate the 5 second derivatives of the equation of state for scalar inputs
250 subroutine calculate_density_second_derivs_scalar_teos10(T, S, pressure, drho_dS_dS, drho_dS_dT, &
251  drho_dT_dT, drho_dS_dP, drho_dT_dP)
252  real, intent(in) :: T !< Conservative temperature [degC]
253  real, intent(in) :: S !< Absolute Salinity [g kg-1]
254  real, intent(in) :: pressure !< pressure [Pa].
255  real, intent(out) :: drho_dS_dS !< Partial derivative of beta with respect to S
256  real, intent(out) :: drho_dS_dT !< Partial derivative of beta with resepct to T
257  real, intent(out) :: drho_dT_dT !< Partial derivative of alpha with respect to T
258  real, intent(out) :: drho_dS_dP !< Partial derivative of beta with respect to pressure
259  real, intent(out) :: drho_dT_dP !< Partial derivative of alpha with respect to pressure
260 
261  ! Local variables
262  real :: zs, zt, zp
263 
264  !Conversions
265  zs = s !gsw_sr_from_sp(S) !Convert practical salinity to absolute salinity
266  zt = t !gsw_ct_from_pt(S,T) !Convert potantial temp to conservative temp
267  zp = pressure* pa2db !Convert pressure from Pascal to decibar
268  if (s < -1.0e-10) return !Can we assume safely that this is a missing value?
269  call gsw_rho_second_derivatives(zs, zt, zp, rho_sa_sa=drho_ds_ds, rho_sa_ct=drho_ds_dt, &
270  rho_ct_ct=drho_dt_dt, rho_sa_p=drho_ds_dp, rho_ct_p=drho_dt_dp)
271 
272 end subroutine calculate_density_second_derivs_scalar_teos10
273 
274 !> Calculate the 5 second derivatives of the equation of state for scalar inputs
275 subroutine calculate_density_second_derivs_array_teos10(T, S, pressure, drho_dS_dS, drho_dS_dT, &
276  drho_dT_dT, drho_dS_dP, drho_dT_dP, start, npts)
277  real, dimension(:), intent(in) :: T !< Conservative temperature [degC]
278  real, dimension(:), intent(in) :: S !< Absolute Salinity [g kg-1]
279  real, dimension(:), intent(in) :: pressure !< pressure [Pa].
280  real, dimension(:), intent(out) :: drho_dS_dS !< Partial derivative of beta with respect to S
281  real, dimension(:), intent(out) :: drho_dS_dT !< Partial derivative of beta with resepct to T
282  real, dimension(:), intent(out) :: drho_dT_dT !< Partial derivative of alpha with respect to T
283  real, dimension(:), intent(out) :: drho_dS_dP !< Partial derivative of beta with respect to pressure
284  real, dimension(:), intent(out) :: drho_dT_dP !< Partial derivative of alpha with respect to pressure
285  integer, intent(in) :: start !< The starting point in the arrays.
286  integer, intent(in) :: npts !< The number of values to calculate.
287 
288  ! Local variables
289  real :: zs, zt, zp
290  integer :: j
291 
292  do j=start,start+npts-1
293  !Conversions
294  zs = s(j) !gsw_sr_from_sp(S) !Convert practical salinity to absolute salinity
295  zt = t(j) !gsw_ct_from_pt(S,T) !Convert potantial temp to conservative temp
296  zp = pressure(j)* pa2db !Convert pressure from Pascal to decibar
297  if (s(j) < -1.0e-10) then ; !Can we assume safely that this is a missing value?
298  drho_ds_ds(j) = 0.0 ; drho_ds_dt(j) = 0.0 ; drho_dt_dt(j) = 0.0
299  drho_ds_dp(j) = 0.0 ; drho_dt_dp(j) = 0.0
300  else
301  call gsw_rho_second_derivatives(zs, zt, zp, rho_sa_sa=drho_ds_ds(j), rho_sa_ct=drho_ds_dt(j), &
302  rho_ct_ct=drho_dt_dt(j), rho_sa_p=drho_ds_dp(j), rho_ct_p=drho_dt_dp(j))
303  endif
304  enddo
305 
306 end subroutine calculate_density_second_derivs_array_teos10
307 
308 !> This subroutine computes the in situ density of sea water (rho in
309 !! [kg m-3]) and the compressibility (drho/dp = C_sound^-2)
310 !! (drho_dp [s2 m-2]) from absolute salinity (sal in g/kg),
311 !! conservative temperature (T [degC]), and pressure [Pa]. It uses the
312 !! subroutines from TEOS10 website
313 subroutine calculate_compress_teos10(T, S, pressure, rho, drho_dp, start, npts)
314  real, intent(in), dimension(:) :: t !< Conservative temperature [degC].
315  real, intent(in), dimension(:) :: s !< Absolute salinity [g kg-1].
316  real, intent(in), dimension(:) :: pressure !< Pressure [Pa].
317  real, intent(out), dimension(:) :: rho !< In situ density [kg m-3].
318  real, intent(out), dimension(:) :: drho_dp !< The partial derivative of density with pressure
319  !! (also the inverse of the square of sound speed)
320  !! [s2 m-2].
321  integer, intent(in) :: start !< The starting point in the arrays.
322  integer, intent(in) :: npts !< The number of values to calculate.
323 
324  ! Local variables
325  real :: zs,zt,zp
326  integer :: j
327 
328  do j=start,start+npts-1
329  !Conversions
330  zs = s(j) !gsw_sr_from_sp(S(j)) !Convert practical salinity to absolute salinity
331  zt = t(j) !gsw_ct_from_pt(S(j),T(j)) !Convert potantial temp to conservative temp
332  zp = pressure(j)* pa2db !Convert pressure from Pascal to decibar
333  if (s(j) < -1.0e-10) then ; !Can we assume safely that this is a missing value?
334  rho(j) = 1000.0 ; drho_dp(j) = 0.0
335  else
336  rho(j) = gsw_rho(zs,zt,zp)
337  call gsw_rho_first_derivatives(zs,zt,zp, drho_dp=drho_dp(j))
338  endif
339  enddo
340 end subroutine calculate_compress_teos10
341 
342 end module mom_eos_teos10
mom_eos_teos10::calculate_spec_vol_teos10
Compute the in situ specific volume of sea water (in [m3 kg-1]), or an anomaly with respect to a refe...
Definition: MOM_EOS_TEOS10.F90:35
mom_eos_teos10::calculate_density_teos10
Compute the in situ density of sea water ([kg m-3]), or its anomaly with respect to a reference densi...
Definition: MOM_EOS_TEOS10.F90:28
mom_eos_teos10
The equation of state using the TEOS10 expressions.
Definition: MOM_EOS_TEOS10.F90:2
mom_eos_teos10::calculate_density_second_derivs_teos10
For a given thermodynamic state, return the second derivatives of density with various combinations o...
Definition: MOM_EOS_TEOS10.F90:47
mom_eos_teos10::calculate_density_derivs_teos10
For a given thermodynamic state, return the derivatives of density with conservative temperature and ...
Definition: MOM_EOS_TEOS10.F90:41