FV3 Bundle
Foam_Utility_Module.f90
Go to the documentation of this file.
1 !
2 ! Helper module containing the foam-related utility routines for the
3 ! CRTM implementation of FASTEM4 and FASTEM5
4 !
5 !
6 ! CREATION HISTORY:
7 ! Written by: Original FASTEM1-5 authors
8 !
9 ! Refactored by: Paul van Delst, November 2011
10 ! paul.vandelst@noaa.gov
11 !
12 
14 
15  ! -----------------
16  ! Environment setup
17  ! -----------------
18  ! Module use
19  USE type_kinds , ONLY: fp
21  ! Disable implicit typing
22  IMPLICIT NONE
23 
24 
25  ! ------------
26  ! Visibilities
27  ! ------------
28  PRIVATE
29  PUBLIC :: foam_coverage
30  PUBLIC :: foam_coverage_tl
31  PUBLIC :: foam_coverage_ad
32  PUBLIC :: foam_reflectivity
33 
34 
35  ! -----------------
36  ! Module parameters
37  ! -----------------
38  CHARACTER(*), PARAMETER :: module_version_id = &
39  '$Id: Foam_Utility_Module.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
40 
41  ! Literal constants
42  REAL(fp), PARAMETER :: zero = 0.0_fp
43  REAL(fp), PARAMETER :: one = 1.0_fp
44  REAL(fp), PARAMETER :: two = 2.0_fp
45 
46 
47 CONTAINS
48 
49 
50  ! ===================================================================
51  ! Foam coverage.
52  !
53  ! Monahan, E.C., and O'Muircheartaigh, I.G., (1986)
54  ! Whitecaps and the passive remote sensing of the ocean surface,
55  ! International Journal of Remote Sensing, 7, pp627-642.
56  !
57  ! The neutral stability condition is used here (i.e. the difference
58  ! between the skin and air temperature is assumed to be zero) so
59  ! that the form of the foam coverage equation is the same as in
60  ! Tang (1974) and Liu et al. (1998)..
61  !
62  ! Liu, Q. et al. (1998) Monte Carlo simulations of the
63  ! microwave emissivity of the sea surface.
64  ! JGR, 103(C11), pp24983-24989
65  !
66  ! Tang, C. (1974) The effect of droplets in the air-sea
67  ! transition zone on the sea brightness temperature.
68  ! J. Phys. Oceanography, 4, pp579-593.
69  !
70  ! ===================================================================
71  ! Forward model
72  SUBROUTINE foam_coverage(FCCoeff, wind_speed, coverage)
73  TYPE(fitcoeff_1d_type), INTENT(IN) :: fccoeff
74  REAL(fp) , INTENT(IN) :: wind_speed
75  REAL(fp) , INTENT(OUT) :: coverage
76  IF ( wind_speed < zero ) THEN
77  coverage = zero
78  RETURN
79  END IF
80  coverage = fccoeff%C(1) * (wind_speed**fccoeff%C(2))
81  END SUBROUTINE foam_coverage
82 
83  ! Tangent-linear model
84  SUBROUTINE foam_coverage_tl(FCCoeff, wind_speed, wind_speed_TL, coverage_TL)
85  TYPE(fitcoeff_1d_type), INTENT(IN) :: fccoeff
86  REAL(fp) , INTENT(IN) :: wind_speed
87  REAL(fp) , INTENT(IN) :: wind_speed_tl
88  REAL(fp) , INTENT(OUT) :: coverage_tl
89  IF ( wind_speed < zero ) THEN
90  coverage_tl = zero
91  RETURN
92  END IF
93  coverage_tl = fccoeff%C(1)*fccoeff%C(2) * (wind_speed**(fccoeff%C(2)-one)) * wind_speed_tl
94  END SUBROUTINE foam_coverage_tl
95 
96  ! Adjoint model
97  SUBROUTINE foam_coverage_ad(FCCoeff, wind_speed, coverage_AD, wind_speed_AD)
98  TYPE(fitcoeff_1d_type), INTENT(IN) :: fccoeff
99  REAL(fp) , INTENT(IN) :: wind_speed ! Input
100  REAL(fp) , INTENT(IN OUT) :: coverage_ad ! Input
101  REAL(fp) , INTENT(IN OUT) :: wind_speed_ad ! Output
102  IF ( wind_speed < zero ) THEN
103  coverage_ad = zero
104  RETURN
105  END IF
106  wind_speed_ad = wind_speed_ad + &
107  fccoeff%C(1)*fccoeff%C(2) * (wind_speed**(fccoeff%C(2)-one)) * coverage_ad
108  coverage_ad = zero
109  END SUBROUTINE foam_coverage_ad
110 
111 
112  ! =============================================================
113  ! Foam reflectivity
114  !
115  ! See section d in
116  !
117  ! Kazumori, M. et al. (2008) Impact Study of AMSR-E Radiances
118  ! in the NCEP Global Data Assimilation System,
119  ! Monthly Weather Review, 136, pp541-559
120  !
121  ! Function dependence is on zenith angle only so no TL
122  ! or AD routine.
123  ! =============================================================
124  SUBROUTINE foam_reflectivity( &
125  FRCoeff , &
126  Zenith_Angle, &
127  Frequency , &
128  Rv , &
129  Rh )
130  ! Arguments
131  TYPE(fitcoeff_1d_type), INTENT(IN) :: frcoeff
132  REAL(fp) , INTENT(IN) :: zenith_angle
133  REAL(fp) , INTENT(IN) :: frequency
134  REAL(fp) , INTENT(OUT) :: rv, rh
135  ! Local variables
136  REAL(fp) :: factor
137 
138  ! The vertical component is a fixed value
139  rv = one - frcoeff%C(1) ! Fixed nadir emissivity
140 
141  ! The horizontal component uses a regression equation
142  ! to compute a factor modifying the nadir emissivity
143  factor = one + zenith_angle*(frcoeff%C(2) + &
144  zenith_angle*(frcoeff%C(3) + &
145  zenith_angle*frcoeff%C(4) ) )
146  rh = one - factor*frcoeff%C(1)
147 
148  ! Frequency correction
149  factor = frcoeff%C(5) * exp(frcoeff%C(6)*frequency)
150  rv = rv * factor
151  rh = rh * factor
152 
153  END SUBROUTINE foam_reflectivity
154 
155 END MODULE foam_utility_module
real(fp), parameter, public zero
integer, parameter, public fp
Definition: Type_Kinds.f90:124
subroutine, public foam_coverage_ad(FCCoeff, wind_speed, coverage_AD, wind_speed_AD)
subroutine, public foam_reflectivity(FRCoeff, Zenith_Angle, Frequency, Rv, Rh)
subroutine, public foam_coverage_tl(FCCoeff, wind_speed, wind_speed_TL, coverage_TL)
real(fp), parameter, public one
real(fp), parameter, public two
character(*), parameter module_version_id
subroutine, public foam_coverage(FCCoeff, wind_speed, coverage)