FV3 Bundle
Liu.f90
Go to the documentation of this file.
1 !
2 ! Liu Ocean Permittivity module.
3 !
4 ! Module containing routines to compute the complex permittivities for
5 ! sea water based on
6 !
7 ! Liu, Q. et al. (2010) An improved fast microwave water emissivity model.
8 ! IEEE Trans. Geosci. Remote Sensing, accepted June 25, 2010
9 !
10 !
11 ! CREATION HISTORY:
12 ! Written by: Quanhua (Mark) Liu, JCSDA 30-Jul-2009
13 ! Quanhua.Liu@noaa.gov
14 
15 MODULE liu
16 
17  ! -----------------
18  ! Environment setup
19  ! -----------------
20  ! Module use
21  USE type_kinds, ONLY: fp
22  USE fundamental_constants, ONLY: pi, &
23  e0 => permittivity, & ! Permittivity of vacuum (F/m)
24  k_to_c => standard_temperature ! Temperature units conversion
25  ! Disable implicit typing
26  IMPLICIT NONE
27 
28 
29  ! ------------
30  ! Visibilities
31  ! ------------
32  PRIVATE
33  ! ... Datatypes
34  PUBLIC :: ivar_type
35  ! ... Procedures
36  PUBLIC :: liu_ocean_permittivity
39 
40 
41  ! -----------------
42  ! Module parameters
43  ! -----------------
44  CHARACTER(*), PARAMETER :: module_version_id = &
45  '$Id: Liu.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
46 
47  ! Literal constants
48  ! -----------------
49  REAL(fp), PARAMETER :: zero = 0.0_fp
50  REAL(fp), PARAMETER :: one = 1.0_fp
51  REAL(fp), PARAMETER :: two = 2.0_fp
52  REAL(fp), PARAMETER :: three = 3.0_fp
53  REAL(fp), PARAMETER :: four = 4.0_fp
54 
55  ! Scaling factors
56  ! ---------------
57  REAL(fp), PARAMETER :: ghz_to_hz = 1.0e+09_fp ! Gigahertz -> Hertz
58 
59  ! Fixed value for ionic conductivity denominator term, scaled
60  ! for frequency. See the last term of eqn.(3) in reference.
61  ! -----------------------------------------------------------
62  REAL(fp), PARAMETER :: tau0 = two*pi*e0*ghz_to_hz
63 
64  ! Parameters for the Liu et al (2010) permittivity model
65  ! ------------------------------------------------------
66  ! The coefficients for the high-frequency permittivity temperature
67  ! polynomial. Eqn.(4a) in reference.
68  REAL(fp), PARAMETER :: einf_coeff(0:1) = (/ 3.8_fp, &
69  2.48033e-02_fp /)
70 
71  ! The coefficients for the static permittivity temperature
72  ! and salinity polynomials. Eqn.(4b) in reference.
73  REAL(fp), PARAMETER :: es_t_coeff(0:3) = (/ 87.9181727_fp , &
74  -4.031592248e-01_fp, &
75  9.493088010e-04_fp, &
76  -1.930858348e-06_fp /)
77  REAL(fp), PARAMETER :: es_s_coeff(0:2) = (/-2.697e-03_fp, &
78  -7.3e-06_fp , &
79  -8.9e-06_fp /)
80 
81  ! The coefficients for the intermediate frequency permittivity
82  ! temperature and salinity polynomials. Eqn.(4c) in reference.
83  REAL(fp), PARAMETER :: e1_t_coeff(0:2) = (/ 5.723_fp , &
84  2.2379e-02_fp, &
85  -7.1237e-04_fp /)
86  REAL(fp), PARAMETER :: e1_s_coeff(0:2) = (/-6.28908e-03_fp, &
87  1.76032e-04_fp, &
88  -9.22144e-05_fp /)
89 
90  ! The coefficients for the relaxation time temperature and
91  ! salinity polynomials. Eqns.(4e) and (4f) in reference.
92  REAL(fp), PARAMETER :: tau1_t_coeff(0:3) = (/ 1.124465e-01_fp , &
93  -3.9815727e-03_fp, &
94  8.113381e-05_fp , &
95  -7.1824242e-07_fp /)
96  REAL(fp), PARAMETER :: tau1_s_coeff(0:2) = (/-2.39357e-03_fp, &
97  3.1353e-05_fp , &
98  -2.52477e-07_fp /)
99 
100  REAL(fp), PARAMETER :: tau2_t_coeff(0:3) = (/ 3.049979018e-03_fp, &
101  -3.010041629e-05_fp, &
102  4.811910733e-06_fp, &
103  -4.259775841e-08_fp /)
104  REAL(fp), PARAMETER :: tau2_s_coeff(0:2) = (/ 1.49e-01_fp, &
105  -8.8e-04_fp , &
106  -1.05e-04_fp /)
107 
108  ! The coefficients for the ionic conductivity exponential.
109  ! Eqn.(4g) in reference.
110  REAL(fp), PARAMETER :: alpha_coeff = -4.259775841e-08_fp
111 
112  ! The coefficients for the ionic conductivity exponent term
113  ! polynomial. Eqn.(4i) in reference.
114  REAL(fp), PARAMETER :: beta_coeff(0:5) = (/ 2.033e-02_fp, &
115  1.266e-04_fp, &
116  2.464e-06_fp, &
117  -1.849e-05_fp, &
118  2.551e-07_fp, &
119  -2.551e-08_fp /)
120 
121  ! The coefficients for the ionic conductivity at 25C polynomial.
122  ! Eqn.(4j) in reference.
123  REAL(fp), PARAMETER :: alpha25_coeff(0:3) = (/ 1.82521e-01_fp, &
124  -1.46192e-03_fp, &
125  2.09324e-05_fp, &
126  -1.28205e-07_fp /)
127 
128 
129  ! --------------------------------------
130  ! Structure definition to hold forward
131  ! variables across FWD, TL, and AD calls
132  ! --------------------------------------
133  TYPE :: ivar_type
134  PRIVATE
135  REAL(fp) :: t=zero ! Temperature in deg.C
136  REAL(fp) :: s=zero ! Salinity
137  REAL(fp) :: delta=zero, beta=zero ! Ionic conductivity components
138  REAL(fp) :: alpha25=zero, alpha=zero ! Ionic conductivity terms
139  REAL(fp) :: es_t=zero, es_s=zero ! The temperature and salinity es terms
140  REAL(fp) :: e1_t=zero, e1_s=zero ! The temperature and salinity e1 terms
141  REAL(fp) :: tau1_t=zero, tau1_s=zero ! The temperature and salinity tau1 terms
142  REAL(fp) :: tau2_t=zero, tau2_s=zero ! The temperature and salinity tau2 terms
143  REAL(fp) :: f1=zero, f2=zero ! The relaxation compound terms, f.tau
144  REAL(fp) :: del1=zero, del2=zero ! The permittivity differences
145  END TYPE ivar_type
146 
147 
148 CONTAINS
149 
150 
151 !--------------------------------------------------------------------------------
152 !:sdoc+:
153 !
154 ! NAME:
155 ! Liu_Ocean_Permittivity
156 !
157 ! PURPOSE:
158 ! Subroutine to compute ocean permittivity according to the reference,
159 ! Liu, Q. et al. (2010) An improved fast microwave water emissivity model.
160 ! IEEE Trans. Geosci. Remote Sensing, accepted June 25, 2010
161 !
162 ! CALLING SEQUENCE:
163 ! CALL Liu_Ocean_Permittivity( Temperature , & ! Input
164 ! Salinity , & ! Input
165 ! Frequency , & ! Input
166 ! Permittivity, & ! Output
167 ! iVar ) ! Internal variable output
168 !
169 ! INPUTS:
170 ! Temperature: Sea surface temperature
171 ! UNITS: Kelvin (K)
172 ! TYPE: REAL(fp)
173 ! DIMENSION: Scalar
174 ! ATTRIBUTES: INTENT(IN)
175 !
176 ! Salinity: Water salinity
177 ! UNITS: ppt (parts per thousand)
178 ! TYPE: REAL(fp)
179 ! DIMENSION: Scalar
180 ! ATTRIBUTES: INTENT(IN)
181 !
182 ! Frequency: Frequency
183 ! UNITS: GHz
184 ! TYPE: REAL(fp)
185 ! DIMENSION: Scalar
186 ! ATTRIBUTES: INTENT(IN)
187 !
188 ! OUTPUTS:
189 ! Permittivity: Ocean permittivity
190 ! UNITS: N/A
191 ! TYPE: COMPLEX(fp)
192 ! DIMENSION: Scalar
193 ! ATTRIBUTES: INTENT(OUT)
194 !
195 ! iVar: Structure containing internal variables required for
196 ! subsequent tangent-linear or adjoint model calls.
197 ! The contents of this structure are NOT accessible
198 ! outside of this module.
199 ! UNITS: N/A
200 ! TYPE: TYPE(iVar_type)
201 ! DIMENSION: Scalar
202 ! ATTRIBUTES: INTENT(OUT)
203 !:sdoc-:
204 !--------------------------------------------------------------------------------
205 
206  SUBROUTINE liu_ocean_permittivity( &
207  Temperature , & ! Input
208  Salinity , & ! Input
209  Frequency , & ! Input
210  Permittivity, & ! Output
211  iVar ) ! Internal variable output
212  ! Arguments
213  REAL(fp), INTENT(IN) :: temperature
214  REAL(fp), INTENT(IN) :: salinity
215  REAL(fp), INTENT(IN) :: frequency
216  COMPLEX(fp), INTENT(OUT) :: permittivity
217  TYPE(ivar_type), INTENT(IN OUT) :: ivar
218  ! Local variables
219  REAL(fp) :: einf
220  REAL(fp) :: tau1, tau2, es, e1
221  REAL(fp) :: re, ie
222 
223  ! Setup
224  ! -----
225  ! ...Initialise imaginary component of result
226  ie = zero
227  ! ...Save the inputs
228  ivar%t = temperature - k_to_c
229  ivar%s = salinity
230 
231 
232  ! Compute the TEMPERATURE polynomial parameterisations
233  ! ----------------------------------------------------
234  ! ...The high-frequency permittivity temperature polynomial (eqn.4a)
235  einf = einf_coeff(0) + ivar%t*einf_coeff(1)
236  ! ...The static permittivity temperature polynomial (eqn.4b)
237  es = es_t_coeff(0) + ivar%t*(es_t_coeff(1) + &
238  ivar%t*(es_t_coeff(2) + &
239  ivar%t*es_t_coeff(3)))
240  ivar%es_t = es ! Save it
241  ! ...The intermediate frequency permittivity temperature polynomial (eqn.4c)
242  e1 = e1_t_coeff(0) + ivar%t*(e1_t_coeff(1) + &
243  ivar%t*e1_t_coeff(2))
244  ivar%e1_t = e1 ! Save it
245  ! ...The Debye relaxation time constants temperature polynomials (eqns.4e & 4f)
246  ! ...Units of tau: nanoseconds (for use with GHz frequencies)
247  tau1 = tau1_t_coeff(0) + ivar%t*(tau1_t_coeff(1) + &
248  ivar%t*(tau1_t_coeff(2) + &
249  ivar%t*tau1_t_coeff(3)))
250  ivar%tau1_t = tau1 ! Save it
251  tau2 = tau2_t_coeff(0) + ivar%t*(tau2_t_coeff(1) + &
252  ivar%t*(tau2_t_coeff(2) + &
253  ivar%t*tau2_t_coeff(3)))
254  ivar%tau2_t = tau2 ! Save it
255 
256 
257  ! Compute the SALINITY polynomial parameterisations
258  ! -------------------------------------------------
259  IF ( ivar%s > zero ) THEN
260  ! ...The temperature difference from 25C (eqn.4h) used to compute ionic conductivity.
261  ivar%delta = 25.0_fp - ivar%t
262  ! ...The beta term (eqn.4i) used to compute ionic conductivity
263  ivar%beta = beta_coeff(0) + ivar%delta*(beta_coeff(1) + &
264  ivar%delta*beta_coeff(2)) + &
265  (beta_coeff(3) + ivar%delta*(beta_coeff(4) + &
266  ivar%delta*beta_coeff(5)))*ivar%S
267  ! ...The ionic conductivity at 25C (eqn.4j)
268  ivar%alpha25 = ivar%s*(alpha25_coeff(0) + &
269  ivar%s*(alpha25_coeff(1) + &
270  ivar%s*(alpha25_coeff(2) + &
271  ivar%s*alpha25_coeff(3))))
272  ! ...The ionic conductivity (eqn.4g)
273  ivar%alpha = ivar%alpha25*exp(-ivar%delta*ivar%beta)
274  ! ...The imaginary component dependent on ionic conductivity (eqn.3)
275  ie = -ivar%alpha/(frequency*tau0)
276 
277 
278  ! ...The static permittivity salinity polynomial (eqn.4b)
279  ivar%es_s = one + ivar%s*(es_s_coeff(0) + ivar%s*es_s_coeff(1) + ivar%t*es_s_coeff(2))
280  es = es * ivar%es_s
281 
282 
283  ! ...The intermediate frequency permittivity salinity polynomial (eqn.4c)
284  ivar%e1_s = one + ivar%s*(e1_s_coeff(0) + ivar%s*e1_s_coeff(1) + ivar%t*e1_s_coeff(2))
285  e1 = e1 * ivar%e1_s
286 
287 
288  ! ...The Debye relaxation time constants salinity polynomials (eqns.4e & 4f)
289  ! ...Units of tau: nanoseconds (for use with GHz frequencies)
290  ivar%tau1_s = one + ivar%s*(tau1_s_coeff(0) + ivar%t*(tau1_s_coeff(1) + &
291  ivar%t*tau1_s_coeff(2)))
292  tau1 = tau1 * ivar%tau1_s
293  ivar%tau2_s = one + ivar%s*(tau2_s_coeff(0) + ivar%t*tau2_s_coeff(1) + &
294  (ivar%s**2)*tau2_s_coeff(2))
295  tau2 = tau2 * ivar%tau2_s
296 
297  END IF
298 
299 
300  ! Compute the complex permittivity
301  ! --------------------------------
302  ! ...The compound terms
303  ivar%f1 = frequency*tau1 ! Note there is no GHz->Hz conversion.
304  ivar%f2 = frequency*tau2 ! That is embedded in the tau values.
305  ivar%del1 = es - e1
306  ivar%del2 = e1 - einf
307  ! ...The real part
308  re = einf + ivar%del1/(one + ivar%f1**2) + &
309  ivar%del2/(one + ivar%f2**2)
310  ! ...The imaginary part
311  ie = -ie + ivar%del1*ivar%f1/(one + ivar%f1**2) + &
312  ivar%del2*ivar%f2/(one + ivar%f2**2)
313  ! ...Combine them (e = re - j.ie)
314  permittivity = cmplx(re,-ie,fp)
315 
316  END SUBROUTINE liu_ocean_permittivity
317 
318 
319 !--------------------------------------------------------------------------------
320 !:sdoc+:
321 !
322 ! NAME:
323 ! Liu_Ocean_Permittivity_TL
324 !
325 ! PURPOSE:
326 ! Subroutine to compute the tangent-linear ocean permittivity according
327 ! to the model in the reference,
328 ! Liu, Q. et al. (2010) An improved fast microwave water emissivity model.
329 ! IEEE Trans. Geosci. Remote Sensing, accepted June 25, 2010
330 !
331 ! CALLING SEQUENCE:
332 ! CALL Liu_Ocean_Permittivity_TL( Temperature_TL , & ! TL Input
333 ! Salinity_TL , & ! TL Input
334 ! Frequency , & ! Invariant Input
335 ! Permittivity_TL, & ! TL Output
336 ! iVar ) ! Internal variable input
337 !
338 ! INPUTS:
339 ! Temperature_TL: Tangent-linear sea surface temperature.
340 ! UNITS: Kelvin (K)
341 ! TYPE: REAL(fp)
342 ! DIMENSION: Scalar
343 ! ATTRIBUTES: INTENT(IN)
344 !
345 ! Salinity_TL: Tangent-linear water salinity.
346 ! UNITS: ppt (parts per thousand)
347 ! TYPE: REAL(fp)
348 ! DIMENSION: Scalar
349 ! ATTRIBUTES: INTENT(IN)
350 !
351 ! Frequency: Frequency
352 ! UNITS: GHz
353 ! TYPE: REAL(fp)
354 ! DIMENSION: Scalar
355 ! ATTRIBUTES: INTENT(IN)
356 !
357 ! iVar: Structure containing internal variables required for
358 ! subsequent tangent-linear or adjoint model calls.
359 ! The contents of this structure are NOT accessible
360 ! outside of this module.
361 ! UNITS: N/A
362 ! TYPE: TYPE(iVar_type)
363 ! DIMENSION: Scalar
364 ! ATTRIBUTES: INTENT(IN)
365 !
366 ! OUTPUTS:
367 ! Permittivity_TL: Tangent-linear permittivity
368 ! UNITS: N/A
369 ! TYPE: COMPLEX(fp)
370 ! DIMENSION: Scalar
371 ! ATTRIBUTES: INTENT(OUT)
372 !:sdoc-:
373 !--------------------------------------------------------------------------------
374 
375  SUBROUTINE liu_ocean_permittivity_tl( &
376  Temperature_TL , & ! TL Input
377  Salinity_TL , & ! TL Input
378  Frequency , & ! Invariant input
379  Permittivity_TL, & ! TL Output
380  iVar ) ! Internal variable input
381  ! Arguments
382  REAL(fp), INTENT(IN) :: temperature_tl
383  REAL(fp), INTENT(IN) :: salinity_tl
384  REAL(fp), INTENT(IN) :: frequency
385  COMPLEX(fp), INTENT(OUT) :: permittivity_tl
386  TYPE(ivar_type), INTENT(IN) :: ivar
387 
388  ! Local variables
389  REAL(fp) :: einf_tl
390  REAL(fp) :: es_s_tl, es_tl
391  REAL(fp) :: e1_s_tl, e1_tl
392  REAL(fp) :: tau1_s_tl, tau1_tl
393  REAL(fp) :: tau2_s_tl, tau2_tl
394  REAL(fp) :: delta_tl, beta_tl
395  REAL(fp) :: alpha25_tl, alpha_tl
396  REAL(fp) :: f1_tl, f2_tl, del1_tl, del2_tl
397  REAL(fp) :: x1, x2
398  REAL(fp) :: re_tl, ie_tl
399 
400 
401  ! Setup
402  ! -----
403  ! ...Initialise imaginary component of result
404  ie_tl = zero
405 
406 
407  ! Compute the tangent-linear TEMPERATURE polynomial parameterisations
408  ! -------------------------------------------------------------------
409  ! ...The high-frequency permittivity temperature polynomial (eqn.4a)
410  einf_tl = einf_coeff(1)*temperature_tl
411  ! ...The static permittivity temperature polynomial (eqn.4b)
412  es_tl = (es_t_coeff(1) + ivar%t*(two*es_t_coeff(2) + &
413  ivar%t*three*es_t_coeff(3))) * temperature_tl
414  ! ...The intermediate frequency permittivity temperature polynomial (eqn.4c)
415  e1_tl = (e1_t_coeff(1) + ivar%t*two*e1_t_coeff(2)) * temperature_tl
416  ! ...The Debye relaxation time constants temperature polynomials (eqns.4e & 4f)
417  ! ...Units of tau: nanoseconds (for use with GHz frequencies)
418  tau1_tl = (tau1_t_coeff(1) + ivar%t*(two*tau1_t_coeff(2) + &
419  ivar%t*three*tau1_t_coeff(3))) * temperature_tl
420  tau2_tl = (tau2_t_coeff(1) + ivar%t*(two*tau2_t_coeff(2) + &
421  ivar%t*three*tau2_t_coeff(3))) * temperature_tl
422 
423 
424  ! Compute the SALINITY polynomial parameterisations
425  ! -------------------------------------------------
426  IF ( ivar%s > zero ) THEN
427  ! ...The temperature difference from 25C (eqn.4h) used to compute ionic conductivity.
428  delta_tl = -temperature_tl
429  ! ...The beta term (eqn.4i) used to compute ionic conductivity
430  beta_tl = (beta_coeff(1) + ivar%delta*two*beta_coeff(2) + &
431  ivar%s*(beta_coeff(4) + ivar%delta*two*beta_coeff(5)))*delta_tl + &
432  (beta_coeff(3) + ivar%delta*(beta_coeff(4) + &
433  ivar%delta*beta_coeff(5)))*salinity_tl
434  ! ...The ionic conductivity at 25C (eqn.4j)
435  alpha25_tl = (alpha25_coeff(0) + &
436  ivar%s*(two*alpha25_coeff(1) + &
437  ivar%s*(three*alpha25_coeff(2) + &
438  ivar%s*four*alpha25_coeff(3))))*salinity_tl
439  ! ...The ionic conductivity (eqn.4g)
440  alpha_tl = (alpha25_tl/ivar%alpha25 - ivar%delta*beta_tl - ivar%beta*delta_tl)*ivar%alpha
441  ! ...The imaginary component dependent on ionic conductivity (eqn.3)
442  ie_tl = -alpha_tl/(frequency*tau0)
443 
444 
445  ! ...The static permittivity salinity polynomial (eqn.4b)
446  es_s_tl = (es_s_coeff(0) + ivar%s*two*es_s_coeff(1) + ivar%t*es_s_coeff(2))*salinity_tl + &
447  ivar%s*es_s_coeff(2)*temperature_tl
448  es_tl = ivar%es_t*es_s_tl + ivar%es_s*es_tl
449 
450 
451  ! ...The intermediate frequency permittivity salinity polynomial (eqn.4c)
452  e1_s_tl = (e1_s_coeff(0) + ivar%s*two*e1_s_coeff(1) + ivar%t*e1_s_coeff(2))*salinity_tl + &
453  ivar%s*e1_s_coeff(2)*temperature_tl
454  e1_tl = ivar%e1_t*e1_s_tl + ivar%e1_s*e1_tl
455 
456 
457  ! ...The Debye relaxation time constants salinity polynomials (eqns.4e & 4f)
458  ! ...Units of tau: nanoseconds (for use with GHz frequencies)
459  tau1_s_tl = (tau1_s_coeff(0) + ivar%t*(tau1_s_coeff(1) + &
460  ivar%t*tau1_s_coeff(2)))*salinity_tl + &
461  ivar%s*(tau1_s_coeff(1) + ivar%t*two*tau1_s_coeff(2))*temperature_tl
462  tau1_tl = ivar%tau1_t*tau1_s_tl + ivar%tau1_s*tau1_tl
463 
464  tau2_s_tl = (tau2_s_coeff(0) + ivar%t*tau2_s_coeff(1) + &
465  (ivar%s**2)*three*tau2_s_coeff(2))*salinity_tl + &
466  ivar%s*tau2_s_coeff(1)*temperature_tl
467  tau2_tl = ivar%tau2_t*tau2_s_tl + ivar%tau2_s*tau2_tl
468 
469  END IF
470 
471 
472  ! Compute the complex permittivity
473  ! --------------------------------
474  ! ...The compound terms
475  f1_tl = frequency*tau1_tl ! Note there is no GHz->Hz conversion.
476  f2_tl = frequency*tau2_tl ! That is embedded in the tau values.
477  del1_tl = es_tl - e1_tl
478  del2_tl = e1_tl - einf_tl
479  ! ...Calculate the denominator terms
480  x1 = one + ivar%f1**2
481  x2 = one + ivar%f2**2
482  ! ...The real part
483  re_tl = einf_tl + &
484  (x1*del1_tl - ivar%del1*ivar%f1*two*f1_tl)/x1**2 + &
485  (x2*del2_tl - ivar%del2*ivar%f2*two*f2_tl)/x2**2
486  ! ...The imaginary part
487  ie_tl = ivar%f1*del1_tl/x1 + &
488  ivar%del1*(one - ivar%f1**2)*f1_tl/x1**2 + &
489  ivar%f2*del2_tl/x2 + &
490  ivar%del2*(one - ivar%f2**2)*f2_tl/x2**2 - &
491  ie_tl
492  ! ...Combine them (e = re - j.ie)
493  permittivity_tl = cmplx(re_tl,-ie_tl,fp)
494 
495  END SUBROUTINE liu_ocean_permittivity_tl
496 
497 
498 !--------------------------------------------------------------------------------
499 !:sdoc+:
500 !
501 ! NAME:
502 ! Liu_Ocean_Permittivity_AD
503 !
504 ! PURPOSE:
505 ! Subroutine to compute the ocean permittivity adjoint according to the
506 ! model in the reference,
507 ! Liu, Q. et al. (2010) An improved fast microwave water emissivity model.
508 ! IEEE Trans. Geosci. Remote Sensing, accepted June 25, 2010
509 !
510 ! CALLING SEQUENCE:
511 ! CALL Liu_Ocean_Permittivity_AD( Permittivity_AD, & ! AD Input
512 ! Frequency , & ! Invariant Input
513 ! Temperature_AD , & ! AD Output
514 ! Salinity_AD , & ! AD Output
515 ! iVar ) ! Internal variable input
516 !
517 ! INPUTS:
518 ! Permittivity_AD: Adjoint ocean permittivity
519 ! *** SET TO ZERO UPON EXIT ***
520 ! UNITS: N/A
521 ! TYPE: COMPLEX(fp)
522 ! DIMENSION: Scalar
523 ! ATTRIBUTES: INTENT(IN OUT)
524 !
525 ! Frequency: Frequency
526 ! UNITS: GHz
527 ! TYPE: REAL(fp)
528 ! DIMENSION: Scalar
529 ! ATTRIBUTES: INTENT(IN)
530 !
531 ! iVar: Structure containing internal variables required for
532 ! subsequent tangent-linear or adjoint model calls.
533 ! The contents of this structure are NOT accessible
534 ! outside of this module.
535 ! UNITS: N/A
536 ! TYPE: TYPE(iVar_type)
537 ! DIMENSION: Scalar
538 ! ATTRIBUTES: INTENT(IN)
539 !
540 ! OUTPUTS:
541 ! Temperature_AD: Adjoint sea surface temperature, de/dT.
542 ! *** MUST HAVE VALUE UPON ENTRY ***
543 ! UNITS: per Kelvin (K^-1)
544 ! TYPE: REAL(fp)
545 ! DIMENSION: Scalar
546 ! ATTRIBUTES: INTENT(IN OUT)
547 !
548 ! Salinity_AD: Adjoint water salinity, de/dS
549 ! *** MUST HAVE VALUE UPON ENTRY ***
550 ! UNITS: per ppt (parts-per-thousand^-1)
551 ! TYPE: REAL(fp)
552 ! DIMENSION: Scalar
553 ! ATTRIBUTES: INTENT(IN OUT)
554 !
555 ! SIDE EFFECTS:
556 ! The input adjoint variable, Permittivity_AD, is set to zero upon
557 ! exiting this routine.
558 !
559 !:sdoc-:
560 !--------------------------------------------------------------------------------
561 
562  SUBROUTINE liu_ocean_permittivity_ad( &
563  Permittivity_AD, & ! AD Input
564  Frequency , & ! Invariant Input
565  Temperature_AD , & ! AD Output
566  Salinity_AD , & ! AD Output
567  iVar ) ! Internal variable input
568  IMPLICIT NONE
569  ! Arguments
570  COMPLEX(fp), INTENT(IN OUT) :: permittivity_ad
571  REAL(fp), INTENT(IN) :: frequency
572  REAL(fp), INTENT(IN OUT) :: temperature_ad
573  REAL(fp), INTENT(IN OUT) :: salinity_ad
574  TYPE(ivar_type), INTENT(IN) :: ivar
575  ! Local variables
576  REAL(fp) :: re_ad, ie_ad
577  REAL(fp) :: x1, x2
578  REAL(fp) :: f1_ad, f2_ad, del1_ad, del2_ad
579  REAL(fp) :: delta_ad, beta_ad
580  REAL(fp) :: alpha25_ad, alpha_ad
581  REAL(fp) :: tau1_s_ad, tau1_ad
582  REAL(fp) :: tau2_s_ad, tau2_ad
583  REAL(fp) :: einf_ad
584  REAL(fp) :: es_s_ad, es_ad
585  REAL(fp) :: e1_s_ad, e1_ad
586 
587 
588  ! Complex permittivity
589  ! --------------------
590  ! ...Separate the real and imaginary parts
591  ie_ad = -aimag(permittivity_ad)
592  re_ad = REAL(permittivity_ad, fp)
593  permittivity_ad = zero
594  ! ...Calculate the denominator terms
595  x1 = one + ivar%f1**2
596  x2 = one + ivar%f2**2
597  ! ...The imaginary part
598  f2_ad = ivar%del2*(one - ivar%f2**2)*ie_ad/x2**2
599  del2_ad = ivar%f2*ie_ad/x2
600  f1_ad = ivar%del1*(one - ivar%f1**2)*ie_ad/x1**2
601  del1_ad = ivar%f1*ie_ad/x1
602  ie_ad = -ie_ad
603  ! ...The real part
604  f2_ad = f2_ad - (ivar%del2*ivar%f2*two*re_ad)/x2**2
605  del2_ad = del2_ad + re_ad/x2
606  f1_ad = f1_ad - (ivar%del1*ivar%f1*two*re_ad)/x1**2
607  del1_ad = del1_ad + re_ad/x1
608  einf_ad = re_ad
609  ! ...The compound terms
610  einf_ad = einf_ad - del2_ad
611  e1_ad = del2_ad
612  e1_ad = e1_ad - del1_ad
613  es_ad = del1_ad
614  tau2_ad = frequency*f2_ad
615  tau1_ad = frequency*f1_ad
616 
617 
618  ! Compute the SALINITY polynomial parameterisations
619  ! -------------------------------------------------
620  IF ( ivar%s > zero ) THEN
621  ! ...The Debye relaxation time constants salinity polynomials (eqns.4e & 4f)
622  ! ...Units of tau: nanoseconds (for use with GHz frequencies)
623  tau2_s_ad = ivar%tau2_t*tau2_ad
624  tau2_ad = ivar%tau2_s*tau2_ad
625  salinity_ad = salinity_ad + &
626  (tau2_s_coeff(0) + ivar%t*tau2_s_coeff(1) + &
627  (ivar%s**2)*three*tau2_s_coeff(2))*tau2_s_ad
628  temperature_ad = temperature_ad + &
629  ivar%s*tau2_s_coeff(1)*tau2_s_ad
630 
631  tau1_s_ad = ivar%tau1_t*tau1_ad
632  tau1_ad = ivar%tau1_s*tau1_ad
633  salinity_ad = salinity_ad + &
634  (tau1_s_coeff(0) + ivar%t*(tau1_s_coeff(1) + &
635  ivar%t*tau1_s_coeff(2)))*tau1_s_ad
636  temperature_ad = temperature_ad + &
637  ivar%s*(tau1_s_coeff(1) + ivar%t*two*tau1_s_coeff(2))*tau1_s_ad
638 
639 
640  ! ...The intermediate frequency permittivity salinity polynomial (eqn.4c)
641  e1_s_ad = ivar%e1_t*e1_ad
642  e1_ad = ivar%e1_s*e1_ad
643  salinity_ad = salinity_ad + &
644  (e1_s_coeff(0) + ivar%s*two*e1_s_coeff(1) + ivar%t*e1_s_coeff(2))*e1_s_ad
645  temperature_ad = temperature_ad + &
646  ivar%s*e1_s_coeff(2)*e1_s_ad
647 
648 
649  ! ...The static permittivity salinity polynomial (eqn.4b)
650  es_s_ad = ivar%es_t*es_ad
651  es_ad = ivar%es_s*es_ad
652  salinity_ad = salinity_ad + &
653  (es_s_coeff(0) + ivar%s*two*es_s_coeff(1) + ivar%t*es_s_coeff(2))*es_s_ad
654  temperature_ad = temperature_ad + &
655  ivar%s*es_s_coeff(2)*es_s_ad
656 
657 
658  ! ...The imaginary component dependent on ionic conductivity (eqn.3)
659  alpha_ad = -ie_ad/(frequency*tau0)
660  ! ...The ionic conductivity (eqn.4g)
661  alpha25_ad = ivar%alpha*alpha_ad/ivar%alpha25
662  beta_ad = -ivar%delta*ivar%alpha*alpha_ad
663  delta_ad = -ivar%beta*ivar%alpha*alpha_ad
664  ! ...The ionic conductivity at 25C (eqn.4j)
665  salinity_ad = salinity_ad + &
666  (alpha25_coeff(0) + &
667  ivar%s*(two*alpha25_coeff(1) + &
668  ivar%s*(three*alpha25_coeff(2) + &
669  ivar%s*four*alpha25_coeff(3))))*alpha25_ad
670  ! ...The beta term (eqn.4i) used to compute ionic conductivity
671  salinity_ad = salinity_ad + &
672  (beta_coeff(3) + ivar%delta*(beta_coeff(4) + &
673  ivar%delta*beta_coeff(5)))*beta_ad
674  delta_ad = delta_ad + &
675  (beta_coeff(1) + ivar%delta*two*beta_coeff(2) + &
676  (beta_coeff(4) + ivar%delta*two*beta_coeff(5))*ivar%s)*beta_ad
677  ! ...The temperature difference from 25C (eqn.4h) used to compute ionic conductivity.
678  temperature_ad = temperature_ad - delta_ad
679  END IF
680 
681 
682  ! ...The Debye relaxation time constants temperature polynomials (eqns.4e & 4f)
683  ! ...Units of tau: nanoseconds (for use with GHz frequencies)
684  temperature_ad = temperature_ad + &
685  (tau2_t_coeff(1) + ivar%t*(two*tau2_t_coeff(2) + &
686  ivar%t*three*tau2_t_coeff(3)))*tau2_ad
687  temperature_ad = temperature_ad + &
688  (tau1_t_coeff(1) + ivar%t*(two*tau1_t_coeff(2) + &
689  ivar%t*three*tau1_t_coeff(3)))*tau1_ad
690  ! ...The intermediate frequency permittivity temperature polynomial (eqn.4c)
691  temperature_ad = temperature_ad + &
692  (e1_t_coeff(1) + ivar%t*two*e1_t_coeff(2))*e1_ad
693  ! ...The static permittivity salinity polynomial (eqn.4b)
694  temperature_ad = temperature_ad + &
695  (es_t_coeff(1) + ivar%t*(two*es_t_coeff(2) + &
696  ivar%t*three*es_t_coeff(3)))*es_ad
697  ! ...The high-frequency permittivity temperature polynomial (eqn.4a)
698  temperature_ad = temperature_ad + einf_coeff(1)*einf_ad
699 
700  END SUBROUTINE liu_ocean_permittivity_ad
701 
702 END MODULE liu
real(fp), dimension(0:3), parameter tau2_t_coeff
Definition: Liu.f90:100
Definition: Liu.f90:15
real(fp), dimension(0:3), parameter alpha25_coeff
Definition: Liu.f90:123
real(fp), parameter, public zero
real(fp), dimension(0:2), parameter tau1_s_coeff
Definition: Liu.f90:96
real(fp), parameter alpha_coeff
Definition: Liu.f90:110
real(fp), parameter, public four
integer, parameter, public fp
Definition: Type_Kinds.f90:124
real(fp), parameter, public three
real(fp), dimension(0:2), parameter e1_t_coeff
Definition: Liu.f90:83
subroutine, public liu_ocean_permittivity(Temperature, Salinity, Frequency, Permittivity, iVar)
Definition: Liu.f90:212
real(fp), dimension(0:3), parameter tau1_t_coeff
Definition: Liu.f90:92
real(fp), dimension(0:2), parameter es_s_coeff
Definition: Liu.f90:77
real(fp), parameter tau0
Definition: Liu.f90:62
real(fp), dimension(0:3), parameter es_t_coeff
Definition: Liu.f90:73
real(fp), dimension(0:2), parameter e1_s_coeff
Definition: Liu.f90:86
real(fp), parameter, public one
real(fp), parameter, public two
real(fp), dimension(0:1), parameter einf_coeff
Definition: Liu.f90:68
real(fp), parameter, public permittivity
subroutine, public liu_ocean_permittivity_ad(Permittivity_AD, Frequency, Temperature_AD, Salinity_AD, iVar)
Definition: Liu.f90:568
real(fp), dimension(0:5), parameter beta_coeff
Definition: Liu.f90:114
subroutine, public liu_ocean_permittivity_tl(Temperature_TL, Salinity_TL, Frequency, Permittivity_TL, iVar)
Definition: Liu.f90:381
character(*), parameter module_version_id
Definition: Liu.f90:44
real(fp), parameter ghz_to_hz
Definition: Liu.f90:57
real(fp), dimension(0:2), parameter tau2_s_coeff
Definition: Liu.f90:104
real(fp), parameter, public pi