FV3 Bundle
Ellison.f90
Go to the documentation of this file.
1 !
2 ! Ellison Ocean Permittivity module.
3 !
4 ! Module containing routines to compute the complex permittivities for
5 ! sea water based on
6 !
7 ! Ellison, W.J. et al. (2003) A comparison of ocean emissivity models
8 ! using the Advanced Microwave Sounding Unit, the Special Sensor
9 ! Microwave Imager, the TRMM Microwave Imager, and airborne radiometer
10 ! observations. Journal of Geophysical Research, v108, D21, Pages ACL 1,1-14
11 ! doi:10.1029/2002JD0032132
12 !
13 !
14 ! CREATION HISTORY:
15 ! Written by: Paul van Delst, 11-Apr-2007
16 ! paul.vandelst@noaa.gov
17 !
18 
19 MODULE ellison
20 
21  ! -----------------
22  ! Environment setup
23  ! -----------------
24  ! Module use
25  USE type_kinds, ONLY: fp
26  USE fundamental_constants, ONLY: pi, &
27  e0 => permittivity, & ! Permittivity of vacuum (F/m)
28  k_to_c => standard_temperature ! Temperature units conversion
29  ! Disable implicit typing
30  IMPLICIT NONE
31 
32 
33  ! ------------
34  ! Visibilities
35  ! ------------
36  PRIVATE
37  ! ... Datatypes
38  PUBLIC :: ivar_type
39  ! ... Procedures
43 
44 
45  ! -----------------
46  ! Module parameters
47  ! -----------------
48  CHARACTER(*), PARAMETER :: module_version_id = &
49  '$Id: Ellison.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
50  REAL(fp), PARAMETER :: zero = 0.0_fp
51  REAL(fp), PARAMETER :: point5 = 0.5_fp
52  REAL(fp), PARAMETER :: one = 1.0_fp
53  REAL(fp), PARAMETER :: two = 2.0_fp
54  REAL(fp), PARAMETER :: three = 3.0_fp
55  REAL(fp), PARAMETER :: four = 4.0_fp
56  REAL(fp), PARAMETER :: five = 5.0_fp
57  REAL(fp), PARAMETER :: twopi = two*pi
58 
59 
60  ! Scaling factors (used here for documenting the conversion
61  ! to SI units of the double Debye model denominator)
62  ! ---------------------------------------------------------
63  REAL(fp), PARAMETER :: ps_to_s = 1.0e-12_fp ! Picoseconds -> Seconds
64  REAL(fp), PARAMETER :: ghz_to_hz = 1.0e+09_fp ! Gigahertz -> Hertz
65  REAL(fp), PARAMETER :: scale_factor = ps_to_s * ghz_to_hz
66 
67 
68  ! Parameters for the Ellison et al (2003) permittivity model
69  ! ----------------------------------------------------------
70  ! The coefficients used to fit the Double Debye model
71  REAL(fp), PARAMETER :: tau1_coeff(0:2) = (/ 17.535_fp, &
72  -0.61767_fp, &
73  0.0089481_fp /)
74  REAL(fp), PARAMETER :: tau2_coeff(0:3) = (/ 3.1842_fp, &
75  0.019189_fp, &
76  -0.010873_fp, &
77  0.00025818_fp /)
78  REAL(fp), PARAMETER :: delta1_coeff(0:3) = (/ 68.396_fp, &
79  -0.40643_fp, &
80  0.022832_fp, &
81  -0.00053061_fp /)
82  REAL(fp), PARAMETER :: delta2_coeff(0:3) = (/ 4.7629_fp, &
83  0.1541_fp, &
84  -0.033717_fp, &
85  0.00084428_fp /)
86  REAL(fp), PARAMETER :: einf_coeff(0:1) = (/ 5.31250_fp, &
87  -0.0114770_fp /)
88  REAL(fp), PARAMETER :: sigma_coeff(0:1) = (/ 2.906_fp, &
89  0.09437_fp /)
90 
91 
92  ! --------------------------------------
93  ! Structure definition to hold forward
94  ! variables across FWD, TL, and AD calls
95  ! --------------------------------------
96  TYPE :: ivar_type
97  PRIVATE
98  REAL(fp) :: t=zero ! Temperature in degC
99  REAL(fp) :: f=zero, f2=zero, f0=zero ! Frequency terms
100  REAL(fp) :: tau1=zero , tau2=zero ! Relaxation frequencies
101  REAL(fp) :: delta1=zero, delta2=zero ! Delta terms
102  REAL(fp) :: d1=zero , d2=zero ! Denominator terms
103  END TYPE ivar_type
104 
105 
106 CONTAINS
107 
108 
109 !################################################################################
110 !################################################################################
111 !## ##
112 !## ## PUBLIC MODULE ROUTINES ## ##
113 !## ##
114 !################################################################################
115 !################################################################################
116 
117 !--------------------------------------------------------------------------------
118 !:sdoc+:
119 !
120 ! NAME:
121 ! Ellison_Ocean_Permittivity
122 !
123 ! PURPOSE:
124 ! Subroutine to compute ocean permittivity according to the reference,
125 ! Ellison, W.J. et al. (2003) A comparison of ocean emissivity models
126 ! using the Advanced Microwave Sounding Unit, the Special Sensor
127 ! Microwave Imager, the TRMM Microwave Imager, and airborne radiometer
128 ! observations. Journal of Geophysical Research, v108, D21, ACL 1,1-14
129 ! doi:10.1029/2002JD0032132
130 !
131 ! CALLING SEQUENCE:
132 ! CALL Ellison_Ocean_Permittivity( Temperature , & ! Input
133 ! Frequency , & ! Input
134 ! Permittivity, & ! Output
135 ! iVar ) ! Internal variable output
136 !
137 ! INPUTS:
138 ! Temperature: Sea surface temperature
139 ! UNITS: Kelvin (K)
140 ! TYPE: REAL(fp)
141 ! DIMENSION: Scalar
142 ! ATTRIBUTES: INTENT(IN)
143 !
144 ! Frequency: Frequency
145 ! UNITS: GHz
146 ! TYPE: REAL(fp)
147 ! DIMENSION: Scalar
148 ! ATTRIBUTES: INTENT(IN)
149 !
150 ! OUTPUTS:
151 ! Permittivity: Ocean permittivity
152 ! UNITS: N/A
153 ! TYPE: COMPLEX(fp)
154 ! DIMENSION: Scalar
155 ! ATTRIBUTES: INTENT(OUT)
156 !
157 ! iVar: Structure containing internal variables required for
158 ! subsequent tangent-linear or adjoint model calls.
159 ! The contents of this structure are NOT accessible
160 ! outside of this module.
161 ! UNITS: N/A
162 ! TYPE: TYPE(iVar_type)
163 ! DIMENSION: Scalar
164 ! ATTRIBUTES: INTENT(OUT)
165 !
166 ! COMMENTS:
167 ! There is currently no salinity dependence.
168 !:sdoc-:
169 !--------------------------------------------------------------------------------
170 
171  SUBROUTINE ellison_ocean_permittivity( &
172  Temperature , & ! Input
173  Frequency , & ! Input
174  Permittivity, & ! Output
175  iVar ) ! Internal variable output
176  ! Arguments
177  REAL(fp), INTENT(IN) :: temperature
178  REAL(fp), INTENT(IN) :: frequency
179  COMPLEX(fp), INTENT(OUT) :: permittivity
180  TYPE(ivar_type), INTENT(IN OUT) :: ivar
181  ! Local variables
182  REAL(fp) :: einf
183  REAL(fp) :: re1, re2
184  REAL(fp) :: ie1, ie2
185  REAL(fp) :: sigma, iesigma
186  REAL(fp) :: re, ie
187 
188 
189  ! Compute the various polynomial components of the double Debye model
190  ! -------------------------------------------------------------------
191  ! Compute temperature value for polynomials
192  ivar%t = temperature - k_to_c
193 
194  ! Compute the Debye model relaxation frequencies
195  ! (eqn on pg ACL 1-4 of Ellison et al. 2003)
196  ivar%tau1 = tau1_coeff(0) + ivar%t*(tau1_coeff(1) + &
197  ivar%t*tau1_coeff(2))
198  ivar%tau2 = tau2_coeff(0) + ivar%t*(tau2_coeff(1) + &
199  ivar%t*(tau2_coeff(2) + &
200  ivar%t*tau2_coeff(3)))
201 
202  ! Compute the delta terms
203  ! (eqn on pg ACL 1-4 of Ellison et al. 2003)
204  ivar%delta1 = delta1_coeff(0) + ivar%t*(delta1_coeff(1) + &
205  ivar%t*(delta1_coeff(2) + &
206  ivar%t*delta1_coeff(3)))
207  ivar%delta2 = delta2_coeff(0) + ivar%t*(delta2_coeff(1) + &
208  ivar%t*(delta2_coeff(2) + &
209  ivar%t*delta2_coeff(3)))
210 
211  ! Compute the "infinite" permittivity term
212  ! (No coeffs provided in ref. Taken from existing code)
213  einf = einf_coeff(0) + ivar%t*einf_coeff(1)
214 
215 
216  ! Compute the permittivities using the double Debye model
217  ! (eqn on pg ACL 1-3 of Ellison et al. 2003)
218  ! -------------------------------------------------------
219  ! The common frequency terms
220  ivar%f = twopi * frequency * scale_factor
221  ivar%f2 = ivar%f**2
222  ivar%f0 = twopi * frequency * ghz_to_hz * e0
223 
224  ! The denominators of the double Debye model
225  ivar%d1 = one + ivar%f2*ivar%tau1**2
226  ivar%d2 = one + ivar%f2*ivar%tau2**2
227 
228  ! The real parts of the "delta" terms
229  re1 = ivar%delta1 / ivar%d1
230  re2 = ivar%delta2 / ivar%d2
231 
232  ! The imaginary parts of the "delta" terms
233  ie1 = ivar%delta1 * ivar%f * ivar%tau1 / ivar%d1
234  ie2 = ivar%delta2 * ivar%f * ivar%tau2 / ivar%d2
235 
236  ! The conductivity term
237  sigma = sigma_coeff(0) + sigma_coeff(1)*ivar%t
238  iesigma = sigma / ivar%f0
239 
240  ! Construct the complex permittivity, e = e' - j.e"
241  re = re1 + re2 + einf
242  ie = ie1 + ie2 + iesigma
243  permittivity = cmplx(re, -ie, fp)
244 
245  END SUBROUTINE ellison_ocean_permittivity
246 
247 
248 !--------------------------------------------------------------------------------
249 !:sdoc+:
250 !
251 ! NAME:
252 ! Ellison_Ocean_Permittivity_TL
253 !
254 ! PURPOSE:
255 ! Subroutine to compute the tangent-linear ocean permittivity according
256 ! to the reference,
257 ! Ellison, W.J. et al. (2003) A comparison of ocean emissivity models
258 ! using the Advanced Microwave Sounding Unit, the Special Sensor
259 ! Microwave Imager, the TRMM Microwave Imager, and airborne radiometer
260 ! observations. Journal of Geophysical Research, v108, D21, ACL 1,1-14
261 ! doi:10.1029/2002JD0032132
262 !
263 ! CALLING SEQUENCE:
264 ! CALL Ellison_Ocean_Permittivity_TL( Temperature_TL , & ! Input
265 ! Permittivity_TL, & ! Output
266 ! iVar ) ! Internal variable input
267 !
268 ! INPUTS:
269 ! Temperature_TL: Tangent-linear sea surface temperature
270 ! UNITS: Kelvin (K)
271 ! TYPE: REAL(fp)
272 ! DIMENSION: Scalar
273 ! ATTRIBUTES: INTENT(IN)
274 !
275 ! iVar: Structure containing internal variables required for
276 ! subsequent tangent-linear or adjoint model calls.
277 ! The contents of this structure are NOT accessible
278 ! outside of this module.
279 ! UNITS: N/A
280 ! TYPE: TYPE(iVar_type)
281 ! DIMENSION: Scalar
282 ! ATTRIBUTES: INTENT(IN)
283 !
284 ! OUTPUTS:
285 ! Permittivity_TL: Tangent-linear ocean permittivity
286 ! UNITS: N/A
287 ! TYPE: COMPLEX(fp)
288 ! DIMENSION: Scalar
289 ! ATTRIBUTES: INTENT(OUT)
290 !
291 ! COMMENTS:
292 ! There is currently no salinity dependence.
293 !:sdoc-:
294 !--------------------------------------------------------------------------------
295 
296  SUBROUTINE ellison_ocean_permittivity_tl( &
297  Temperature_TL , & ! Input
298  Permittivity_TL, & ! Output
299  iVar ) ! Internal variable input
300  ! Arguments
301  REAL(fp), INTENT(IN) :: temperature_tl
302  COMPLEX(fp), INTENT(OUT) :: permittivity_tl
303  TYPE(ivar_type), INTENT(IN) :: ivar
304  ! Local variables
305  REAL(fp) :: t_tl
306  REAL(fp) :: tau1_tl, tau2_tl
307  REAL(fp) :: delta1_tl, delta2_tl, einf_tl
308  REAL(fp) :: d1_tl, d2_tl
309  REAL(fp) :: d12, d22
310  REAL(fp) :: re1_tl, re2_tl
311  REAL(fp) :: ie1_tl, ie2_tl
312  REAL(fp) :: sigma_tl, iesigma_tl
313  REAL(fp) :: re_tl, ie_tl
314 
315 
316  ! Compute the tangent-linear for of the various
317  ! polynomial components of the double Debye model
318  ! -----------------------------------------------
319  ! Compute temperature value for polynomials
320  t_tl = temperature_tl
321 
322  ! Compute the tangent-linear Debye model relaxation frequencies
323  ! (eqn on pg ACL 1-4 of Ellison et al. 2003)
324  tau1_tl = (tau1_coeff(1) + ivar%t*two*tau1_coeff(2)) * t_tl
325  tau2_tl = (tau2_coeff(1) + ivar%t*(two*tau2_coeff(2) + ivar%t*three*tau2_coeff(3))) * t_tl
326 
327  ! Compute the tangent-linear delta terms
328  ! (eqn on pg ACL 1-4 of Ellison et al. 2003)
329  delta1_tl = (delta1_coeff(1) + ivar%t*(two*delta1_coeff(2) + ivar%t*three*delta1_coeff(3))) * t_tl
330  delta2_tl = (delta2_coeff(1) + ivar%t*(two*delta2_coeff(2) + ivar%t*three*delta2_coeff(3))) * t_tl
331 
332  ! Compute the tangent-liner "infinite" permittivity term
333  ! (No coeffs provided in ref. Taken from existing code)
334  einf_tl = einf_coeff(1) * t_tl
335 
336 
337  ! Compute the tangent-linear permittivities
338  ! using the double Debye model
339  ! (eqn on pg ACL 1-3 of Ellison et al. 2003)
340  ! ------------------------------------------
341  ! The tangent-linear denominators of the double Debye model
342  d1_tl = two*ivar%f2*ivar%tau1*tau1_tl
343  d2_tl = two*ivar%f2*ivar%tau2*tau2_tl
344 
345  ! The tangent-linear real parts of the "delta" terms
346  d12 = ivar%d1**2
347  d22 = ivar%d2**2
348  re1_tl = (ivar%d1*delta1_tl - ivar%delta1*d1_tl) / d12
349  re2_tl = (ivar%d2*delta2_tl - ivar%delta2*d2_tl) / d22
350 
351  ! The tangent-linear imaginary parts of the "delta" terms
352  ie1_tl = ivar%f * (delta1_tl*ivar%tau1*ivar%d1 + ivar%delta1*tau1_tl*ivar%d1 - ivar%delta1*ivar%tau1*d1_tl) / d12
353  ie2_tl = ivar%f * (delta2_tl*ivar%tau2*ivar%d2 + ivar%delta2*tau2_tl*ivar%d2 - ivar%delta2*ivar%tau2*d2_tl) / d22
354 
355  ! The conductivity term
356  sigma_tl = sigma_coeff(1)*t_tl
357  iesigma_tl = sigma_tl / ivar%f0
358 
359  ! Construct the complex permittivity, de = de' - j.de"
360  re_tl = re1_tl + re2_tl + einf_tl
361  ie_tl = ie1_tl + ie2_tl + iesigma_tl
362  permittivity_tl = cmplx(re_tl, -ie_tl, fp)
363 
364  END SUBROUTINE ellison_ocean_permittivity_tl
365 
366 
367 !--------------------------------------------------------------------------------
368 !:sdoc+:
369 !
370 ! NAME:
371 ! Ellison_Ocean_Permittivity_AD
372 !
373 ! PURPOSE:
374 ! Subroutine to compute the adjoint ocean permittivity according
375 ! to the reference,
376 ! Ellison, W.J. et al. (2003) A comparison of ocean emissivity models
377 ! using the Advanced Microwave Sounding Unit, the Special Sensor
378 ! Microwave Imager, the TRMM Microwave Imager, and airborne radiometer
379 ! observations. Journal of Geophysical Research, v108, D21, ACL 1,1-14
380 ! doi:10.1029/2002JD0032132
381 !
382 ! CALLING SEQUENCE:
383 ! CALL Ellison_Ocean_Permittivity_AD( Permittivity_AD, & ! Input
384 ! Temperature_AD , & ! Output
385 ! iVar ) ! Internal variable input
386 !
387 ! INPUTS:
388 ! Permittivity_AD: Adjoint ocean permittivity
389 ! UNITS: N/A
390 ! TYPE: COMPLEX(fp)
391 ! DIMENSION: Scalar
392 ! ATTRIBUTES: INTENT(IN OUT)
393 !
394 ! iVar: Structure containing internal variables required for
395 ! subsequent tangent-linear or adjoint model calls.
396 ! The contents of this structure are NOT accessible
397 ! outside of this module.
398 ! UNITS: N/A
399 ! TYPE: TYPE(iVar_type)
400 ! DIMENSION: Scalar
401 ! ATTRIBUTES: INTENT(IN)
402 !
403 ! OUTPUTS:
404 ! Temperature_AD: Adjoint sea surface temperature, de/dT.
405 ! UNITS: per Kelvin (K^-1)
406 ! TYPE: REAL(fp)
407 ! DIMENSION: Scalar
408 ! ATTRIBUTES: INTENT(IN OUT)
409 !
410 ! SIDE EFFECTS:
411 ! The input adjoint variable, Permittivity_AD, is set to zero upon
412 ! exiting this routine.
413 !
414 ! COMMENTS:
415 ! There is currently no salinity dependence.
416 !
417 !:sdoc-:
418 !--------------------------------------------------------------------------------
419 
420  SUBROUTINE ellison_ocean_permittivity_ad( &
421  Permittivity_AD, & ! Input
422  Temperature_AD , & ! Output
423  iVar ) ! Internal variable input
424  ! Arguments
425  COMPLEX(fp), INTENT(IN OUT) :: permittivity_ad
426  REAL(fp), INTENT(IN OUT) :: temperature_ad
427  TYPE(ivar_type), INTENT(IN) :: ivar
428  ! Local variables
429  REAL(fp) :: t_ad
430  REAL(fp) :: tau1_ad, tau2_ad
431  REAL(fp) :: delta1_ad, delta2_ad, einf_ad
432  REAL(fp) :: d1_ad, d2_ad
433  REAL(fp) :: d12, d22
434  REAL(fp) :: m1 , m2
435  REAL(fp) :: re1_ad, re2_ad
436  REAL(fp) :: ie1_ad, ie2_ad
437  REAL(fp) :: sigma_ad, iesigma_ad
438  REAL(fp) :: re_ad, ie_ad
439 
440  ! Compute the adjoint of the permittivities
441  ! using the double Debye model
442  ! (eqn on pg ACL 1-3 of Ellison et al. 2003)
443  ! ------------------------------------------
444  ! The complex permittivity
445  ie_ad = -aimag(permittivity_ad)
446  re_ad = REAL(permittivity_ad,fp)
447  permittivity_ad = zero
448 
449  ! Initialise all the local adjoint variables
450  iesigma_ad = ie_ad; ie2_ad = ie_ad; ie1_ad = ie_ad
451  einf_ad = re_ad; re2_ad = re_ad; re1_ad = re_ad
452 
453  ! The adjoint of the conductivity term
454  sigma_ad = iesigma_ad / ivar%f0
455  t_ad = sigma_coeff(1)*sigma_ad
456 
457  ! The adjoints of the imaginary parts of the "delta" terms
458  d22 = ivar%d2**2; m2 = ivar%f / d22
459  d12 = ivar%d1**2; m1 = ivar%f / d12
460 
461  d2_ad = -(ivar%delta2 * ivar%tau2 * m2 * ie2_ad )
462  tau2_ad = ivar%delta2 * ivar%d2 * m2 * ie2_ad
463  delta2_ad = ivar%tau2 * ivar%d2 * m2 * ie2_ad
464 
465  d1_ad = -(ivar%delta1 * ivar%tau1 * m1 * ie1_ad )
466  tau1_ad = ivar%delta1 * ivar%d1 * m1 * ie1_ad
467  delta1_ad = ivar%tau1 * ivar%d1 * m1 * ie1_ad
468 
469  ! The adjoints of the real parts of the "delta" terms
470  d2_ad = d2_ad - (re2_ad * ivar%delta2 / d22)
471  delta2_ad = delta2_ad + (re2_ad / ivar%d2)
472 
473  d1_ad = d1_ad - (re1_ad * ivar%delta1 / d12)
474  delta1_ad = delta1_ad + (re1_ad / ivar%d1)
475 
476  ! The adjoints of the denominators of the double Debye model
477  tau2_ad = tau2_ad + (two * ivar%f2 * ivar%tau2 * d2_ad)
478  tau1_ad = tau1_ad + (two * ivar%f2 * ivar%tau1 * d1_ad)
479 
480 
481  ! Compute the adjoints of the various
482  ! polynomial components of the double Debye model
483  ! -----------------------------------------------
484  ! Compute the adjoint of the "infinite" permittivity term
485  ! (No coeffs provided in ref. Taken from existing code)
486  t_ad = t_ad + einf_coeff(1) * einf_ad
487 
488  ! Compute the adjoint of the delta terms
489  ! (eqn on pg ACL 1-4 of Ellison et al. 2003)
490  t_ad = t_ad + (delta2_coeff(1) + ivar%t*(two*delta2_coeff(2) + &
491  ivar%t*three*delta2_coeff(3)) ) * delta2_ad
492  t_ad = t_ad + (delta1_coeff(1) + ivar%t*(two*delta1_coeff(2) + &
493  ivar%t*three*delta1_coeff(3)) ) * delta1_ad
494 
495  ! Compute the adjoint of the Debye model relaxation frequencies
496  ! (eqn on pg ACL 1-4 of Ellison et al. 2003)
497  t_ad = t_ad + (tau2_coeff(1) + ivar%t*(two*tau2_coeff(2) + &
498  ivar%t*three*tau2_coeff(3)) ) * tau2_ad
499  t_ad = t_ad + (tau1_coeff(1) + ivar%t*two*tau1_coeff(2)) * tau1_ad
500 
501  ! The return value
502  temperature_ad = temperature_ad + t_ad
503 
504  END SUBROUTINE ellison_ocean_permittivity_ad
505 
506 END MODULE ellison
real(fp), dimension(0:2), parameter tau1_coeff
Definition: Ellison.f90:71
real(fp), parameter point5
Definition: Ellison.f90:51
subroutine, public ellison_ocean_permittivity(Temperature, Frequency, Permittivity, iVar)
Definition: Ellison.f90:176
real(fp), parameter two
Definition: Ellison.f90:53
integer, parameter, public fp
Definition: Type_Kinds.f90:124
real(fp), parameter, public pi
real(fp), parameter ghz_to_hz
Definition: Ellison.f90:64
real(fp), parameter zero
Definition: Ellison.f90:50
character(*), parameter module_version_id
Definition: Ellison.f90:48
real(fp), parameter ps_to_s
Definition: Ellison.f90:63
real(fp), dimension(0:1), parameter sigma_coeff
Definition: Ellison.f90:88
real(fp), parameter four
Definition: Ellison.f90:55
real(fp), dimension(0:3), parameter delta2_coeff
Definition: Ellison.f90:82
real(fp), parameter three
Definition: Ellison.f90:54
subroutine, public ellison_ocean_permittivity_tl(Temperature_TL, Permittivity_TL, iVar)
Definition: Ellison.f90:300
real(fp), dimension(0:3), parameter delta1_coeff
Definition: Ellison.f90:78
real(fp), parameter one
Definition: Ellison.f90:52
real(fp), parameter five
Definition: Ellison.f90:56
real(fp), dimension(0:3), parameter tau2_coeff
Definition: Ellison.f90:74
real(fp), dimension(0:1), parameter einf_coeff
Definition: Ellison.f90:86
real(fp), parameter twopi
Definition: Ellison.f90:57
real(fp), parameter, public permittivity
subroutine, public ellison_ocean_permittivity_ad(Permittivity_AD, Temperature_AD, iVar)
Definition: Ellison.f90:424
real(fp), parameter scale_factor
Definition: Ellison.f90:65