FV3 Bundle
CRTM_MW_Ice_SfcOptics.f90
Go to the documentation of this file.
1 !
2 ! CRTM_MW_Ice_SfcOptics
3 !
4 ! Module to compute the surface optical properties for ICE surfaces at
5 ! microwave frequencies required for determining the ICE surface
6 ! contribution to the radiative transfer.
7 !
8 ! This module is provided to allow developers to "wrap" their existing
9 ! codes inside the provided functions to simplify integration into
10 ! the main CRTM_SfcOptics module.
11 !
12 !
13 ! CREATION HISTORY:
14 ! Written by: Paul van Delst, 23-Jun-2005
15 ! paul.vandelst@noaa.gov
16 !
17 ! Modified by: Banghua Yan, 03-Oct-2007
18 ! Banghua.Yan@noaa.gov
19 !
20 
22 
23  ! -----------------
24  ! Environment setup
25  ! -----------------
26  ! Module use
27  USE type_kinds, ONLY: fp
28  USE message_handler, ONLY: success
29  USE crtm_parameters, ONLY: zero, one
30  USE crtm_spccoeff, ONLY: sc
35  USE crtm_sensorinfo, ONLY: wmo_amsua, &
36  wmo_amsub, &
37  wmo_amsre, &
38  wmo_ssmi , &
39  wmo_msu , &
40  wmo_mhs , &
41  wmo_ssmis
48  ! Disable implicit typing
49  IMPLICIT NONE
50 
51 
52  ! ------------
53  ! Visibilities
54  ! ------------
55  ! Everything private by default
56  PRIVATE
57  ! Data types
58  PUBLIC :: ivar_type
59  ! Science routines
60  PUBLIC :: compute_mw_ice_sfcoptics
63 
64 
65  ! -----------------
66  ! Module parameters
67  ! -----------------
68  CHARACTER(*), PARAMETER :: module_version_id = &
69  '$Id: CRTM_MW_Ice_SfcOptics.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
70 
71 
72  ! --------------------------------------
73  ! Structure definition to hold forward
74  ! variables across FWD, TL, and AD calls
75  ! --------------------------------------
76  TYPE :: ivar_type
77  PRIVATE
78  INTEGER :: dummy = 0
79  END TYPE ivar_type
80 
81 
82 CONTAINS
83 
84 
85 !----------------------------------------------------------------------------------
86 !:sdoc+:
87 !
88 ! NAME:
89 ! Compute_MW_Ice_SfcOptics
90 !
91 ! PURPOSE:
92 ! Function to compute the surface emissivity and reflectivity at microwave
93 ! frequencies over an ice surface.
94 !
95 ! This function is a wrapper for third party code.
96 !
97 ! CALLING SEQUENCE:
98 ! Error_Status = Compute_MW_Ice_SfcOptics( &
99 ! Surface , &
100 ! GeometryInfo, &
101 ! SensorIndex , &
102 ! ChannelIndex, &
103 ! SfcOptics )
104 !
105 ! INPUTS:
106 ! Surface: CRTM_Surface structure containing the surface state
107 ! data.
108 ! UNITS: N/A
109 ! TYPE: CRTM_Surface_type
110 ! DIMENSION: Scalar
111 ! ATTRIBUTES: INTENT(IN)
112 !
113 ! GeometryInfo: CRTM_GeometryInfo structure containing the
114 ! view geometry information.
115 ! UNITS: N/A
116 ! TYPE: CRTM_GeometryInfo_type
117 ! DIMENSION: Scalar
118 ! ATTRIBUTES: INTENT(IN)
119 !
120 ! SensorIndex: Sensor index id. This is a unique index associated
121 ! with a (supported) sensor used to access the
122 ! shared coefficient data for a particular sensor.
123 ! See the ChannelIndex argument.
124 ! UNITS: N/A
125 ! TYPE: INTEGER
126 ! DIMENSION: Scalar
127 ! ATTRIBUTES: INTENT(IN)
128 !
129 ! ChannelIndex: Channel index id. This is a unique index associated
130 ! with a (supported) sensor channel used to access the
131 ! shared coefficient data for a particular sensor's
132 ! channel.
133 ! See the SensorIndex argument.
134 ! UNITS: N/A
135 ! TYPE: INTEGER
136 ! DIMENSION: Scalar
137 ! ATTRIBUTES: INTENT(IN)
138 !
139 ! OUTPUTS:
140 ! SfcOptics: CRTM_SfcOptics structure containing the surface
141 ! optical properties required for the radiative
142 ! transfer calculation. On input the Angle component
143 ! is assumed to contain data.
144 ! UNITS: N/A
145 ! TYPE: CRTM_SfcOptics_type
146 ! DIMENSION: Scalar
147 ! ATTRIBUTES: INTENT(IN OUT)
148 !
149 ! FUNCTION RESULT:
150 ! Error_Status: The return value is an integer defining the error status.
151 ! The error codes are defined in the Message_Handler module.
152 ! If == SUCCESS the computation was sucessful
153 ! == FAILURE an unrecoverable error occurred
154 ! UNITS: N/A
155 ! TYPE: INTEGER
156 ! DIMENSION: Scalar
157 !
158 ! COMMENTS:
159 ! Note the INTENT on the output SfcOptics argument is IN OUT rather
160 ! than just OUT as it is assumed to contain some data upon input.
161 !
162 !:sdoc-:
163 !----------------------------------------------------------------------------------
164 
165  FUNCTION compute_mw_ice_sfcoptics( &
166  Surface , & ! Input
167  GeometryInfo, & ! Input
168  SensorIndex , & ! Input
169  ChannelIndex, & ! Input
170  SfcOptics ) & ! Output
171  result( error_status )
172  ! Arguments
173  TYPE(crtm_surface_type), INTENT(IN) :: surface
174  TYPE(crtm_geometryinfo_type), INTENT(IN) :: geometryinfo
175  INTEGER, INTENT(IN) :: sensorindex
176  INTEGER, INTENT(IN) :: channelindex
177  TYPE(crtm_sfcoptics_type), INTENT(IN OUT) :: sfcoptics
178  ! Function result
179  INTEGER :: error_status
180  ! Local parameters
181  CHARACTER(*), PARAMETER :: routine_name = 'Compute_MW_Ice_SfcOptics'
182  REAL(fp), PARAMETER :: default_emissivity = 0.92_fp
183  REAL(fp), PARAMETER :: not_used(4) = -99.9_fp
184  INTEGER, PARAMETER :: amsre_v_index(6) = (/1, 3, 5, 7, 9, 11/) ! AMSRE channels with V pol.
185  INTEGER, PARAMETER :: amsre_h_index(6) = (/2, 4, 6, 8, 10, 12/) ! AMSRE channels with H pol.
186  INTEGER, PARAMETER :: amsua_index(4) = (/1, 2, 3, 15/)
187  INTEGER, PARAMETER :: ssmis_index(8) = (/13,12,14,16,15,17,18,8/) ! With swapped polarisations
188  ! Local variables
189  INTEGER :: i
190  REAL(fp) :: sensor_zenith_angle
191 
192 
193  ! Set up
194  error_status = success
195  CALL crtm_geometryinfo_getvalue( geometryinfo, sensor_zenith_angle = sensor_zenith_angle )
196 
197 
198  ! Compute the surface emissivities
199  sensor_type: SELECT CASE( surface%SensorData%WMO_Sensor_ID )
200 
201  ! AMSU-A emissivity model
202  CASE( wmo_amsua )
203  DO i = 1, sfcoptics%n_Angles
204  CALL nesdis_iceem_amsu( sensor_zenith_angle, & ! Input, Degree
205  sfcoptics%Angle(i), & ! Input, Degree
206  sc(sensorindex)%Frequency(channelindex), & ! Input, GHz
207  surface%Ice_Temperature, & ! Input, K
208  surface%SensorData%Tb(amsua_index), & ! Input, AMSUA
209  not_used(1:2), & ! Input, AMSUB *** NO AMSU-B DATA ***
210  sfcoptics%Emissivity(i,2), & ! Output, H component
211  sfcoptics%Emissivity(i,1) ) ! Output, V component
212  END DO
213 
214  ! AMSU-B emissivity model
215  CASE( wmo_amsub )
216  DO i = 1, sfcoptics%n_Angles
217  CALL nesdis_iceem_amsu( sensor_zenith_angle, & ! Input, Degree
218  sfcoptics%Angle(i), & ! Input, Degree
219  sc(sensorindex)%Frequency(channelindex), & ! Input, GHz
220  surface%Ice_Temperature, & ! Input, K
221  not_used, & ! Input AMSUA *** NO AMSU-A DATA ***
222  surface%SensorData%Tb(1:2), & ! Input, AMSUB
223  sfcoptics%Emissivity(i,2), & ! Output, H component
224  sfcoptics%Emissivity(i,1) ) ! Output, V component
225  END DO
226 
227  ! MHS emissivity model
228  CASE (wmo_mhs)
229  DO i = 1, sfcoptics%n_Angles
230  CALL nesdis_iceem_mhs( sensor_zenith_angle, & ! Input, Degree
231  sfcoptics%Angle(i), & ! Input, Degree
232  sc(sensorindex)%Frequency(channelindex), & ! Input, GHz
233  surface%Ice_Temperature, & ! Input, K
234  surface%SensorData%Tb(1:2), & ! Input, MHS
235  sfcoptics%Emissivity(i,2), & ! Output, H component
236  sfcoptics%Emissivity(i,1) ) ! Output, V component
237  END DO
238 
239  ! AMSR-E emissivity model
240  CASE( wmo_amsre )
241  DO i = 1, sfcoptics%n_Angles
242  CALL nesdis_amsre_ssiceem( sc(sensorindex)%Frequency(channelindex), & ! Input, GHz
243  sfcoptics%Angle(i), & ! Input, Degree
244  surface%SensorData%Tb(amsre_v_index), & ! Input, Tb_V, K
245  surface%SensorData%Tb(amsre_h_index), & ! Input, Tb_H, K
246  surface%Ice_Temperature, & ! Input, Ts, K
247  surface%Ice_Temperature, & ! Input, Tice, K
248  sfcoptics%Emissivity(i,2), & ! Output, H component
249  sfcoptics%Emissivity(i,1) ) ! Output, V component
250  END DO
251 
252  ! SSM/I emissivity model
253  CASE( wmo_ssmi )
254  DO i = 1, sfcoptics%n_Angles
255  CALL nesdis_ssmi_siceem( sc(sensorindex)%Frequency(channelindex), & ! Input, GHz
256  sfcoptics%Angle(i), & ! Input, Degree
257  surface%Ice_Temperature, & ! Input, K
258  surface%SensorData%Tb, & ! Input, K
259  surface%Ice_Thickness, & ! Input, mm
260  sfcoptics%Emissivity(i,2), & ! Output, H component
261  sfcoptics%Emissivity(i,1) ) ! Output, V component
262  END DO
263 
264  ! SSMIS emissivity model
265  CASE( wmo_ssmis )
266  DO i = 1, sfcoptics%n_Angles
267  CALL nesdis_ssmis_iceem( sc(sensorindex)%Frequency(channelindex), & ! Input, GHz
268  sfcoptics%Angle(i), & ! Input, Degree
269  surface%Ice_Temperature, & ! Input, K
270  surface%SensorData%Tb(ssmis_index), & ! Input, K
271  surface%Ice_Thickness, & ! Input, mm
272  sfcoptics%Emissivity(i,2), & ! Output, H component
273  sfcoptics%Emissivity(i,1) ) ! Output, V component
274  END DO
275 
276  ! Default physical model
277  CASE DEFAULT
278  DO i = 1, sfcoptics%n_Angles
279 ! CALL NESDIS_SIce_Phy_EM( SC(SensorIndex)%Frequency(ChannelIndex), & ! Input, GHz
280 ! SfcOptics%Angle(i), & ! Input, Degree
281 ! Surface%Ice_Temperature, & ! Input, K
282 ! Surface_Dummy%Salinity, & ! Input
283 ! SfcOptics%Emissivity(i,2), & ! Output, H component
284 ! SfcOptics%Emissivity(i,1) ) ! Output, V component
285  sfcoptics%Emissivity(i,1:2) = default_emissivity
286  END DO
287 
288  END SELECT sensor_type
289 
290 
291  ! Compute the surface reflectivities,
292  ! assuming a specular surface
293  sfcoptics%Reflectivity = zero
294  DO i = 1, sfcoptics%n_Angles
295  sfcoptics%Reflectivity(i,1,i,1) = one-sfcoptics%Emissivity(i,1)
296  sfcoptics%Reflectivity(i,2,i,2) = one-sfcoptics%Emissivity(i,2)
297  END DO
298 
299  END FUNCTION compute_mw_ice_sfcoptics
300 
301 
302 !----------------------------------------------------------------------------------
303 !:sdoc+:
304 !
305 ! NAME:
306 ! Compute_MW_Ice_SfcOptics_TL
307 !
308 ! PURPOSE:
309 ! Function to compute the tangent-linear surface emissivity and
310 ! reflectivity at microwave frequencies over an ice surface.
311 !
312 ! This function is a wrapper for third party code.
313 !
314 ! NB: CURRENTLY THIS IS A STUB FUNCTION AS THERE ARE NO TL
315 ! COMPONENTS IN THE MW ICE SFCOPTICS COMPUTATIONS.
316 !
317 ! CALLING SEQUENCE:
318 ! Error_Status = Compute_MW_Ice_SfcOptics_TL( SfcOptics_TL )
319 !
320 ! OUTPUTS:
321 ! SfcOptics_TL: Structure containing the tangent-linear surface
322 ! optical properties required for the tangent-
323 ! linear radiative transfer calculation.
324 ! UNITS: N/A
325 ! TYPE: CRTM_SfcOptics_type
326 ! DIMENSION: Scalar
327 ! ATTRIBUTES: INTENT(IN OUT)
328 !
329 ! FUNCTION RESULT:
330 ! Error_Status: The return value is an integer defining the error status.
331 ! The error codes are defined in the Message_Handler module.
332 ! If == SUCCESS the computation was sucessful
333 ! == FAILURE an unrecoverable error occurred
334 ! UNITS: N/A
335 ! TYPE: INTEGER
336 ! DIMENSION: Scalar
337 !
338 ! COMMENTS:
339 ! Note the INTENT on the output SfcOptics_TL argument is IN OUT rather
340 ! than just OUT. This is necessary because the argument may be defined
341 ! upon input.
342 !
343 !:sdoc-:
344 !----------------------------------------------------------------------------------
345 
346  FUNCTION compute_mw_ice_sfcoptics_tl( &
347  SfcOptics_TL) & ! TL Output
348  result( err_stat )
349  ! Arguments
350  TYPE(crtm_sfcoptics_type), INTENT(IN OUT) :: sfcoptics_tl
351  ! Function result
352  INTEGER :: err_stat
353  ! Local parameters
354  CHARACTER(*), PARAMETER :: routine_name = 'Compute_MW_Ice_SfcOptics_TL'
355  ! Local variables
356 
357 
358  ! Set up
359  err_stat = success
360 
361 
362  ! Compute the tangent-linear surface optical parameters
363  ! ***No TL models yet, so default TL output is zero***
364  sfcoptics_tl%Reflectivity = zero
365  sfcoptics_tl%Emissivity = zero
366 
367  END FUNCTION compute_mw_ice_sfcoptics_tl
368 
369 
370 
371 !----------------------------------------------------------------------------------
372 !:sdoc+:
373 !
374 ! NAME:
375 ! Compute_MW_Ice_SfcOptics_AD
376 !
377 ! PURPOSE:
378 ! Function to compute the adjoint surface emissivity and
379 ! reflectivity at microwave frequencies over an ice surface.
380 !
381 ! This function is a wrapper for third party code.
382 !
383 ! NB: CURRENTLY THIS IS A STUB FUNCTION AS THERE ARE NO AD
384 ! COMPONENTS IN THE MW ICE SFCOPTICS COMPUTATIONS.
385 !
386 ! CALLING SEQUENCE:
387 ! Error_Status = Compute_MW_Ice_SfcOptics_AD( SfcOptics_AD )
388 !
389 ! INPUTS:
390 ! SfcOptics_AD: Structure containing the adjoint surface optical
391 ! properties required for the adjoint radiative
392 ! transfer calculation.
393 ! *** COMPONENTS MODIFIED UPON OUTPUT ***
394 ! UNITS: N/A
395 ! TYPE: CRTM_SfcOptics_type
396 ! DIMENSION: Scalar
397 ! ATTRIBUTES: INTENT(IN OUT)
398 !
399 ! FUNCTION RESULT:
400 ! Error_Status: The return value is an integer defining the error status.
401 ! The error codes are defined in the Message_Handler module.
402 ! If == SUCCESS the computation was sucessful
403 ! == FAILURE an unrecoverable error occurred
404 ! UNITS: N/A
405 ! TYPE: INTEGER
406 ! DIMENSION: Scalar
407 !
408 ! COMMENTS:
409 ! Note the INTENT on the input adjoint arguments are IN OUT regardless
410 ! of their specification as "input" or "output". This is because these
411 ! arguments may contain information on input, or need to be zeroed on
412 ! output (or both).
413 !
414 !:sdoc-:
415 !----------------------------------------------------------------------------------
416 
417  FUNCTION compute_mw_ice_sfcoptics_ad( &
418  SfcOptics_AD) & ! AD Input
419  result( err_stat )
420  ! Arguments
421  TYPE(crtm_sfcoptics_type), INTENT(IN OUT) :: sfcoptics_ad
422  ! Function result
423  INTEGER :: err_stat
424  ! Local parameters
425  CHARACTER(*), PARAMETER :: routine_name = 'Compute_MW_Ice_SfcOptics_AD'
426  ! Local variables
427 
428 
429  ! Set up
430  err_stat = success
431 
432 
433  ! Compute the adjoint surface optical parameters
434  ! ***No AD models yet, so there is no impact on AD result***
435  sfcoptics_ad%Reflectivity = zero
436  sfcoptics_ad%Emissivity = zero
437 
438  END FUNCTION compute_mw_ice_sfcoptics_ad
439 
440 END MODULE crtm_mw_ice_sfcoptics
integer, parameter, public wmo_ssmi
subroutine, public nesdis_ssmi_siceem(frequency, Angle, Ts, tb, Depth, Emissivity_H, Emissivity_V)
integer, parameter, public wmo_mhs
subroutine, public nesdis_sice_phy_em(Frequency, Angle, Ts_ice, Salinity, Emissivity_H, Emissivity_V)
integer, parameter, public wmo_amsre
real(fp), parameter, public zero
subroutine, public nesdis_ssmis_iceem(frequency, Angle, Ts, tb, Depth, Emissivity_H, Emissivity_V)
integer, parameter, public fp
Definition: Type_Kinds.f90:124
character(*), parameter module_version_id
integer, parameter, public wmo_ssmis
integer, parameter, public wmo_msu
real(fp), parameter, public one
integer, parameter, public wmo_amsua
integer function, public compute_mw_ice_sfcoptics_ad(SfcOptics_AD)
subroutine, public nesdis_iceem_amsu(Satellite_Angle, User_Angle, frequency, Ts, tba, tbb, Emissivity_H, Emissivity_V)
type(spccoeff_type), dimension(:), allocatable, save, public sc
integer, parameter, public wmo_amsub
integer function, public compute_mw_ice_sfcoptics(Surface, GeometryInfo, SensorIndex, ChannelIndex, SfcOptics)
integer function, public compute_mw_ice_sfcoptics_tl(SfcOptics_TL)
subroutine, public nesdis_amsre_ssiceem(frequency, User_Angle, tv, th, Ts, Tice, Emissivity_H, Emissivity_V)
integer, parameter, public success
elemental subroutine, public crtm_geometryinfo_getvalue(gInfo, Geometry, iFOV, Longitude, Latitude, Surface_Altitude, Sensor_Scan_Angle, Sensor_Zenith_Angle, Sensor_Azimuth_Angle, Source_Zenith_Angle, Source_Azimuth_Angle, Flux_Zenith_Angle, Year, Month, Day, Distance_Ratio, Sensor_Scan_Radian, Sensor_Zenith_Radian, Sensor_Azimuth_Radian, Secant_Sensor_Zenith, Cosine_Sensor_Zenith, Source_Zenith_Radian, Source_Azimuth_Radian, Secant_Source_Zenith, Flux_Zenith_Radian, Secant_Flux_Zenith, Trans_Zenith_Radian, Secant_Trans_Zenith, AU_ratio2)
subroutine, public nesdis_iceem_mhs(Satellite_Angle, User_Angle, frequency, Ts, tbb, Emissivity_H, Emissivity_V)