FV3 Bundle
Fresnel.f90
Go to the documentation of this file.
1 !
2 ! Fresnel
3 !
4 ! Module containing routines to compute Fresnel reflectivities.
5 !
6 !
7 ! CREATION HISTORY:
8 ! Written by: Masahiro Kazumori, JCSDA
9 ! Masahiro.Kazumori@noaa.gov
10 ! Modified by: Paul van Delst, CIMSS/SSEC 11-Apr-2007
11 ! paul.vandelst@noaa.gov
12 
13 MODULE fresnel
14 
15  ! -----------------
16  ! Environment setup
17  ! -----------------
18  ! Module use
19  USE type_kinds, ONLY: fp
20  ! Disable implicit typing
21  IMPLICIT NONE
22 
23 
24  ! ------------
25  ! Visibilities
26  ! ------------
27  PRIVATE
28  PUBLIC :: ivar_type
29  PUBLIC :: fresnel_reflectivity
30  PUBLIC :: fresnel_reflectivity_tl
31  PUBLIC :: fresnel_reflectivity_ad
32 
33  ! -----------------
34  ! Module parameters
35  ! -----------------
36  ! RCS Id for the module
37  CHARACTER(*), PARAMETER :: module_rcs_id = &
38  '$Id: Fresnel.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
39  REAL(fp), PARAMETER :: zero = 0.0_fp
40  REAL(fp), PARAMETER :: point5 = 0.5_fp
41  REAL(fp), PARAMETER :: one = 1.0_fp
42  REAL(fp), PARAMETER :: two = 2.0_fp
43 
44 
45  ! --------------------------------------
46  ! Structure definition to hold forward
47  ! variables across FWD, TL, and AD calls
48  ! --------------------------------------
49  TYPE :: ivar_type
50  PRIVATE
51  ! The intermediate terms
52  COMPLEX(fp) :: z1, z2
53  ! The real and imaginary components
54  REAL(fp) :: rzrv,izrv ! Vertical
55  REAL(fp) :: rzrh,izrh ! Horizontal
56  END TYPE ivar_type
57 
58 
59 CONTAINS
60 
61 
62 !--------------------------------------------------------------------------------
63 !
64 ! NAME:
65 ! Fresnel_Reflectivity
66 !
67 ! PURPOSE:
68 ! Subroutine to compute Fresnel reflectivities
69 !
70 ! CALLING SEQUENCE:
71 ! CALL Fresnel_Reflectivity( permittivity, & ! Input
72 ! cos_i , & ! Input
73 ! Rv , & ! Output
74 ! Rh , & ! Output
75 ! iVar ) ! Internal variable output
76 !
77 ! INPUT ARGUMENTS:
78 ! permittivity: Permittivity of medium
79 ! UNITS: Farads per metre (F.m^-1)
80 ! TYPE: COMPLEX(fp)
81 ! DIMENSION: Scalar
82 ! ATTRIBUTES: INTENT(IN)
83 !
84 ! cos_i: Cosine of incidence angle
85 ! UNITS: N/A
86 ! TYPE: REAL(fp)
87 ! DIMENSION: Scalar
88 ! ATTRIBUTES: INTENT(IN)
89 !
90 ! OUTPUT ARGUMENTS:
91 ! Rv: Reflectivity for polarisation parallel to the
92 ! plane of incidence (i.e. vertical polarization)
93 ! UNITS: N/A
94 ! TYPE: REAL(fp)
95 ! DIMENSION: Scalar
96 ! ATTRIBUTES: INTENT(OUT)
97 !
98 ! Rh: Reflectivity for polarisation perpendicular to the
99 ! plane of incidence (i.e. horizontal polarization)
100 ! UNITS: N/A
101 ! TYPE: REAL(fp)
102 ! DIMENSION: Scalar
103 ! ATTRIBUTES: INTENT(OUT)
104 !
105 ! iVar: Structure containing internal variables required for
106 ! subsequent tangent-linear or adjoint model calls.
107 ! The contents of this structure are NOT accessible
108 ! outside of the Fresnel module.
109 ! UNITS: N/A
110 ! TYPE: TYPE(iVar_type)
111 ! DIMENSION: Scalar
112 ! ATTRIBUTES: INTENT(OUT)
113 !
114 ! CREATION HISTORY:
115 ! Written by: Masahiro Kazumori, JCSDA
116 ! Masahiro.Kazumori@noaa.gov
117 ! Modified by: Paul van Delst, CIMSS/SSEC 11-Apr-2007
118 ! paul.vandelst@noaa.gov
119 !
120 !--------------------------------------------------------------------------------
121 
122  SUBROUTINE fresnel_reflectivity( permittivity, & ! Input
123  cos_i , & ! Input
124  Rv , & ! Output
125  Rh , & ! Output
126  iVar ) ! Internal variable output
127  ! Arguments
128  COMPLEX(fp), INTENT(IN) :: permittivity
129  REAL(fp), INTENT(IN) :: cos_i
130  REAL(fp), INTENT(OUT) :: rv
131  REAL(fp), INTENT(OUT) :: rh
132  TYPE(ivar_type), INTENT(IN OUT) :: ivar
133  ! Local variables
134  COMPLEX(fp) :: zrv ! Vertical
135  COMPLEX(fp) :: zrh ! Horizontal
136 
137  ! Compute the complex reflectivity components
138  ivar%z1 = sqrt(permittivity - one + (cos_i*cos_i))
139  ivar%z2 = permittivity * cos_i
140  zrh = (cos_i -ivar%z1) / (cos_i +ivar%z1)
141  zrv = (ivar%z2-ivar%z1) / (ivar%z2+ivar%z1)
142 
143  ! The square of the vertical abs value
144  ivar%rzRv = REAL(zrv,fp)
145  ivar%izRv = aimag(zrv)
146  rv = ivar%rzRv**2 + ivar%izRv**2
147 
148  ! The square of the horizontal abs value
149  ivar%rzRh = REAL(zrh,fp)
150  ivar%izRh = aimag(zrh)
151  rh = ivar%rzRh**2 + ivar%izRh**2
152 
153  END SUBROUTINE fresnel_reflectivity
154 
155 
156 !--------------------------------------------------------------------------------
157 !
158 ! NAME:
159 ! Fresnel_Reflectivity_TL
160 !
161 ! PURPOSE:
162 ! Subroutine to compute tangent-linear Fresnel reflectivities
163 !
164 ! CALLING SEQUENCE:
165 ! CALL Fresnel_Reflectivity_TL( permittivity_TL, & ! Input
166 ! cos_i , & ! Input
167 ! Rv_TL , & ! Output
168 ! Rh_TL , & ! Output
169 ! iVar ) ! Internal variable input
170 !
171 ! INPUT ARGUMENTS:
172 ! permittivity_TL: Tangent-linear permittivity of medium
173 ! UNITS: Farads per metre (F.m^-1)
174 ! TYPE: COMPLEX(fp)
175 ! DIMENSION: Scalar
176 ! ATTRIBUTES: INTENT(IN)
177 !
178 ! cos_i Cosine of incidence angle
179 ! UNITS: N/A
180 ! TYPE: REAL(fp)
181 ! DIMENSION: Scalar
182 ! ATTRIBUTES: INTENT(IN)
183 !
184 ! iVar: Structure containing internal variables required for
185 ! subsequent tangent-linear or adjoint model calls.
186 ! The contents of this structure are NOT accessible
187 ! outside of the Fresnel module.
188 ! UNITS: N/A
189 ! TYPE: TYPE(iVar_type)
190 ! DIMENSION: Scalar
191 ! ATTRIBUTES: INTENT(IN)
192 !
193 ! OUTPUT ARGUMENTS:
194 ! Rv_TL Tangent-linear reflectivity for polarisation parallel
195 ! to the plane of incidence (i.e. vertical polarization)
196 ! UNITS: N/A
197 ! TYPE: REAL(fp)
198 ! DIMENSION: Scalar
199 ! ATTRIBUTES: INTENT(OUT)
200 !
201 ! Rh_TL Tangent-linear reflectivity for polarisation
202 ! perpendicular to the plane of incidence
203 ! (i.e. horizontal polarization)
204 ! UNITS: N/A
205 ! TYPE: REAL(fp)
206 ! DIMENSION: Scalar
207 ! ATTRIBUTES: INTENT(OUT)
208 !
209 ! CREATION HISTORY:
210 ! Written by: Masahiro Kazumori, JCSDA
211 ! Masahiro.Kazumori@noaa.gov
212 ! Modified by: Paul van Delst, CIMSS/SSEC 11-Apr-2007
213 ! paul.vandelst@noaa.gov
214 !
215 !--------------------------------------------------------------------------------
216 
217  SUBROUTINE fresnel_reflectivity_tl( permittivity_TL, & ! Input
218  cos_i , & ! Input
219  Rv_TL , & ! Output
220  Rh_TL , & ! Output
221  iVar ) ! Internal variable input
222  ! Arguments
223  COMPLEX(fp), INTENT(IN) :: permittivity_tl
224  REAL(fp), INTENT(IN) :: cos_i
225  REAL(fp), INTENT(OUT) :: rv_tl
226  REAL(fp), INTENT(OUT) :: rh_tl
227  TYPE(ivar_type), INTENT(IN) :: ivar
228  ! Local variables
229  COMPLEX(fp) :: z1_tl, z2_tl
230  COMPLEX(fp) :: zrv_tl ! Vertical
231  COMPLEX(fp) :: zrh_tl ! Horizontal
232  REAL(fp) :: rzrv_tl,izrv_tl ! Vertical
233  REAL(fp) :: rzrh_tl,izrh_tl ! Horizontal
234 
235  ! Compute the tangent-linear complex reflectivity components
236  z1_tl = point5 * permittivity_tl / ivar%z1
237  z2_tl = cos_i * permittivity_tl
238  zrh_tl = -two * cos_i * z1_tl / (cos_i+ivar%z1)**2
239  zrv_tl = two * (ivar%z1*z2_tl - ivar%z2*z1_tl) / (ivar%z2+ivar%z1)**2
240 
241  ! The square of the tangent-linear vertical abs value
242  rzrv_tl = REAL(zrv_tl,fp)
243  izrv_tl = aimag(zrv_tl)
244  rv_tl = two * (ivar%rzRv*rzrv_tl + ivar%izRv*izrv_tl)
245 
246  ! The square of the tangent-linear horizontal abs value
247  rzrh_tl = REAL(zrh_tl,fp)
248  izrh_tl = aimag(zrh_tl)
249  rh_tl = two * (ivar%rzRh*rzrh_tl + ivar%izRh*izrh_tl)
250 
251  END SUBROUTINE fresnel_reflectivity_tl
252 
253 
254 !--------------------------------------------------------------------------------
255 !
256 ! NAME:
257 ! Fresnel_Reflectivity_AD
258 !
259 ! PURPOSE:
260 ! Subroutine to compute Fresnel reflectivity adjoints
261 !
262 ! CALLING SEQUENCE:
263 ! CALL Fresnel_Reflectivity_AD( Rv_AD , & ! Input
264 ! Rh_AD , & ! Input
265 ! cos_i , & ! Input
266 ! permittivity_AD, & ! Output
267 ! iVar ) ! Internal variable input
268 !
269 ! INPUT ARGUMENTS:
270 ! Rv_AD Adjoint reflectivity for polarisation parallel
271 ! to the plane of incidence (i.e. vertical polarization)
272 ! ** Set to ZERO on exit **
273 ! UNITS: N/A
274 ! TYPE: REAL(fp)
275 ! DIMENSION: Scalar
276 ! ATTRIBUTES: INTENT(IN OUT)
277 !
278 ! Rh_AD Adjoint reflectivity for polarisation
279 ! perpendicular to the plane of incidence
280 ! (i.e. horizontal polarization)
281 ! ** Set to ZERO on exit **
282 ! UNITS: N/A
283 ! TYPE: REAL(fp)
284 ! DIMENSION: Scalar
285 ! ATTRIBUTES: INTENT(IN OUT)
286 !
287 ! cos_i Cosine of incidence angle
288 ! UNITS: N/A
289 ! TYPE: REAL(fp)
290 ! DIMENSION: Scalar
291 ! ATTRIBUTES: INTENT(IN)
292 !
293 ! iVar: Structure containing internal variables required for
294 ! subsequent tangent-linear or adjoint model calls.
295 ! The contents of this structure are NOT accessible
296 ! outside of the Fresnel module.
297 ! UNITS: N/A
298 ! TYPE: TYPE(iVar_type)
299 ! DIMENSION: Scalar
300 ! ATTRIBUTES: INTENT(IN)
301 !
302 ! OUTPUT ARGUMENTS:
303 ! permittivity_AD: Adjoint permittivity of medium, dR/de,
304 ! where R == reflectivity
305 ! e == permittivity
306 ! UNITS: inverse Farads per metre (F.m^-1)^-1
307 ! TYPE: COMPLEX(fp)
308 ! DIMENSION: Scalar
309 ! ATTRIBUTES: INTENT(IN OUT)
310 !
311 ! CREATION HISTORY:
312 ! Written by: Masahiro Kazumori, JCSDA
313 ! Masahiro.Kazumori@noaa.gov
314 ! Modified by: Paul van Delst, CIMSS/SSEC 11-Apr-2007
315 ! paul.vandelst@noaa.gov
316 !
317 !--------------------------------------------------------------------------------
318 
319  SUBROUTINE fresnel_reflectivity_ad( Rv_AD , & ! Input
320  Rh_AD , & ! Input
321  cos_i , & ! Input
322  permittivity_AD, & ! Output
323  iVar ) ! Internal variable input
324  ! Arguments
325  REAL(fp), INTENT(IN OUT) :: rv_ad
326  REAL(fp), INTENT(IN OUT) :: rh_ad
327  REAL(fp), INTENT(IN) :: cos_i
328  COMPLEX(fp), INTENT(IN OUT) :: permittivity_ad
329  TYPE(ivar_type), INTENT(IN) :: ivar
330  ! Local variables
331  COMPLEX(fp) :: z1_ad, z2_ad
332  COMPLEX(fp) :: zrv_ad ! Vertical
333  COMPLEX(fp) :: zrh_ad ! Horizontal
334  REAL(fp) :: rzrv_ad,izrv_ad ! Vertical
335  REAL(fp) :: rzrh_ad,izrh_ad ! Horizontal
336  COMPLEX(fp) :: denom
337 
338  ! The adjoint of the horizontal reflectivity
339  izrh_ad = two*ivar%izRh*rh_ad
340  rzrh_ad = two*ivar%rzRh*rh_ad
341  rh_ad = zero
342  zrh_ad = cmplx(rzrh_ad, -izrh_ad, fp) ! complex conjugate
343 
344  ! The adjoint of the vertical reflectivity
345  izrv_ad = two*ivar%izRv*rv_ad
346  rzrv_ad = two*ivar%rzRv*rv_ad
347  rv_ad = zero
348  zrv_ad = cmplx(rzrv_ad, -izrv_ad, fp) ! complex conjugate
349 
350  ! The adjoint of the complex vertical polarised component
351  denom = (ivar%z2+ivar%z1)**2
352  z1_ad = -two*ivar%z2*zrv_ad / denom
353  z2_ad = two*ivar%z1*zrv_ad / denom
354 
355  ! The adjoint of the complex horizontal polarised component
356  z1_ad = z1_ad - ( two*cos_i*zrh_ad / (cos_i+ivar%z1)**2 )
357 
358  ! The adjoint of the preserved variables
359  permittivity_ad = permittivity_ad + conjg(cos_i*z2_ad)
360  permittivity_ad = permittivity_ad + conjg(point5*z1_ad/ivar%z1)
361 
362  END SUBROUTINE fresnel_reflectivity_ad
363 
364 END MODULE fresnel
real(fp), parameter, public zero
integer, parameter, public fp
Definition: Type_Kinds.f90:124
subroutine, public fresnel_reflectivity_ad(Rv_AD, Rh_AD, cos_i, permittivity_AD, iVar)
Definition: Fresnel.f90:324
real(fp), parameter point5
Definition: Fresnel.f90:40
character(*), parameter module_rcs_id
Definition: Fresnel.f90:37
real(fp), parameter, public one
real(fp), parameter, public two
subroutine, public fresnel_reflectivity(permittivity, cos_i, Rv, Rh, iVar)
Definition: Fresnel.f90:127
subroutine, public fresnel_reflectivity_tl(permittivity_TL, cos_i, Rv_TL, Rh_TL, iVar)
Definition: Fresnel.f90:222