FV3 Bundle
Guillou.f90
Go to the documentation of this file.
1 !
2 ! Guillou Ocean Permittivity module.
3 !
4 ! Module containing routines to compute the complex permittivities for
5 ! sea water based on
6 !
7 ! Guillou, C. et al. (1998) Impact of new permittivity measurements
8 ! on sea surface emissivity modeling in microwaves.
9 ! Radio Science, Volume 33, Number 3, Pages 649-667
10 !
11 !
12 ! CREATION HISTORY:
13 ! Written by: Paul van Delst, 11-Apr-2007
14 ! paul.vandelst@noaa.gov
15 !
16 
17 MODULE guillou
18 
19  ! -----------------
20  ! Environment setup
21  ! -----------------
22  ! Module use
23  USE type_kinds, ONLY: fp
24  USE fundamental_constants, ONLY: pi, &
25  e0 => permittivity, & ! Permittivity of vacuum (F/m)
26  k_to_c => standard_temperature ! Temperature units conversion
27  ! Disable implicit typing
28  IMPLICIT NONE
29 
30 
31  ! ------------
32  ! Visibilities
33  ! ------------
34  PRIVATE
35  ! ...Datatypes
36  PUBLIC :: ivar_type
37  ! ...Procedures
41 
42 
43  ! -----------------
44  ! Module parameters
45  ! -----------------
46  CHARACTER(*), PARAMETER :: module_version_id = &
47  '$Id: Guillou.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
48  REAL(fp), PARAMETER :: zero = 0.0_fp
49  REAL(fp), PARAMETER :: point5 = 0.5_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  REAL(fp), PARAMETER :: five = 5.0_fp
55  REAL(fp), PARAMETER :: twopi = two*pi
56 
57 
58  ! Scaling factors (used here for documenting the conversion
59  ! to SI units of the double Debye model denominator)
60  ! ---------------------------------------------------------
61  REAL(fp), PARAMETER :: ps_to_s = 1.0e-12_fp ! Picoseconds -> Seconds
62  REAL(fp), PARAMETER :: ghz_to_hz = 1.0e+09_fp ! Gigahertz -> Hertz
63  REAL(fp), PARAMETER :: scale_factor = ps_to_s * ghz_to_hz
64 
65 
66  ! Parameters for the Guillou et al (1998) permittivity model
67  ! ----------------------------------------------------------
68  ! The coefficients for the sea water conductivity temperature
69  ! polynomials. Eqn.(1) in reference. Note that these values
70  ! have more precision than is reported in the ref.
71  REAL(fp), PARAMETER :: d1_coeff(0:2) = (/ 0.086374_fp, &
72  0.030606_fp, &
73  -0.0004121_fp /)
74  REAL(fp), PARAMETER :: d2_coeff(0:2) = (/ 0.077454_fp, &
75  0.001687_fp, &
76  0.00001937_fp /)
77 
78  ! The coefficients for the static permittivity temperature
79  ! polynomials. Eqn.(3) in reference. Note that these values
80  ! have more precision than is reported in the ref.
81  REAL(fp), PARAMETER :: a1_coeff(0:5) = (/ 81.820_fp, &
82  -6.0503e-02_fp, &
83  -3.1661e-02_fp, &
84  3.1097e-03_fp, &
85  -1.1791e-04_fp, &
86  1.4838e-06_fp /)
87  REAL(fp), PARAMETER :: a2_coeff(0:5) = (/ 0.12544_fp, &
88  9.4037e-03_fp, &
89  -9.5551e-04_fp, &
90  9.0888e-05_fp, &
91  -3.6011e-06_fp, &
92  4.7130e-08_fp /)
93 
94  ! The coefficients for the high-frequency permittivity temperature
95  ! polynomial. Eqn.(4) in reference. Note that these values
96  ! have more precision than is reported in the ref.
97  REAL(fp), PARAMETER :: b1_coeff(0:5) = (/ 6.4587_fp , &
98  -0.04203_fp , &
99  -0.0065881_fp , &
100  0.00064924_fp, &
101  -1.2328e-05_fp, &
102  5.0433e-08_fp /)
103 
104  ! The coefficients for the relaxation time temperature
105  ! polynomial. Eqn.(5) in reference. Note that these values
106  ! have more precision than is reported in the ref.
107  REAL(fp), PARAMETER :: c1_coeff(0:5) = (/ 17.303_fp , &
108  -0.66651_fp , &
109  5.1482e-03_fp, &
110  1.2145e-03_fp, &
111  -5.0325e-05_fp, &
112  5.8272e-07_fp /)
113  REAL(fp), PARAMETER :: c2_coeff(0:5) = (/-6.272e-03_fp , &
114  2.357e-04_fp , &
115  5.075e-04_fp , &
116  -6.3983e-05_fp, &
117  2.463e-06_fp , &
118  -3.0676e-08_fp /)
119 
120 
121  ! --------------------------------------
122  ! Structure definition to hold forward
123  ! variables across FWD, TL, and AD calls
124  ! --------------------------------------
125  TYPE :: ivar_type
126  PRIVATE
127  REAL(fp) :: t=zero, s=zero ! Temperature in degC; salinity
128  REAL(fp) :: f=zero, f2=zero, f0=zero, f2po=zero ! Frequency terms
129  REAL(fp) :: a1=zero, a2=zero, es=zero ! Static permittivity temperature polynomials
130  REAL(fp) :: einf=zero ! High-frequency permittivity temperature polynomial
131  REAL(fp) :: c1=zero, c2=zero ! Relaxation time temperature polynomial
132  REAL(fp) :: d1=zero, d2=zero ! Conductivity temperature polynomials
133  END TYPE ivar_type
134 
135 
136 CONTAINS
137 
138 
139 !################################################################################
140 !################################################################################
141 !## ##
142 !## ## PUBLIC MODULE ROUTINES ## ##
143 !## ##
144 !################################################################################
145 !################################################################################
146 
147 !--------------------------------------------------------------------------------
148 !:sdoc+:
149 !
150 ! NAME:
151 ! Guillou_Ocean_Permittivity
152 !
153 ! PURPOSE:
154 ! Subroutine to compute ocean permittivity according to the reference,
155 ! Guillou, C. et al. (1998) Impact of new permittivity measurements
156 ! on sea surface emissivity modeling in microwaves.
157 ! Radio Science, Volume 33, Number 3, Pages 649-667
158 !
159 ! CALLING SEQUENCE:
160 ! CALL Guillou_Ocean_Permittivity( Temperature , & ! Input
161 ! Salinity , & ! Input
162 ! Frequency , & ! Input
163 ! Permittivity, & ! Output
164 ! iVar ) ! Internal variable output
165 !
166 ! INPUTS:
167 ! Temperature: Sea surface temperature
168 ! UNITS: Kelvin (K)
169 ! TYPE: REAL(fp)
170 ! DIMENSION: Scalar
171 ! ATTRIBUTES: INTENT(IN)
172 !
173 ! Salinity: Water salinity
174 ! UNITS: ppt (parts per thousand)
175 ! TYPE: REAL(fp)
176 ! DIMENSION: Scalar
177 ! ATTRIBUTES: INTENT(IN)
178 !
179 ! Frequency: Frequency
180 ! UNITS: GHz
181 ! TYPE: REAL(fp)
182 ! DIMENSION: Scalar
183 ! ATTRIBUTES: INTENT(IN)
184 !
185 ! OUTPUTS:
186 ! Permittivity: Ocean permittivity
187 ! UNITS: N/A
188 ! TYPE: COMPLEX(fp)
189 ! DIMENSION: Scalar
190 ! ATTRIBUTES: INTENT(OUT)
191 !
192 ! iVar: Structure containing internal variables required for
193 ! subsequent tangent-linear or adjoint model calls.
194 ! The contents of this structure are NOT accessible
195 ! outside of this module.
196 ! UNITS: N/A
197 ! TYPE: TYPE(iVar_type)
198 ! DIMENSION: Scalar
199 ! ATTRIBUTES: INTENT(OUT)
200 !:sdoc-:
201 !--------------------------------------------------------------------------------
202 
203  SUBROUTINE guillou_ocean_permittivity( &
204  Temperature , & ! Input
205  Salinity , & ! Input
206  Frequency , & ! Input
207  Permittivity, & ! Output
208  iVar ) ! Internal variable output
209  ! Arguments
210  REAL(fp), INTENT(IN) :: temperature
211  REAL(fp), INTENT(IN) :: salinity
212  REAL(fp), INTENT(IN) :: frequency
213  COMPLEX(fp), INTENT(OUT) :: permittivity
214  TYPE(ivar_type), INTENT(IN OUT) :: ivar
215  ! Local variables
216  REAL(fp) :: sigma
217  REAL(fp) :: tau
218  REAL(fp) :: re, ie
219 
220 
221  ! Save the inputs
222  ! ---------------
223  ivar%t = temperature - k_to_c
224  ivar%s = salinity
225 
226 
227  ! Conductivity
228  ! ------------
229  ! Compute the conductivity temperature polynomials
230  ! Eqn.(1) in reference
231  ivar%d1 = d1_coeff(0) + ivar%t*(d1_coeff(1) + ivar%t*d1_coeff(2))
232  ivar%d2 = d2_coeff(0) + ivar%t*(d2_coeff(1) + ivar%t*d2_coeff(2))
233 
234  ! Compute the salinity dependent conductivity
235  sigma = ivar%d1 + ivar%s*ivar%d2
236 
237 
238  ! Static permittivity
239  ! -------------------
240  ! Compute the static permittivity temperature polynomials.
241  ! Eqn.(3) in reference.
242  ivar%a1 = a1_coeff(0) + ivar%t*(a1_coeff(1) + &
243  ivar%t*(a1_coeff(2) + &
244  ivar%t*(a1_coeff(3) + &
245  ivar%t*(a1_coeff(4) + &
246  ivar%t*a1_coeff(5) ))))
247  ivar%a2 = a2_coeff(0) + ivar%t*(a2_coeff(1) + &
248  ivar%t*(a2_coeff(2) + &
249  ivar%t*(a2_coeff(3) + &
250  ivar%t*(a2_coeff(4) + &
251  ivar%t*a2_coeff(5) ))))
252 
253  ! Compute the salinity dependent static permittivity
254  ivar%es = ivar%a1 - ivar%s*ivar%a2
255 
256 
257  ! High frequency permittivity
258  ! ---------------------------
259  ! Compute the high-frequency permittivity temperature polynomial
260  ! Eqn.(4) in reference
261  ivar%einf = b1_coeff(0) + ivar%t*(b1_coeff(1) + &
262  ivar%t*(b1_coeff(2) + &
263  ivar%t*(b1_coeff(3) + &
264  ivar%t*(b1_coeff(4) + &
265  ivar%t*b1_coeff(5) ))))
266 
267 
268  ! Relaxation time
269  ! ---------------
270  ! Compute the Debye relaxation time temperature polynomials
271  ! Eqn.(5) in reference
272  ivar%c1 = c1_coeff(0) + ivar%t*(c1_coeff(1) + &
273  ivar%t*(c1_coeff(2) + &
274  ivar%t*(c1_coeff(3) + &
275  ivar%t*(c1_coeff(4) + &
276  ivar%t*c1_coeff(5) ))))
277  ivar%c2 = c2_coeff(0) + ivar%t*(c2_coeff(1) + &
278  ivar%t*(c2_coeff(2) + &
279  ivar%t*(c2_coeff(3) + &
280  ivar%t*(c2_coeff(4) + &
281  ivar%t*c2_coeff(5) ))))
282 
283  ! Compute the salinity dependent relaxation time in picoseconds
284  tau = ivar%c1 + ivar%s*ivar%c2
285 
286 
287  ! Compute the complex permittivity
288  ! --------------------------------
289  ! The various frequency terms
290  ivar%f = twopi * frequency * tau * scale_factor
291  ivar%f2 = ivar%f**2
292  ivar%f0 = twopi * frequency * ghz_to_hz * e0
293 
294  ivar%f2po = one+ivar%f2
295 
296  ! The real part
297  re = (ivar%es + ivar%einf*ivar%f2)/ivar%f2po
298 
299  ! The imaginary part
300  ie = ivar%f*(ivar%es - ivar%einf)/ivar%f2po + sigma/ivar%f0
301 
302  ! Combine them
303  permittivity = cmplx(re,-ie,fp)
304 
305  END SUBROUTINE guillou_ocean_permittivity
306 
307 
308 !--------------------------------------------------------------------------------
309 !:sdoc+:
310 !
311 ! NAME:
312 ! Guillou_Ocean_Permittivity_TL
313 !
314 ! PURPOSE:
315 ! Subroutine to compute the tangent-linear ocean permittivity according
316 ! to the reference,
317 ! Guillou, C. et al. (1998) Impact of new permittivity measurements
318 ! on sea surface emissivity modeling in microwaves.
319 ! Radio Science, Volume 33, Number 3, Pages 649-667
320 !
321 ! CALLING SEQUENCE:
322 ! CALL Guillou_Ocean_Permittivity_TL( Temperature_TL , & ! Input
323 ! Salinity_TL , & ! Input
324 ! Frequency , & ! Input
325 ! Permittivity_TL, & ! Output
326 ! iVar ) ! Internal variable input
327 !
328 ! INPUTS:
329 ! Temperature_TL: Tangent-linear sea surface temperature
330 ! UNITS: Kelvin (K)
331 ! TYPE: REAL(fp)
332 ! DIMENSION: Scalar
333 ! ATTRIBUTES: INTENT(IN)
334 !
335 ! Salinity_TL: Tangent-linear water salinity
336 ! UNITS: ppt (parts per thousand)
337 ! TYPE: REAL(fp)
338 ! DIMENSION: Scalar
339 ! ATTRIBUTES: INTENT(IN)
340 !
341 ! Frequency: Frequency
342 ! UNITS: GHz
343 ! TYPE: REAL(fp)
344 ! DIMENSION: Scalar
345 ! ATTRIBUTES: INTENT(IN)
346 !
347 ! iVar: Structure containing internal variables required for
348 ! subsequent tangent-linear or adjoint model calls.
349 ! The contents of this structure are NOT accessible
350 ! outside of this module.
351 ! UNITS: N/A
352 ! TYPE: TYPE(iVar_type)
353 ! DIMENSION: Scalar
354 ! ATTRIBUTES: INTENT(OUT)
355 !
356 ! OUTPUTS:
357 ! Permittivity_TL: Tangent-linear ocean permittivity
358 ! UNITS: N/A
359 ! TYPE: COMPLEX(fp)
360 ! DIMENSION: Scalar
361 ! ATTRIBUTES: INTENT(OUT)
362 !:sdoc-:
363 !--------------------------------------------------------------------------------
364 
365  SUBROUTINE guillou_ocean_permittivity_tl( &
366  Temperature_TL , & ! Input
367  Salinity_TL , & ! Input
368  Frequency , & ! Input
369  Permittivity_TL, & ! Output
370  iVar ) ! Internal variable input
371  ! Arguments
372  REAL(fp), INTENT(IN) :: temperature_tl
373  REAL(fp), INTENT(IN) :: salinity_tl
374  REAL(fp), INTENT(IN) :: frequency
375  COMPLEX(fp), INTENT(OUT) :: permittivity_tl
376  TYPE(ivar_type), INTENT(IN) :: ivar
377  ! Local variables
378  REAL(fp) :: d1_tl, d2_tl, sigma_tl
379  REAL(fp) :: a1_tl, a2_tl, es_tl
380  REAL(fp) :: einf_tl
381  REAL(fp) :: c1_tl, c2_tl, tau_tl
382  REAL(fp) :: f_tl, f2_tl, f2po_tl
383  REAL(fp) :: inv_f2po
384  REAL(fp) :: re_tl, ie_tl
385 
386 
387  ! Conductivity
388  ! ------------
389  ! Compute the tangent-linear conductivity
390  ! temperature polynomials. Eqn.(1) in reference
391  d1_tl = (d1_coeff(1) + ivar%t*two*d1_coeff(2)) * temperature_tl
392  d2_tl = (d2_coeff(1) + ivar%t*two*d2_coeff(2)) * temperature_tl
393 
394  ! Compute the tangent-linear salinity
395  ! dependent conductivity
396  sigma_tl = d1_tl + ivar%s*d2_tl + salinity_tl*ivar%d2
397 
398 
399  ! Static permittivity
400  ! -------------------
401  ! Compute the tangent-linear static permittivity
402  ! temperature polynomials. Eqn.(3) in reference.
403  a1_tl = (a1_coeff(1) + ivar%t*(two*a1_coeff(2) + &
404  ivar%t*(three*a1_coeff(3) + &
405  ivar%t*(four*a1_coeff(4) + &
406  ivar%t*five*a1_coeff(5)))) ) * temperature_tl
407  a2_tl = (a2_coeff(1) + ivar%t*(two*a2_coeff(2) + &
408  ivar%t*(three*a2_coeff(3) + &
409  ivar%t*(four*a2_coeff(4) + &
410  ivar%t*five*a2_coeff(5)))) ) * temperature_tl
411 
412  ! Compute the tangent-linear salinity
413  ! dependent static permittivity
414  es_tl = a1_tl - ivar%s*a2_tl - salinity_tl*ivar%a2
415 
416 
417  ! High frequency permittivity
418  ! ---------------------------
419  ! Compute the tangent-linear high-frequency permittivity
420  ! temperature polynomial. Eqn.(4) in reference
421  einf_tl = (b1_coeff(1) + ivar%t*(two*b1_coeff(2) + &
422  ivar%t*(three*b1_coeff(3) + &
423  ivar%t*(four*b1_coeff(4) + &
424  ivar%t*five*b1_coeff(5)))) ) * temperature_tl
425 
426 
427  ! Relaxation time
428  ! ---------------
429  ! Compute the tangent-linear Debye relaxation time
430  ! temperature polynomials. Eqn.(5) in reference
431  c1_tl = (c1_coeff(1) + ivar%t*(two*c1_coeff(2) + &
432  ivar%t*(three*c1_coeff(3) + &
433  ivar%t*(four*c1_coeff(4) + &
434  ivar%t*five*c1_coeff(5)))) ) * temperature_tl
435  c2_tl = (c2_coeff(1) + ivar%t*(two*c2_coeff(2) + &
436  ivar%t*(three*c2_coeff(3) + &
437  ivar%t*(four*c2_coeff(4) + &
438  ivar%t*five*c2_coeff(5)))) ) * temperature_tl
439 
440  ! Compute the tangent-linear salinity
441  ! dependent relaxation time in picoseconds
442  tau_tl = c1_tl + ivar%s*c2_tl + salinity_tl*ivar%c2
443 
444 
445  ! Compute the complex permittivity
446  ! --------------------------------
447  ! The tangent-linear of various frequency terms
448  f_tl = twopi * frequency * tau_tl * scale_factor
449  f2_tl = two * ivar%f * f_tl
450 
451  f2po_tl = f2_tl
452  inv_f2po = one/ivar%f2po
453 
454  ! The real part
455  re_tl = inv_f2po*(ivar%f2*einf_tl + &
456  es_tl - &
457  inv_f2po*(ivar%es-ivar%einf)*f2po_tl)
458 
459  ! The imaginary part
460  ie_tl = inv_f2po*(ivar%f*es_tl - &
461  ivar%f*einf_tl +&
462  inv_f2po*(ivar%es-ivar%einf)*(one-ivar%f2)*f_tl) + &
463  sigma_tl/ivar%f0
464 
465  ! Combine them
466  permittivity_tl = cmplx(re_tl, -ie_tl, fp)
467 
468  END SUBROUTINE guillou_ocean_permittivity_tl
469 
470 
471 !--------------------------------------------------------------------------------
472 !:sdoc+:
473 !
474 ! NAME:
475 ! Guillou_Ocean_Permittivity_AD
476 !
477 ! PURPOSE:
478 ! Subroutine to compute the adjoint of the ocean permittivity according
479 ! to the reference,
480 ! Guillou, C. et al. (1998) Impact of new permittivity measurements
481 ! on sea surface emissivity modeling in microwaves.
482 ! Radio Science, Volume 33, Number 3, Pages 649-667
483 !
484 ! CALLING SEQUENCE:
485 ! CALL Guillou_Ocean_Permittivity_AD( Permittivity_AD, & ! Input
486 ! Frequency , & ! Input
487 ! Temperature_AD , & ! Output
488 ! Salinity_AD , & ! Output
489 ! iVar ) ! Internal variable input
490 !
491 ! INPUTS:
492 ! Permittivity_AD: Adjoint ocean permittivity
493 ! UNITS: N/A
494 ! TYPE: COMPLEX(fp)
495 ! DIMENSION: Scalar
496 ! ATTRIBUTES: INTENT(IN OUT)
497 !
498 ! Frequency: Frequency
499 ! UNITS: GHz
500 ! TYPE: REAL(fp)
501 ! DIMENSION: Scalar
502 ! ATTRIBUTES: INTENT(IN)
503 !
504 ! iVar: Structure containing internal variables required for
505 ! subsequent tangent-linear or adjoint model calls.
506 ! The contents of this structure are NOT accessible
507 ! outside of this module.
508 ! UNITS: N/A
509 ! TYPE: TYPE(iVar_type)
510 ! DIMENSION: Scalar
511 ! ATTRIBUTES: INTENT(OUT)
512 !
513 ! OUTPUTS:
514 ! Temperature_AD: Adjoint sea surface temperature, de/dT.
515 ! UNITS: per Kelvin (K^-1)
516 ! TYPE: REAL(fp)
517 ! DIMENSION: Scalar
518 ! ATTRIBUTES: INTENT(IN OUT)
519 !
520 ! Salinity_AD: Adjoint water salinity, de/dS
521 ! UNITS: per ppt (parts-per-thousand^-1)
522 ! TYPE: REAL(fp)
523 ! DIMENSION: Scalar
524 ! ATTRIBUTES: INTENT(IN OUT)
525 !
526 ! SIDE EFFECTS:
527 ! The input adjoint variable, Permittivity_AD, is set to zero upon
528 ! exiting this routine.
529 !
530 !:sdoc-:
531 !--------------------------------------------------------------------------------
532 
533  SUBROUTINE guillou_ocean_permittivity_ad( &
534  Permittivity_AD, & ! Input
535  Frequency , & ! Input
536  Temperature_AD , & ! Output
537  Salinity_AD , & ! Output
538  iVar ) ! Internal variable input
539  ! Arguments
540  COMPLEX(fp), INTENT(IN OUT) :: permittivity_ad
541  REAL(fp), INTENT(IN) :: frequency
542  REAL(fp), INTENT(IN OUT) :: temperature_ad
543  REAL(fp), INTENT(IN OUT) :: salinity_ad
544  TYPE(ivar_type), INTENT(IN) :: ivar
545  ! Local variables
546  REAL(fp) :: ie_ad, re_ad
547  REAL(fp) :: f2po2
548  REAL(fp) :: a1_ad, a2_ad, es_ad
549  REAL(fp) :: einf_ad
550  REAL(fp) :: c1_ad, c2_ad, tau_ad
551  REAL(fp) :: d1_ad, d2_ad, sigma_ad
552  REAL(fp) :: f2_ad, f_ad
553 
554 
555  ! Complex permittivity
556  ! --------------------
557  ! Separate the real and imaginary parts
558  ie_ad = -aimag(permittivity_ad)
559  re_ad = REAL(permittivity_ad, fp)
560  permittivity_ad = zero
561 
562  ! Adjoint of the imaginary part
563  f2po2 = ivar%f2po**2
564  sigma_ad = ie_ad/ivar%f0
565  f2_ad = -ie_ad*ivar%f*(ivar%es-ivar%einf)/f2po2
566  einf_ad = -ie_ad*ivar%f/ivar%f2po
567  es_ad = ie_ad*ivar%f/ivar%f2po
568  f_ad = ie_ad*(ivar%es-ivar%einf)/ivar%f2po
569  ie_ad = zero
570 
571  ! Adjoint of the real part
572  f2_ad = f2_ad - re_ad*(ivar%es-ivar%einf)/f2po2
573  einf_ad = einf_ad + re_ad*ivar%f2/ivar%f2po
574  es_ad = es_ad + re_ad/ivar%f2po
575  re_ad = zero
576 
577  ! Adjoint of the frequency terms
578  f_ad = f_ad + two*ivar%f*f2_ad
579  f2_ad = zero
580  tau_ad = twopi * frequency * scale_factor * f_ad
581  f_ad = zero
582 
583 
584  ! Relaxation time
585  ! ---------------
586  ! Compute the adjoint of the salinity
587  ! dependent relaxation time in picoseconds
588  salinity_ad = salinity_ad + ivar%c2*tau_ad
589  c2_ad = ivar%s * tau_ad
590  c1_ad = tau_ad
591  tau_ad = zero
592 
593  ! Compute the adjoint of the Debye relaxation time
594  ! temperature polynomials. Eqn.(5) in reference
595  temperature_ad = temperature_ad + (c2_coeff(1) + ivar%t*(two*c2_coeff(2) + &
596  ivar%t*(three*c2_coeff(3) + &
597  ivar%t*(four*c2_coeff(4) + &
598  ivar%t*five*c2_coeff(5)))) ) * c2_ad
599  temperature_ad = temperature_ad + (c1_coeff(1) + ivar%t*(two*c1_coeff(2) + &
600  ivar%t*(three*c1_coeff(3) + &
601  ivar%t*(four*c1_coeff(4) + &
602  ivar%t*five*c1_coeff(5)))) ) * c1_ad
603 
604 
605  ! High frequency permittivity
606  ! ---------------------------
607  ! Compute the adjoint of the high-frequency permittivity
608  ! temperature polynomial. Eqn.(4) in reference
609  temperature_ad = temperature_ad + (b1_coeff(1) + ivar%t*(two*b1_coeff(2) + &
610  ivar%t*(three*b1_coeff(3) + &
611  ivar%t*(four*b1_coeff(4) + &
612  ivar%t*five*b1_coeff(5)))) ) * einf_ad
613 
614 
615  ! Static permittivity
616  ! -------------------
617  ! Compute the adjoint of the salinity
618  ! dependent static permittivity
619  salinity_ad = salinity_ad - ivar%a2*es_ad
620  a2_ad = -ivar%s * es_ad
621  a1_ad = es_ad
622  es_ad = zero
623 
624  ! Compute the adjoint of the static permittivity
625  ! temperature polynomials. Eqn.(3) in reference.
626  temperature_ad = temperature_ad + (a2_coeff(1) + ivar%t*(two*a2_coeff(2) + &
627  ivar%t*(three*a2_coeff(3) + &
628  ivar%t*(four*a2_coeff(4) + &
629  ivar%t*five*a2_coeff(5)))) ) * a2_ad
630  temperature_ad = temperature_ad + (a1_coeff(1) + ivar%t*(two*a1_coeff(2) + &
631  ivar%t*(three*a1_coeff(3) + &
632  ivar%t*(four*a1_coeff(4) + &
633  ivar%t*five*a1_coeff(5)))) ) * a1_ad
634 
635  ! Conductivity
636  ! ------------
637  ! Compute the adjoint of the salinity
638  ! dependent conductivity
639  salinity_ad = salinity_ad + ivar%d2*sigma_ad
640  d2_ad = ivar%s * sigma_ad
641  d1_ad = sigma_ad
642  sigma_ad = zero
643 
644  ! Compute the adjoint of the conductivity
645  ! temperature polynomials. Eqn.(1) in reference
646  temperature_ad = temperature_ad + (d2_coeff(1) + ivar%t*two*d2_coeff(2)) * d2_ad
647  temperature_ad = temperature_ad + (d1_coeff(1) + ivar%t*two*d1_coeff(2)) * d1_ad
648 
649  END SUBROUTINE guillou_ocean_permittivity_ad
650 
651 END MODULE guillou
real(fp), parameter, public zero
real(fp), parameter, public four
integer, parameter, public fp
Definition: Type_Kinds.f90:124
real(fp), parameter, public three
real(fp), dimension(0:5), parameter c2_coeff
Definition: Guillou.f90:113
real(fp), dimension(0:5), parameter a2_coeff
Definition: Guillou.f90:87
real(fp), dimension(0:2), parameter d2_coeff
Definition: Guillou.f90:74
real(fp), dimension(0:5), parameter b1_coeff
Definition: Guillou.f90:97
real(fp), parameter ghz_to_hz
Definition: Guillou.f90:62
subroutine, public guillou_ocean_permittivity_ad(Permittivity_AD, Frequency, Temperature_AD, Salinity_AD, iVar)
Definition: Guillou.f90:539
real(fp), parameter, public one
real(fp), parameter, public twopi
real(fp), parameter point5
Definition: Guillou.f90:49
real(fp), dimension(0:5), parameter c1_coeff
Definition: Guillou.f90:107
real(fp), parameter, public two
real(fp), parameter, public permittivity
subroutine, public guillou_ocean_permittivity(Temperature, Salinity, Frequency, Permittivity, iVar)
Definition: Guillou.f90:209
real(fp), dimension(0:5), parameter a1_coeff
Definition: Guillou.f90:81
character(*), parameter module_version_id
Definition: Guillou.f90:46
real(fp), parameter scale_factor
Definition: Guillou.f90:63
real(fp), parameter, public five
real(fp), parameter ps_to_s
Definition: Guillou.f90:61
subroutine, public guillou_ocean_permittivity_tl(Temperature_TL, Salinity_TL, Frequency, Permittivity_TL, iVar)
Definition: Guillou.f90:371
real(fp), parameter, public pi
real(fp), dimension(0:2), parameter d1_coeff
Definition: Guillou.f90:71