FV3 Bundle
CRTM_IR_Land_SfcOptics.f90
Go to the documentation of this file.
1 !
2 ! CRTM_IR_Land_SfcOptics
3 !
4 ! Module to compute the surface optical properties for LAND surfaces at
5 ! infrared frequencies required for determining the LAND 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 
19 
20  ! -----------------
21  ! Environment setup
22  ! -----------------
23  ! Module use
24  USE type_kinds , ONLY: fp
26  USE crtm_parameters , ONLY: zero, one, max_n_angles
27  USE crtm_spccoeff , ONLY: sc, spccoeff_issolar
31  USE crtm_secategory , ONLY: sevar_type => ivar_type, &
33  USE crtm_irlandcoeff , ONLY: irlandc
34  ! Disable implicit typing
35  IMPLICIT NONE
36 
37 
38  ! ------------
39  ! Visibilities
40  ! ------------
41  ! Everything private by default
42  PRIVATE
43  ! Data types
44  PUBLIC :: ivar_type
45  ! Science routines
49 
50 
51  ! -----------------
52  ! Module parameters
53  ! -----------------
54  CHARACTER(*), PARAMETER :: module_version_id = &
55  '$Id: CRTM_IR_Land_SfcOptics.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
56  ! Message string length
57  INTEGER, PARAMETER :: ml = 256
58 
59 
60  ! --------------------------------------
61  ! Structure definition to hold forward
62  ! variables across FWD, TL, and AD calls
63  ! --------------------------------------
64  TYPE :: ivar_type
65  PRIVATE
66  TYPE(sevar_type) :: sevar
67  END TYPE ivar_type
68 
69 
70 CONTAINS
71 
72 
73 !----------------------------------------------------------------------------------
74 !:sdoc+:
75 !
76 ! NAME:
77 ! Compute_IR_Land_SfcOptics
78 !
79 ! PURPOSE:
80 ! Function to compute the surface emissivity and reflectivity at infrared
81 ! frequencies over a land surface.
82 !
83 ! This function is a wrapper for third party code.
84 !
85 ! CALLING SEQUENCE:
86 ! Error_Status = Compute_IR_Land_SfcOptics( &
87 ! Surface , &
88 ! SensorIndex , &
89 ! ChannelIndex, &
90 ! SfcOptics , &
91 ! iVar )
92 !
93 ! INPUTS:
94 ! Surface: Structure containing the surface state data.
95 ! UNITS: N/A
96 ! TYPE: CRTM_Surface_type
97 ! DIMENSION: Scalar
98 ! ATTRIBUTES: INTENT(IN)
99 !
100 ! SensorIndex: Sensor index id. This is a unique index associated
101 ! with a (supported) sensor used to access the
102 ! shared coefficient data for a particular sensor.
103 ! See the ChannelIndex argument.
104 ! UNITS: N/A
105 ! TYPE: INTEGER
106 ! DIMENSION: Scalar
107 ! ATTRIBUTES: INTENT(IN)
108 !
109 ! ChannelIndex: Channel index id. This is a unique index associated
110 ! with a (supported) sensor channel used to access the
111 ! shared coefficient data for a particular sensor's
112 ! channel.
113 ! See the SensorIndex argument.
114 ! UNITS: N/A
115 ! TYPE: INTEGER
116 ! DIMENSION: Scalar
117 ! ATTRIBUTES: INTENT(IN)
118 !
119 ! OUTPUTS:
120 ! SfcOptics: CRTM_SfcOptics structure containing the surface
121 ! optical properties required for the radiative
122 ! transfer calculation. On input the Angle component
123 ! is assumed to contain data.
124 ! UNITS: N/A
125 ! TYPE: CRTM_SfcOptics_type
126 ! DIMENSION: Scalar
127 ! ATTRIBUTES: INTENT(IN OUT)
128 !
129 ! iVar: Structure containing internal variables required for
130 ! subsequent tangent-linear or adjoint model calls.
131 ! The contents of this structure are NOT accessible
132 ! outside of the module containing this procedure.
133 ! UNITS: N/A
134 ! TYPE: iVar_type
135 ! DIMENSION: Scalar
136 ! ATTRIBUTES: INTENT(OUT)
137 !
138 ! FUNCTION RESULT:
139 ! Error_Status: The return value is an integer defining the error status.
140 ! The error codes are defined in the Message_Handler module.
141 ! If == SUCCESS the computation was sucessful
142 ! == FAILURE an unrecoverable error occurred
143 ! UNITS: N/A
144 ! TYPE: INTEGER
145 ! DIMENSION: Scalar
146 !
147 ! COMMENTS:
148 ! Note the INTENT on the output SfcOptics argument is IN OUT rather
149 ! than just OUT as it is assumed to contain some data upon input.
150 !
151 !:sdoc-:
152 !----------------------------------------------------------------------------------
153 
154  FUNCTION compute_ir_land_sfcoptics( &
155  Surface , & ! Input
156  SensorIndex , & ! Input
157  ChannelIndex, & ! Input
158  SfcOptics , & ! Output
159  iVar ) & ! Internal variable output
160  result( err_stat )
161  ! Arguments
162  TYPE(crtm_surface_type), INTENT(IN) :: surface
163  INTEGER, INTENT(IN) :: sensorindex
164  INTEGER, INTENT(IN) :: channelindex
165  TYPE(crtm_sfcoptics_type), INTENT(IN OUT) :: sfcoptics
166  TYPE(ivar_type), INTENT(IN OUT) :: ivar
167  ! Function result
168  INTEGER :: err_stat
169  ! Local parameters
170  CHARACTER(*), PARAMETER :: routine_name = 'Compute_IR_Land_SfcOptics'
171  ! Local variables
172  CHARACTER(ML) :: msg
173  INTEGER :: j
174  REAL(fp) :: frequency, emissivity
175 
176  ! Set up
177  err_stat = success
178  frequency = sc(sensorindex)%Wavenumber(channelindex)
179 
180 
181  ! Compute Lambertian surface emissivity
182  err_stat = secategory_emissivity( &
183  irlandc , & ! Input
184  frequency , & ! Input
185  surface%Land_Type, & ! Input
186  emissivity , & ! Output
187  ivar%sevar ) ! Internal variable output
188  IF ( err_stat /= success ) THEN
189  msg = 'Error occurred in SEcategory_Emissivity()'
190  CALL display_message( routine_name, msg, err_stat ); RETURN
191  END IF
192 
193 
194  ! Solar direct component
195  IF ( spccoeff_issolar(sc(sensorindex), channelindex=channelindex) ) THEN
196  sfcoptics%Direct_Reflectivity(:,1) = one - emissivity
197  END IF
198 
199 
200  ! Fill the return emissivity and reflectivity arrays
201  sfcoptics%Emissivity(1:sfcoptics%n_Angles,1) = emissivity
202  DO j = 1, sfcoptics%n_Angles
203  sfcoptics%Reflectivity(j,1,j,1) = one - sfcoptics%Emissivity(j,1)
204  END DO
205 
206  END FUNCTION compute_ir_land_sfcoptics
207 
208 
209 !----------------------------------------------------------------------------------
210 !:sdoc+:
211 !
212 ! NAME:
213 ! Compute_IR_Land_SfcOptics_TL
214 !
215 ! PURPOSE:
216 ! Function to compute the tangent-linear surface emissivity and
217 ! reflectivity at infrared frequencies over a land surface.
218 !
219 ! This function is a wrapper for third party code.
220 !
221 ! NB: CURRENTLY THIS IS A STUB FUNCTION AS THERE ARE NO TL
222 ! COMPONENTS IN THE IR LAND SFCOPTICS COMPUTATIONS.
223 !
224 ! CALLING SEQUENCE:
225 ! Error_Status = Compute_IR_Land_SfcOptics_TL( SfcOptics_TL )
226 !
227 ! OUTPUTS:
228 ! SfcOptics_TL: Structure containing the tangent-linear surface
229 ! optical properties required for the tangent-
230 ! linear radiative transfer calculation.
231 ! UNITS: N/A
232 ! TYPE: CRTM_SfcOptics_type
233 ! DIMENSION: Scalar
234 ! ATTRIBUTES: INTENT(IN OUT)
235 !
236 ! FUNCTION RESULT:
237 ! Error_Status: The return value is an integer defining the error status.
238 ! The error codes are defined in the Message_Handler module.
239 ! If == SUCCESS the computation was sucessful
240 ! == FAILURE an unrecoverable error occurred
241 ! UNITS: N/A
242 ! TYPE: INTEGER
243 ! DIMENSION: Scalar
244 !
245 ! COMMENTS:
246 ! Note the INTENT on the input SfcOptics_TL argument is IN OUT rather
247 ! than just OUT as it may be defined upon input.
248 !
249 !:sdoc-:
250 !----------------------------------------------------------------------------------
251 
252  FUNCTION compute_ir_land_sfcoptics_tl( &
253  SfcOptics_TL ) & ! Output
254  result( err_stat )
255  ! Arguments
256  TYPE(crtm_sfcoptics_type), INTENT(IN OUT) :: sfcoptics_tl
257  ! Function result
258  INTEGER :: err_stat
259  ! Local parameters
260  CHARACTER(*), PARAMETER :: routine_name = 'Compute_IR_Land_SfcOptics_TL'
261  ! Local variables
262 
263 
264  ! Set up
265  err_stat = success
266 
267 
268  ! Compute the tangent-linear surface optical parameters
269  ! ***No TL models yet, so default TL output is zero***
270  sfcoptics_tl%Reflectivity = zero
271  sfcoptics_tl%Direct_Reflectivity = zero
272  sfcoptics_tl%Emissivity = zero
273 
274  END FUNCTION compute_ir_land_sfcoptics_tl
275 
276 
277 !----------------------------------------------------------------------------------
278 !:sdoc+:
279 !
280 ! NAME:
281 ! Compute_IR_Land_SfcOptics_AD
282 !
283 ! PURPOSE:
284 ! Function to compute the adjoint surface emissivity and
285 ! reflectivity at infrared frequencies over a land surface.
286 !
287 ! This function is a wrapper for third party code.
288 !
289 ! NB: CURRENTLY THIS IS A STUB FUNCTION AS THERE ARE NO AD
290 ! COMPONENTS IN THE IR LAND SFCOPTICS COMPUTATIONS.
291 !
292 ! CALLING SEQUENCE:
293 ! Error_Status = Compute_IR_Land_SfcOptics_AD( SfcOptics_AD )
294 !
295 ! INPUTS:
296 ! SfcOptics_AD: Structure containing the adjoint surface optical
297 ! properties required for the adjoint radiative
298 ! transfer calculation.
299 ! *** COMPONENTS MODIFIED UPON OUTPUT ***
300 ! UNITS: N/A
301 ! TYPE: CRTM_SfcOptics_type
302 ! DIMENSION: Scalar
303 ! ATTRIBUTES: INTENT(IN OUT)
304 !
305 ! FUNCTION RESULT:
306 ! Error_Status: The return value is an integer defining the error status.
307 ! The error codes are defined in the Message_Handler module.
308 ! If == SUCCESS the computation was sucessful
309 ! == FAILURE an unrecoverable error occurred
310 ! UNITS: N/A
311 ! TYPE: INTEGER
312 ! DIMENSION: Scalar
313 !
314 ! COMMENTS:
315 ! Note the INTENT on the input adjoint arguments are IN OUT regardless
316 ! of their specification as "input" or "output". This is because these
317 ! arguments may contain information on input, or need to be zeroed on
318 ! output (or both).
319 !
320 !:sdoc-:
321 !----------------------------------------------------------------------------------
322 
323  FUNCTION compute_ir_land_sfcoptics_ad( &
324  SfcOptics_AD ) & ! Input
325  result( err_stat )
326  ! Arguments
327  TYPE(crtm_sfcoptics_type), INTENT(IN OUT) :: sfcoptics_ad
328  ! Function result
329  INTEGER :: err_stat
330  ! Local parameters
331  CHARACTER(*), PARAMETER :: routine_name = 'Compute_IR_Land_SfcOptics_AD'
332  ! Local variables
333 
334 
335  ! Set up
336  err_stat = success
337 
338 
339  ! Compute the adjoint surface optical parameters
340  ! ***No AD models yet, so there is no impact on AD result***
341  sfcoptics_ad%Reflectivity = zero
342  sfcoptics_ad%Direct_Reflectivity = zero
343  sfcoptics_ad%Emissivity = zero
344 
345  END FUNCTION compute_ir_land_sfcoptics_ad
346 
347 END MODULE crtm_ir_land_sfcoptics
character(*), parameter module_version_id
integer function, public compute_ir_land_sfcoptics(Surface, SensorIndex, ChannelIndex, SfcOptics, iVar)
real(fp), parameter, public zero
integer, parameter, public fp
Definition: Type_Kinds.f90:124
integer function, public compute_ir_land_sfcoptics_tl(SfcOptics_TL)
integer, parameter, public max_n_angles
type(secategory_type), save, public irlandc
integer function, public compute_ir_land_sfcoptics_ad(SfcOptics_AD)
real(fp), parameter, public one
recursive subroutine, public display_message(Routine_Name, Message, Error_State, Message_Log)
integer function, public secategory_emissivity(SEcategory, Frequency, Surface_Type, Emissivity, iVar)
type(spccoeff_type), dimension(:), allocatable, save, public sc
integer, parameter, public success