FV3 Bundle
CRTM_FastemX.f90
Go to the documentation of this file.
1 !
2 ! CRTM_FastemX
3 !
4 ! Module containing the Fastem4/5/6 procedures. The difference between the Fastem4
5 ! and Fastem5 models is realised purely through the coefficients read during CRTM
6 ! initialisation. For Fastem6, a different azimuth emissivity model is used.
7 !
8 ! CREATION HISTORY:
9 ! Written by: Quanhua (Mark) Liu, Quanhua.Liu@noaa.gov
10 ! Stephen English, Stephen.English@metoffice.gov.uk
11 ! Fuzhong Weng, Fuzhong.Weng@noaa.gov
12 ! July, 2009
13 !
14 ! Refactored by: Paul van Delst, paul.vandelst@noaa.gov
15 ! October, 2010
16 !
17 ! Modified by: Quanhua Liu, Quanhua.Liu@noaa.gov
18 ! Stephen English, Stephen.English@metoffice.gov.uk
19 ! August, 2011
20 !
21 ! Refactored by: Paul van Delst, paul.vandelst@noaa.gov
22 ! December, 2011
23 !
24 ! Renamed: Separate Fastem4 and Fastem5 modules replaced with
25 ! single module named "FastemX"
26 ! Paul van Delst, paul.vandelst@noaa.gov
27 ! March, 2012
28 !
29 ! Added: M. Kazumori's azimuthal emissivity model for FASTEM6.
30 ! Paul van Delst, paul.vandelst@noaa.gov
31 ! January, 2015
32 !
33 
35 
36  ! -----------------
37  ! Environment setup
38  ! -----------------
39  ! Module use
40  USE type_kinds , ONLY: fp
42 
43  USE crtm_parameters, &
44  only: pi, degrees_to_radians, &
46 
47  USE fresnel, &
48  only: fvar_type => ivar_type , &
52 
53  USE liu, &
54  only: pvar_type => ivar_type, &
55  ocean_permittivity => liu_ocean_permittivity , &
56  ocean_permittivity_tl => liu_ocean_permittivity_tl, &
57  ocean_permittivity_ad => liu_ocean_permittivity_ad
58 
59  USE foam_utility_module, &
60  only: foam_coverage, &
64 
66  only: sscvar_type => ivar_type, &
70 
72  only: lscvar_type => ivar_type, &
76 
78  only: rcvar_type => ivar_type, &
82 
84  only: aevar_type => ivar_type, &
89  only: aef6var_type => ivar_type, &
93 
94  ! Disable implicit typing
95  IMPLICIT NONE
96 
97 
98  ! ------------
99  ! Visibilities
100  ! ------------
101  PRIVATE
102  ! Data types
103  PUBLIC :: ivar_type
104  ! Science routines
105  PUBLIC :: compute_fastemx
106  PUBLIC :: compute_fastemx_tl
107  PUBLIC :: compute_fastemx_ad
108 
109 
110  ! -----------------
111  ! Module parameters
112  ! -----------------
113  CHARACTER(*), PARAMETER :: module_version_id = &
114  '$Id: CRTM_FastemX.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
115 
116  ! FASTEM6 version number for use with azimuth model
117  INTEGER, PARAMETER :: fastem6 = 6
118 
119  ! Stokes component information
120  ! ...The number of Stokes components
121  INTEGER, PARAMETER :: n_stokes = 4
122  ! ...The vector indices
123  INTEGER, PARAMETER :: iv_idx = 1 ! Describes vertical polarization
124  INTEGER, PARAMETER :: ih_idx = 2 ! Describes horizontal polarization
125  INTEGER, PARAMETER :: u_idx = 3 ! Describes plane of polarization
126  INTEGER, PARAMETER :: v_idx = 4 ! Describes ellipticity of polarization
127 
128  ! Invalid indicators
129  REAL(fp), PARAMETER :: invalid_azimuth_angle = -999.0_fp
130  REAL(fp), PARAMETER :: invalid_transmittance = -999.0_fp ! Disable non-specular correction
131 
132 
133  ! --------------------------------------
134  ! Structure definition to hold internal
135  ! variables across FWD, TL, and AD calls
136  ! --------------------------------------
137  TYPE :: ivar_type
138  PRIVATE
139  ! Validity indicator
140  LOGICAL :: is_valid = .false.
141  ! Forward model input values
142  REAL(fp) :: frequency = zero
143  REAL(fp) :: zenith_angle = zero
144  REAL(fp) :: temperature = zero
145  REAL(fp) :: salinity = zero
146  REAL(fp) :: wind_speed = zero
147  ! ...Optional
148  LOGICAL :: azimuth_angle_valid = .false.
149  REAL(fp) :: azimuth_angle = zero
150  LOGICAL :: transmittance_valid = .false.
151  REAL(fp) :: transmittance = zero
152  ! The zenith angle term
153  REAL(fp) :: cos_z = one
154  ! The permittivity term
155  COMPLEX(fp) :: permittivity = zero
156  ! The Fresnel reflectivity terms
157  REAL(fp) :: rv_fresnel = zero
158  REAL(fp) :: rh_fresnel = zero
159  ! Foam Terms
160  REAL(fp) :: rv_foam = zero
161  REAL(fp) :: rh_foam = zero
162  REAL(fp) :: foam_cover = zero
163  ! Large scale correction reflectivities
164  REAL(fp) :: rv_large = zero
165  REAL(fp) :: rh_large = zero
166  ! Small scale correction factor
167  REAL(fp) :: f_small = zero
168  ! Final reflectivities
169  REAL(fp) :: rv = zero
170  REAL(fp) :: rh = zero
171  ! Azimuthal emissivity
172  REAL(fp) :: e_azimuth(n_stokes) = zero
173  ! Anisotropic downward radiation correction
174  REAL(fp) :: rv_mod = zero
175  REAL(fp) :: rh_mod = zero
176  ! The final emissivity
177  REAL(fp) :: e(n_stokes) = zero
178  ! Internal variables for subcomponents
179  TYPE(pvar_type) :: pvar
180  TYPE(fvar_type) :: fvar
181  TYPE(sscvar_type) :: sscvar
182  TYPE(lscvar_type) :: lscvar
183  TYPE(aevar_type) :: aevar
184  TYPE(aef6var_type) :: aef6var
185  TYPE(rcvar_type) :: rcvar
186  END TYPE ivar_type
187 
188 
189 CONTAINS
190 
191 
192 !################################################################################
193 !################################################################################
194 !## ##
195 !## ## PUBLIC MODULE ROUTINES ## ##
196 !## ##
197 !################################################################################
198 !################################################################################
199 
200 !--------------------------------------------------------------------------------
201 !:sdoc+:
202 !
203 ! NAME:
204 ! Compute_FastemX
205 !
206 ! PURPOSE:
207 ! Subroutine to compute the Fastem4 or Fastem5 microwave sea surface
208 ! emissivity and reflectivity.
209 !
210 ! CALLING SEQUENCE:
211 ! CALL Compute_FastemX( &
212 ! MWwaterCoeff , & ! Input
213 ! Frequency , & ! Input
214 ! Zenith_Angle , & ! Input
215 ! Temperature , & ! Input
216 ! Salinity , & ! Input
217 ! Wind_Speed , & ! Input
218 ! iVar , & ! Internal variable output
219 ! Emissivity , & ! Output
220 ! Reflectivity , & ! Output
221 ! Azimuth_Angle, & ! Optional input
222 ! Transmittance ) ! Optional input
223 !
224 !
225 ! INPUTS:
226 ! MWwaterCoeff: Microwave water emissivity model coefficient object.
227 ! Load the object with the coefficients for the emissivity
228 ! model to use (Fastem4 or Fastem5)
229 ! UNITS: N/A
230 ! TYPE: MWwaterCoeff_type
231 ! DIMENSION: Scalar
232 ! ATTRIBUTES: INTENT(IN)
233 !
234 ! Frequency: Microwave frequency.
235 ! UNITS: GHz
236 ! TYPE: REAL(fp)
237 ! DIMENSION: Scalar
238 ! ATTRIBUTES: INTENT(IN)
239 !
240 ! Zenith_Angle: Sensor zenith angle at the sea surface
241 ! UNITS: Degrees
242 ! TYPE: REAL(fp)
243 ! DIMENSION: Scalar
244 ! ATTRIBUTES: INTENT(IN)
245 !
246 ! Temperature: Sea surface temperature
247 ! UNITS: Kelvin, K
248 ! TYPE: REAL(fp)
249 ! DIMENSION: Scalar
250 ! ATTRIBUTES: INTENT(IN)
251 !
252 ! Salinity: Water salinity
253 ! UNITS: ppt (parts per thousand)
254 ! TYPE: REAL(fp)
255 ! DIMENSION: Scalar
256 ! ATTRIBUTES: INTENT(IN)
257 !
258 ! Wind_Speed: Sea surface wind speed
259 ! UNITS: m/s
260 ! TYPE: REAL(fp)
261 ! DIMENSION: Scalar
262 ! ATTRIBUTES: INTENT(IN)
263 !
264 ! OUTPUTS:
265 ! iVar: Structure containing internal variables required for
266 ! subsequent tangent-linear or adjoint model calls.
267 ! The contents of this structure are NOT accessible
268 ! outside of this module.
269 ! UNITS: N/A
270 ! TYPE: iVar_type
271 ! DIMENSION: Scalar
272 ! ATTRIBUTES: INTENT(OUT)
273 !
274 ! Emissivity: The surface emissivity
275 ! UNITS: N/A
276 ! TYPE: REAL(fp)
277 ! DIMENSION: Rank-1, 4-elements (n_Stokes)
278 ! ATTRIBUTES: INTENT(OUT)
279 !
280 ! Reflectivity: The surface reflectivity.
281 ! UNITS: N/A
282 ! TYPE: REAL(fp)
283 ! DIMENSION: Rank-1, 4-elements (n_Stokes)
284 ! ATTRIBUTES: INTENT(OUT)
285 !
286 ! OPTIONAL INPUTS:
287 ! Azimuth_Angle: Relative azimuth angle (wind direction - sensor azimuth)
288 ! UNITS: Degrees
289 ! TYPE: REAL(fp)
290 ! DIMENSION: Scalar
291 ! ATTRIBUTES: INTENT(IN), OPTIONAL
292 !
293 ! Transmittance: Total atmospheric transmittance
294 ! UNITS: N/A
295 ! TYPE: REAL(fp)
296 ! DIMENSION: Scalar
297 ! ATTRIBUTES: INTENT(IN), OPTIONAL
298 !
299 !:sdoc-:
300 !--------------------------------------------------------------------------------
301 
302  SUBROUTINE compute_fastemx( &
303  MWwaterCoeff , & ! Input
304  Frequency , & ! Input
305  Zenith_Angle , & ! Input
306  Temperature , & ! Input
307  Salinity , & ! Input
308  Wind_Speed , & ! Input
309  iVar , & ! Internal variable output
310  Emissivity , & ! Output
311  Reflectivity , & ! Output
312  Azimuth_Angle, & ! Optional Input
313  Transmittance ) ! Optional Input
314  ! Arguments
315  TYPE(mwwatercoeff_type), INTENT(IN) :: mwwatercoeff
316  REAL(fp), INTENT(IN) :: frequency
317  REAL(fp), INTENT(IN) :: zenith_angle
318  REAL(fp), INTENT(IN) :: temperature
319  REAL(fp), INTENT(IN) :: salinity
320  REAL(fp), INTENT(IN) :: wind_speed
321  TYPE(ivar_type), INTENT(OUT) :: ivar
322  REAL(fp), INTENT(OUT) :: emissivity(:)
323  REAL(fp), INTENT(OUT) :: reflectivity(:)
324  REAL(fp), OPTIONAL, INTENT(IN) :: azimuth_angle
325  REAL(fp), OPTIONAL, INTENT(IN) :: transmittance
326 
327  ! Setup
328  ! ...Save forward input variables for TL and AD calculations
329  ivar%Frequency = frequency
330  ivar%Zenith_Angle = zenith_angle
331  ivar%Temperature = temperature
332  ivar%Salinity = salinity
333  ivar%Wind_Speed = wind_speed
334  ! ...Save derived variables
335  ivar%cos_z = cos(zenith_angle*degrees_to_radians)
336 
337  ! Permittivity calculation
338  CALL ocean_permittivity( temperature, salinity, frequency, &
339  ivar%Permittivity, &
340  ivar%pVar )
341 
342 
343  ! Fresnel reflectivity calculation
344  CALL fresnel_reflectivity( ivar%Permittivity, ivar%cos_z, &
345  ivar%Rv_Fresnel, ivar%Rh_Fresnel, &
346  ivar%fVar )
347 
348 
349  ! Foam reflectivity calculation
350  CALL foam_reflectivity( &
351  mwwatercoeff%FRCoeff, &
352  zenith_angle, &
353  frequency , &
354  ivar%Rv_Foam, &
355  ivar%Rh_Foam )
356 
357 
358  ! Foam coverage calculation
359  CALL foam_coverage( &
360  mwwatercoeff%FCCoeff, &
361  wind_speed, &
362  ivar%Foam_Cover )
363 
364 
365  ! Large scale correction calculation
366  CALL large_scale_correction( &
367  mwwatercoeff%LSCCoeff, &
368  ivar%Frequency , &
369  ivar%cos_z , &
370  ivar%Wind_Speed, &
371  ivar%Rv_Large , &
372  ivar%Rh_Large , &
373  ivar%lscVar )
374 
375  ! Small scale correction calculation, Var%small_corr
376  CALL small_scale_correction( &
377  mwwatercoeff%SSCCoeff, &
378  ivar%Frequency , &
379  ivar%cos_z , &
380  ivar%Wind_Speed, &
381  ivar%F_Small , &
382  ivar%sscVar )
383 
384  ! Compute the first two Stokes components of the emissivity
385  ivar%Rv = ivar%Rv_Fresnel*ivar%F_Small -ivar%Rv_Large
386  ivar%Rh = ivar%Rh_Fresnel*ivar%F_Small -ivar%Rh_Large
387  emissivity(iv_idx) = one - (one-ivar%Foam_Cover)*ivar%Rv - ivar%Foam_Cover*ivar%Rv_Foam
388  emissivity(ih_idx) = one - (one-ivar%Foam_Cover)*ivar%Rh - ivar%Foam_Cover*ivar%Rh_Foam
389 
390  ! Azimuthal component calculation
391  ivar%Azimuth_Angle_Valid = .false.
392  ivar%e_Azimuth = zero
393  IF ( PRESENT(azimuth_angle) ) THEN
394  IF ( abs(azimuth_angle) <= 360.0_fp ) THEN
395  IF ( mwwatercoeff%Version == fastem6 ) THEN
396  CALL azimuth_emissivity_f6( &
397  mwwatercoeff%AZCoeff, &
398  ivar%Wind_Speed, &
399  azimuth_angle , &
400  ivar%Frequency , &
401  zenith_angle , &
402  ivar%e_Azimuth , &
403  ivar%aeF6Var )
404  ELSE
405  CALL azimuth_emissivity( &
406  mwwatercoeff%AZCoeff, &
407  ivar%Wind_Speed, &
408  azimuth_angle , &
409  ivar%Frequency , &
410  ivar%cos_z , &
411  ivar%e_Azimuth , &
412  ivar%aeVar )
413  END IF
414  ivar%Azimuth_Angle_Valid = .true.
415  ivar%Azimuth_Angle = azimuth_angle
416  END IF
417  END IF
418 
419  ! Anisotropic downward radiation correction calculation
420  ivar%Transmittance_Valid = .false.
421  ivar%Rv_Mod = one
422  ivar%Rh_Mod = one
423  IF ( PRESENT(transmittance) ) THEN
424  IF ( transmittance > zero .AND. transmittance < one ) THEN
425  CALL reflection_correction( &
426  mwwatercoeff%RCCoeff, &
427  ivar%Frequency , &
428  ivar%cos_z , &
429  ivar%Wind_Speed, &
430  transmittance , &
431  ivar%Rv_Mod , &
432  ivar%Rh_Mod , &
433  ivar%rcVar )
434  ivar%Transmittance_Valid = .true.
435  ivar%Transmittance = transmittance
436  END IF
437  END IF
438 
439  ! Assemble the return...
440  ! ...emissivities
441  emissivity(iv_idx) = emissivity(iv_idx) + ivar%e_Azimuth(iv_idx)
442  emissivity(ih_idx) = emissivity(ih_idx) + ivar%e_Azimuth(ih_idx)
443  emissivity(u_idx) = ivar%e_Azimuth(u_idx)
444  emissivity(v_idx) = ivar%e_Azimuth(v_idx)
445  ! ...reflectivties
446 
447  reflectivity(iv_idx) = ivar%Rv_Mod * (one-emissivity(iv_idx))
448  reflectivity(ih_idx) = ivar%Rh_Mod * (one-emissivity(ih_idx))
449  reflectivity(u_idx:v_idx) = zero ! 3rd, 4th Stokes from atmosphere are not included.
450  ! ...save the emissivity for TL and AD reflectivity calculations
451  ivar%e = emissivity
452 
453 
454  ! Flag the internal variable structure as valid
455  ivar%Is_Valid = .true.
456 
457  END SUBROUTINE compute_fastemx
458 
459 
460 !--------------------------------------------------------------------------------
461 !:sdoc+:
462 !
463 ! NAME:
464 ! Compute_FastemX_TL
465 !
466 ! PURPOSE:
467 ! Subroutine to compute the tangent-linear Fastem4 or Fastem5 microwave
468 ! sea surface emissivity and reflectivity.
469 !
470 ! NOTE: The forward model must be called first to fill the internal
471 ! variable argument with the intermediate forward calculations.
472 !
473 ! CALLING SEQUENCE:
474 ! CALL Compute_FastemX_TL( &
475 ! MWwaterCoeff , &
476 ! Temperature_TL , &
477 ! Salinity_TL , &
478 ! Wind_Speed_TL , &
479 ! iVar , &
480 ! Emissivity_TL , &
481 ! Reflectivity_TL , &
482 ! Azimuth_Angle_TL, &
483 ! Transmittance_TL )
484 !
485 !
486 ! INPUTS:
487 ! MWwaterCoeff: Microwave water emissivity model coefficient object.
488 ! Load the object with the coefficients for the emissivity
489 ! model to use (Fastem4 or Fastem5)
490 ! UNITS: N/A
491 ! TYPE: MWwaterCoeff_type
492 ! DIMENSION: Scalar
493 ! ATTRIBUTES: INTENT(IN)
494 !
495 ! Temperature_TL: Tangent-linear sea surface temperature
496 ! UNITS: Kelvin, K
497 ! TYPE: REAL(fp)
498 ! DIMENSION: Scalar
499 ! ATTRIBUTES: INTENT(IN)
500 !
501 ! Salinity_TL: Tangent-linear water salinity
502 ! UNITS: ppt (parts per thousand)
503 ! TYPE: REAL(fp)
504 ! DIMENSION: Scalar
505 ! ATTRIBUTES: INTENT(IN)
506 !
507 ! Wind_Speed_TL: Tangent-linear sea surface wind speed
508 ! UNITS: m/s
509 ! TYPE: REAL(fp)
510 ! DIMENSION: Scalar
511 ! ATTRIBUTES: INTENT(IN)
512 !
513 ! iVar: Structure containing internal variables computed
514 ! in a previous forward model call.
515 ! The contents of this structure are NOT accessible
516 ! outside of this module.
517 ! UNITS: N/A
518 ! TYPE: iVar_type
519 ! DIMENSION: Scalar
520 ! ATTRIBUTES: INTENT(IN)
521 !
522 ! OUTPUTS:
523 ! Emissivity_TL: Tangent-linear surface emissivity
524 ! UNITS: N/A
525 ! TYPE: REAL(fp)
526 ! DIMENSION: Rank-1, 4-elements (n_Stokes)
527 ! ATTRIBUTES: INTENT(OUT)
528 !
529 ! Reflectivity_TL: Tangent-linear surface reflectivity.
530 ! UNITS: N/A
531 ! TYPE: REAL(fp)
532 ! DIMENSION: Rank-1, 4-elements (n_Stokes)
533 ! ATTRIBUTES: INTENT(OUT)
534 !
535 ! OPTIONAL INPUTS:
536 ! Azimuth_Angle_TL: Tangent-linear relative azimuth angle.
537 ! This argument is ignored if a valid relative azimuth
538 ! angle was not passed into the forward model call.
539 ! UNITS: Degrees
540 ! TYPE: REAL(fp)
541 ! DIMENSION: Scalar
542 ! ATTRIBUTES: INTENT(IN), OPTIONAL
543 !
544 ! Transmittance_TL: Tangent-linear total atmospheric transmittance
545 ! This argument is ignored if a valid transmittance
546 ! was not passed into the forward model call.
547 ! UNITS: N/A
548 ! TYPE: REAL(fp)
549 ! DIMENSION: Scalar
550 ! ATTRIBUTES: INTENT(IN), OPTIONAL
551 !
552 !:sdoc-:
553 !--------------------------------------------------------------------------------
554 
555  SUBROUTINE compute_fastemx_tl( &
556  MWwaterCoeff , & ! Input
557  Temperature_TL , & ! TL Input
558  Salinity_TL , & ! TL Input
559  Wind_Speed_TL , & ! TL Input
560  iVar , & ! Internal variable input
561  Emissivity_TL , & ! TL Output
562  Reflectivity_TL , & ! TL Output
563  Azimuth_Angle_TL, & ! Optional TL input
564  Transmittance_TL ) ! Optional TL input
565  ! Arguments
566  TYPE(mwwatercoeff_type), INTENT(IN) :: mwwatercoeff
567  REAL(fp), INTENT(IN) :: temperature_tl
568  REAL(fp), INTENT(IN) :: salinity_tl
569  REAL(fp), INTENT(IN) :: wind_speed_tl
570  TYPE(ivar_type), INTENT(IN) :: ivar
571  REAL(fp), INTENT(OUT) :: emissivity_tl(:)
572  REAL(fp), INTENT(OUT) :: reflectivity_tl(:)
573  REAL(fp), OPTIONAL, INTENT(IN) :: azimuth_angle_tl
574  REAL(fp), OPTIONAL, INTENT(IN) :: transmittance_tl
575  ! Local variables
576  REAL(fp) :: rv_fresnel_tl, rh_fresnel_tl
577  REAL(fp) :: rv_foam_tl , rh_foam_tl
578  REAL(fp) :: rv_large_tl , rh_large_tl
579  REAL(fp) :: rv_tl , rh_tl
580  REAL(fp) :: rv_mod_tl , rh_mod_tl
581  REAL(fp) :: foam_cover_tl
582  REAL(fp) :: e_azimuth_tl(n_stokes)
583  COMPLEX(fp) :: permittivity_tl
584  REAL(fp) :: f_small_tl
585 
586  ! Check internal structure
587  IF ( .NOT. ivar%Is_Valid ) THEN
588  emissivity_tl = zero
589  reflectivity_tl = zero
590  RETURN
591  END IF
592 
593 
594  ! Permittivity calculation
595  CALL ocean_permittivity_tl( temperature_tl, salinity_tl, ivar%Frequency, &
596  permittivity_tl, &
597  ivar%pVar)
598 
599 
600  ! Fresnel reflectivity calculation
601  CALL fresnel_reflectivity_tl( permittivity_tl, ivar%cos_z, &
602  rv_fresnel_tl, rh_fresnel_tl, &
603  ivar%fVar )
604 
605 
606  ! Foam reflectivity "calculation"
607  rv_foam_tl = zero
608  rh_foam_tl = zero
609 
610 
611  ! Foam coverage calculation
612  CALL foam_coverage_tl( &
613  mwwatercoeff%FCCoeff, &
614  ivar%Wind_Speed, &
615  wind_speed_tl, &
616  foam_cover_tl )
617 
618 
619  ! Large Scale Correction Calculation
621  wind_speed_tl, &
622  rv_large_tl , &
623  rh_large_tl , &
624  ivar%lscVar )
625 
626 
627  ! Small Scale Correction Calculation
629  mwwatercoeff%SSCCoeff, &
630  wind_speed_tl, &
631  f_small_tl , &
632  ivar%sscVar )
633 
634  ! Compute the first two Stokes components of the tangent-linear emissivity
635  rv_tl = rv_fresnel_tl*ivar%F_Small + ivar%Rv_Fresnel*f_small_tl - rv_large_tl
636  emissivity_tl(iv_idx) = (ivar%Foam_Cover-one)*rv_tl + &
637  (ivar%Rv-ivar%Rv_Foam)*foam_cover_tl - &
638  ivar%Foam_Cover*rv_foam_tl
639  rh_tl = rh_fresnel_tl*ivar%F_Small + ivar%Rh_Fresnel*f_small_tl - rh_large_tl
640  emissivity_tl(ih_idx) = (ivar%Foam_Cover-one)*rh_tl + &
641  (ivar%Rh-ivar%Rh_Foam)*foam_cover_tl - &
642  ivar%Foam_Cover*rh_foam_tl
643 
644  ! Azimuthal component calculation
645  IF ( PRESENT(azimuth_angle_tl) .AND. ivar%Azimuth_Angle_Valid ) THEN
646  IF ( mwwatercoeff%Version == fastem6 ) THEN
648  mwwatercoeff%AZCoeff, &
649  wind_speed_tl , &
650  azimuth_angle_tl , &
651  e_azimuth_tl , &
652  ivar%aeF6Var )
653 
654  ELSE
655  CALL azimuth_emissivity_tl( &
656  mwwatercoeff%AZCoeff, &
657  wind_speed_tl , &
658  azimuth_angle_tl, &
659  e_azimuth_tl , &
660  ivar%aeVar )
661  END IF
662  ELSE
663  e_azimuth_tl = zero
664  END IF
665 
666 
667  ! Anisotropic downward radiation correction calculation
668  IF ( PRESENT(transmittance_tl) .AND. ivar%Transmittance_Valid ) THEN
670  mwwatercoeff%RCCoeff, &
671  wind_speed_tl , &
672  transmittance_tl, &
673  rv_mod_tl , &
674  rh_mod_tl , &
675  ivar%rcVar )
676  ELSE
677  rv_mod_tl = zero
678  rh_mod_tl = zero
679  END IF
680 
681 
682  ! Compute the tangent-linear...
683  ! ...emissivities
684  emissivity_tl(iv_idx) = emissivity_tl(iv_idx) + e_azimuth_tl(iv_idx)
685  emissivity_tl(ih_idx) = emissivity_tl(ih_idx) + e_azimuth_tl(ih_idx)
686  emissivity_tl(u_idx) = e_azimuth_tl(u_idx)
687  emissivity_tl(v_idx) = e_azimuth_tl(v_idx)
688  ! ...reflectivities
689  reflectivity_tl(iv_idx) = (one-ivar%e(iv_idx))*rv_mod_tl - ivar%Rv_Mod*emissivity_tl(iv_idx)
690  reflectivity_tl(ih_idx) = (one-ivar%e(ih_idx))*rh_mod_tl - ivar%Rh_Mod*emissivity_tl(ih_idx)
691  reflectivity_tl(u_idx:v_idx) = zero ! 3rd, 4th Stokes from atmosphere are not included.
692 
693  END SUBROUTINE compute_fastemx_tl
694 
695 
696 !--------------------------------------------------------------------------------
697 !:sdoc+:
698 !
699 ! NAME:
700 ! Compute_FastemX_AD
701 !
702 ! PURPOSE:
703 ! Subroutine to compute the adjoint Fastem4 or Fastem5 microwave
704 ! sea surface emissivity and reflectivity.
705 !
706 ! NOTE: The forward model must be called first to fill the internal
707 ! variable argument with the intermediate forward calculations.
708 !
709 ! CALLING SEQUENCE:
710 ! CALL Compute_FastemX_AD( &
711 ! MWwaterCoeff , &
712 ! Emissivity_AD , &
713 ! Reflectivity_AD , &
714 ! iVar , &
715 ! Temperature_AD , &
716 ! Salinity_AD , &
717 ! Wind_Speed_AD , &
718 ! Azimuth_Angle_AD, &
719 ! Transmittance_AD )
720 !
721 !
722 ! INPUTS:
723 ! MWwaterCoeff: Microwave water emissivity model coefficient object.
724 ! Load the object with the coefficients for the emissivity
725 ! model to use (Fastem4 or Fastem5)
726 ! UNITS: N/A
727 ! TYPE: MWwaterCoeff_type
728 ! DIMENSION: Scalar
729 ! ATTRIBUTES: INTENT(IN)
730 !
731 ! Emissivity_AD: Adjoint surface emissivity
732 ! ***SET TO ZERO UPON EXIT***
733 ! UNITS: N/A
734 ! TYPE: REAL(fp)
735 ! DIMENSION: Rank-1, 4-elements (n_Stokes)
736 ! ATTRIBUTES: INTENT(IN OUT)
737 !
738 ! Reflectivity_AD: Adjoint surface reflectivity.
739 ! ***SET TO ZERO UPON EXIT***
740 ! UNITS: N/A
741 ! TYPE: REAL(fp)
742 ! DIMENSION: Rank-1, 4-elements (n_Stokes)
743 ! ATTRIBUTES: INTENT(IN OUT)
744 !
745 ! iVar: Structure containing internal variables computed
746 ! in a previous forward model call.
747 ! The contents of this structure are NOT accessible
748 ! outside of this module.
749 ! UNITS: N/A
750 ! TYPE: iVar_type
751 ! DIMENSION: Scalar
752 ! ATTRIBUTES: INTENT(IN)
753 !
754 ! OUTPUTS:
755 ! Temperature_AD: Adjoint sea surface temperature
756 ! ***MUST CONTAIN VALUE UPON ENTRY***
757 ! UNITS: K^-1
758 ! TYPE: REAL(fp)
759 ! DIMENSION: Scalar
760 ! ATTRIBUTES: INTENT(IN OUT)
761 !
762 ! Salinity_AD: Adjoint water salinity
763 ! ***MUST CONTAIN VALUE UPON ENTRY***
764 ! UNITS: ppt^-1 (parts per thousand)
765 ! TYPE: REAL(fp)
766 ! DIMENSION: Scalar
767 ! ATTRIBUTES: INTENT(IN OUT)
768 !
769 ! Wind_Speed_AD: Adjoint sea surface wind speed
770 ! ***MUST CONTAIN VALUE UPON ENTRY***
771 ! UNITS: (m/s)^-1
772 ! TYPE: REAL(fp)
773 ! DIMENSION: Scalar
774 ! ATTRIBUTES: INTENT(IN)
775 !
776 ! OPTIONAL OUTPUTS:
777 ! Azimuth_Angle_AD: Adjoint relative azimuth angle.
778 ! This argument is ignored if a valid relative azimuth
779 ! angle was not passed into the forward model call.
780 ! UNITS: Degrees^-1
781 ! TYPE: REAL(fp)
782 ! DIMENSION: Scalar
783 ! ATTRIBUTES: INTENT(IN), OPTIONAL
784 !
785 ! Transmittance_AD: Adjoint total atmospheric transmittance
786 ! This argument is ignored if a valid transmittance
787 ! was not passed into the forward model call.
788 ! UNITS: N/A
789 ! TYPE: REAL(fp)
790 ! DIMENSION: Scalar
791 ! ATTRIBUTES: INTENT(IN), OPTIONAL
792 !
793 !:sdoc-:
794 !--------------------------------------------------------------------------------
795 
796  SUBROUTINE compute_fastemx_ad( &
797  MWwaterCoeff , & ! Input
798  Emissivity_AD , & ! AD Input
799  Reflectivity_AD , & ! AD Input
800  iVar , & ! Internal variable input
801  Temperature_AD , & ! AD Output
802  Salinity_AD , & ! AD Output
803  Wind_Speed_AD , & ! AD Output
804  Azimuth_Angle_AD, & ! Optional AD Output
805  Transmittance_AD ) ! Optional AD Output
806  ! Arguments
807  TYPE(mwwatercoeff_type), INTENT(IN) :: mwwatercoeff
808  REAL(fp), INTENT(IN OUT) :: emissivity_ad(:)
809  REAL(fp), INTENT(IN OUT) :: reflectivity_ad(:)
810  TYPE(ivar_type), INTENT(IN) :: ivar
811  REAL(fp), INTENT(IN OUT) :: temperature_ad
812  REAL(fp), INTENT(IN OUT) :: salinity_ad
813  REAL(fp), INTENT(IN OUT) :: wind_speed_ad
814  REAL(fp), OPTIONAL, INTENT(IN OUT) :: azimuth_angle_ad
815  REAL(fp), OPTIONAL, INTENT(IN OUT) :: transmittance_ad
816  ! Local variables
817  REAL(fp) :: rv_fresnel_ad, rh_fresnel_ad
818  REAL(fp) :: rv_foam_ad , rh_foam_ad
819  REAL(fp) :: rv_large_ad , rh_large_ad
820  REAL(fp) :: rv_ad , rh_ad
821  REAL(fp) :: rv_mod_ad , rh_mod_ad
822  REAL(fp) :: foam_cover_ad
823  REAL(fp) :: e_azimuth_ad(n_stokes)
824  COMPLEX(fp) :: permittivity_ad
825  REAL(fp) :: f_small_ad
826 
827  ! Check internal structure
828  IF ( .NOT. ivar%Is_Valid ) THEN
829  temperature_ad = zero
830  salinity_ad = zero
831  wind_speed_ad = zero
832  IF ( PRESENT(azimuth_angle_ad) ) azimuth_angle_ad = zero
833  IF ( PRESENT(transmittance_ad) ) transmittance_ad = zero
834  RETURN
835  END IF
836 
837 
838  ! Compute the adjoint of the...
839  ! ...reflectivities
840  reflectivity_ad(u_idx:v_idx) = zero ! 3rd, 4th Stokes from atmosphere are not included.
841 
842  emissivity_ad(ih_idx) = emissivity_ad(ih_idx) - ivar%Rh_Mod*reflectivity_ad(ih_idx)
843  rh_mod_ad = (one-ivar%e(ih_idx))*reflectivity_ad(ih_idx)
844  reflectivity_ad(ih_idx) = zero
845 
846  emissivity_ad(iv_idx) = emissivity_ad(iv_idx) - ivar%Rv_Mod*reflectivity_ad(iv_idx)
847  rv_mod_ad = (one-ivar%e(iv_idx))*reflectivity_ad(iv_idx)
848  reflectivity_ad(iv_idx) = zero
849 
850  ! ...emissivities
851  e_azimuth_ad(v_idx) = emissivity_ad(v_idx); emissivity_ad(v_idx) = zero
852  e_azimuth_ad(u_idx) = emissivity_ad(u_idx); emissivity_ad(u_idx) = zero
853  e_azimuth_ad(ih_idx) = emissivity_ad(ih_idx) ! No zero of Emissivity_AD(Ih_IDX)
854  e_azimuth_ad(iv_idx) = emissivity_ad(iv_idx) ! No zero of Emissivity_AD(Ih_IDX)
855 
856 
857  ! Anisotropic downward radiation correction calculation
858  IF ( PRESENT(transmittance_ad) .AND. ivar%Transmittance_Valid ) THEN
860  mwwatercoeff%RCCoeff, &
861  rv_mod_ad , &
862  rh_mod_ad , &
863  wind_speed_ad , &
864  transmittance_ad, &
865  ivar%rcVar )
866  ELSE
867  rv_mod_ad = zero
868  rh_mod_ad = zero
869  END IF
870 
871 
872  ! Azimuthal component calculation
873  IF ( PRESENT(azimuth_angle_ad) .AND. ivar%Azimuth_Angle_Valid ) THEN
874  IF ( mwwatercoeff%Version == fastem6 ) THEN
876  mwwatercoeff%AZCoeff, &
877  e_azimuth_ad , &
878  wind_speed_ad , &
879  azimuth_angle_ad, &
880  ivar%aeF6Var )
881  ELSE
882  CALL azimuth_emissivity_ad( &
883  mwwatercoeff%AZCoeff, &
884  e_azimuth_ad , &
885  wind_speed_ad , &
886  azimuth_angle_ad, &
887  ivar%aeVar )
888  END IF
889  ELSE
890  e_azimuth_ad = zero
891  END IF
892 
893  ! Compute the adjoint of the first two Stokes components of the emissivity
894  rh_foam_ad = -ivar%Foam_Cover *emissivity_ad(ih_idx)
895  foam_cover_ad = (ivar%Rh-ivar%Rh_Foam)*emissivity_ad(ih_idx)
896  rh_ad = (ivar%Foam_Cover-one) *emissivity_ad(ih_idx)
897  emissivity_ad(ih_idx) = zero
898  rh_large_ad = -rh_ad
899  f_small_ad = ivar%Rh_Fresnel*rh_ad
900  rh_fresnel_ad = rh_ad*ivar%F_Small
901  rh_ad = zero
902 
903  rv_foam_ad = -ivar%Foam_Cover *emissivity_ad(iv_idx)
904  foam_cover_ad = (ivar%Rv-ivar%Rv_Foam)*emissivity_ad(iv_idx) + foam_cover_ad
905  rv_ad = (ivar%Foam_Cover-one) *emissivity_ad(iv_idx)
906  emissivity_ad(iv_idx) = zero
907  rv_large_ad = -rv_ad
908  f_small_ad = f_small_ad + ivar%Rv_Fresnel*rv_ad
909  rv_fresnel_ad = rv_ad*ivar%F_Small
910  rv_ad = zero
911 
912 
913  ! Small scale Correction Calculation AD
915  mwwatercoeff%SSCCoeff, &
916  f_small_ad , &
917  wind_speed_ad, &
918  ivar%sscVar )
919 
920 
921  ! Large Scale Correction Calculation
923  rv_large_ad , &
924  rh_large_ad , &
925  wind_speed_ad, &
926  ivar%lscVar )
927 
928 
929  ! Foam coverage calculation
930  CALL foam_coverage_ad( &
931  mwwatercoeff%FCCoeff, &
932  ivar%Wind_Speed, &
933  foam_cover_ad, &
934  wind_speed_ad )
935 
936 
937  ! Foam reflectivity "calculation"
938  rv_foam_ad = zero
939  rh_foam_ad = zero
940 
941 
942  ! Fresnel reflectivity calculation
943  permittivity_ad = zero
944  CALL fresnel_reflectivity_ad( rv_fresnel_ad, rh_fresnel_ad, ivar%cos_z, &
945  permittivity_ad, &
946  ivar%fVar )
947 
948  ! Permittivity calculation
949  CALL ocean_permittivity_ad( permittivity_ad, ivar%Frequency, &
950  temperature_ad, salinity_ad, &
951  ivar%pVar )
952 
953  END SUBROUTINE compute_fastemx_ad
954 
955 
956 !################################################################################
957 !################################################################################
958 !## ##
959 !## ## PRIVATE MODULE ROUTINES ## ##
960 !## ##
961 !################################################################################
962 !################################################################################
963 
964 
965 
966 END MODULE crtm_fastemx
Definition: Liu.f90:15
subroutine, public azimuth_emissivity_tl(AZCoeff, Wind_Speed_TL, Azimuth_Angle_TL, e_Azimuth_TL, iVar)
real(fp), parameter, public zero
integer, parameter v_idx
subroutine, public compute_fastemx_tl(MWwaterCoeff, Temperature_TL, Salinity_TL, Wind_Speed_TL, iVar, Emissivity_TL, Reflectivity_TL, Azimuth_Angle_TL, Transmittance_TL)
integer, parameter, public fp
Definition: Type_Kinds.f90:124
real(fp), parameter, public three
subroutine, public small_scale_correction(SSCCoeff, Frequency, cos_Z, Wind_Speed, Correction, iVar)
subroutine, public liu_ocean_permittivity(Temperature, Salinity, Frequency, Permittivity, iVar)
Definition: Liu.f90:212
subroutine, public azimuth_emissivity_f6(AZCoeff, Wind_Speed, Azimuth_Angle, Frequency, Zenith_Angle, e_Azimuth, iVar)
subroutine, public azimuth_emissivity_ad(AZCoeff, e_Azimuth_AD, Wind_Speed_AD, Azimuth_Angle_AD, iVar)
subroutine, public fresnel_reflectivity_ad(Rv_AD, Rh_AD, cos_i, permittivity_AD, iVar)
Definition: Fresnel.f90:324
integer, parameter u_idx
subroutine, public foam_coverage_ad(FCCoeff, wind_speed, coverage_AD, wind_speed_AD)
integer, parameter ih_idx
subroutine, public foam_reflectivity(FRCoeff, Zenith_Angle, Frequency, Rv, Rh)
subroutine, public large_scale_correction(LSCCoeff, Frequency, cos_Z, Wind_Speed, Rv_Large, Rh_Large, iVar)
subroutine, public foam_coverage_tl(FCCoeff, wind_speed, wind_speed_TL, coverage_TL)
real(fp), parameter invalid_transmittance
subroutine, public azimuth_emissivity(AZCoeff, Wind_Speed, Azimuth_Angle, Frequency, cos_z, e_Azimuth, iVar)
integer, parameter fastem6
subroutine, public reflection_correction_ad(RCCoeff, Rv_Mod_AD, Rh_Mod_AD, Wind_Speed_AD, Transmittance_AD, iVar)
real(fp), parameter invalid_azimuth_angle
real(fp), parameter, public one
subroutine, public small_scale_correction_tl(SSCCoeff, Wind_Speed_TL, Correction_TL, iVar)
subroutine, public large_scale_correction_tl(Wind_Speed_TL, Rv_Large_TL, Rh_Large_TL, iVar)
real(fp), parameter, public two
subroutine, public compute_fastemx_ad(MWwaterCoeff, Emissivity_AD, Reflectivity_AD, iVar, Temperature_AD, Salinity_AD, Wind_Speed_AD, Azimuth_Angle_AD, Transmittance_AD)
real(fp), parameter, public degrees_to_radians
real(fp), parameter, public point_5
subroutine, public small_scale_correction_ad(SSCCoeff, Correction_AD, Wind_Speed_AD, iVar)
subroutine, public reflection_correction_tl(RCCoeff, Wind_Speed_TL, Transmittance_TL, Rv_Mod_TL, Rh_Mod_TL, iVar)
subroutine, public azimuth_emissivity_f6_tl(AZCoeff, Wind_Speed_TL, Azimuth_Angle_TL, e_Azimuth_TL, iVar)
subroutine, public liu_ocean_permittivity_ad(Permittivity_AD, Frequency, Temperature_AD, Salinity_AD, iVar)
Definition: Liu.f90:568
integer, parameter iv_idx
subroutine, public liu_ocean_permittivity_tl(Temperature_TL, Salinity_TL, Frequency, Permittivity_TL, iVar)
Definition: Liu.f90:381
subroutine, public large_scale_correction_ad(Rv_Large_AD, Rh_Large_AD, Wind_Speed_AD, iVar)
subroutine, public compute_fastemx(MWwaterCoeff, Frequency, Zenith_Angle, Temperature, Salinity, Wind_Speed, iVar, Emissivity, Reflectivity, Azimuth_Angle, Transmittance)
subroutine, public fresnel_reflectivity(permittivity, cos_i, Rv, Rh, iVar)
Definition: Fresnel.f90:127
subroutine, public reflection_correction(RCCoeff, Frequency, cos_z, Wind_Speed, Transmittance, Rv_Mod, Rh_Mod, iVar)
subroutine, public fresnel_reflectivity_tl(permittivity_TL, cos_i, Rv_TL, Rh_TL, iVar)
Definition: Fresnel.f90:222
subroutine, public azimuth_emissivity_f6_ad(AZCoeff, e_Azimuth_AD, Wind_Speed_AD, Azimuth_Angle_AD, iVar)
real(fp), parameter, public pi
subroutine, public foam_coverage(FCCoeff, wind_speed, coverage)