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