FV3 Bundle
CRTM_Adjoint_Module.f90
Go to the documentation of this file.
1 !
2 ! CRTM_Adjoint_Module
3 !
4 ! Module containing the CRTM adjoint model function.
5 !
6 !
7 ! CREATION HISTORY:
8 ! Written by: Paul van Delst, 28-Jan-2005
9 ! paul.vandelst@noaa.gov
10 !
11 
13 
14 
15  ! ------------
16  ! Module usage
17  ! ------------
18  USE type_kinds, ONLY: fp
20  USE crtm_parameters, ONLY: set, not_set, zero, one, &
21  max_n_layers , &
24  max_n_stokes , &
25  max_n_angles , &
28  max_n_streams , &
30  USE crtm_spccoeff, ONLY: sc, &
31  spccoeff_isinfraredsensor , &
32  spccoeff_ismicrowavesensor, &
33  spccoeff_isvisiblesensor
57  USE crtm_predictor, ONLY: crtm_pvar_type => ivar_type, &
60  USE crtm_atmabsorption, ONLY: crtm_aavar_type => ivar_type , &
72  USE crtm_atmoptics, ONLY: aovar_type , &
73  aovar_create, &
86  USE crtm_rtsolution, ONLY: crtm_rtsolution_type , &
97  USE crtm_nltecorrection, ONLY: nlte_predictor_type , &
98  nlte_predictor_isactive , &
107 
108  ! Internal variable definition modules
109  ! ...CloudScatter
110  USE csvar_define, ONLY: csvar_type, &
112  csvar_destroy , &
114  ! ...AerosolScatter
115  USE asvar_define, ONLY: asvar_type, &
117  asvar_destroy , &
119  ! ...Radiative transfer
120  USE rtv_define, ONLY: rtv_type , &
121  rtv_associated, &
122  rtv_destroy , &
123  rtv_create
124 
125  ! -----------------------
126  ! Disable implicit typing
127  ! -----------------------
128  IMPLICIT NONE
129 
130 
131  ! ------------
132  ! Visibilities
133  ! ------------
134  ! Everything private by default
135  PRIVATE
136  ! Public procedures
137  PUBLIC :: crtm_adjoint
138  PUBLIC :: crtm_adjoint_version
139 
140 
141  ! -----------------
142  ! Module parameters
143  ! -----------------
144  ! Version Id for the module
145  CHARACTER(*), PARAMETER :: module_version_id = &
146  '$Id: CRTM_Adjoint_Module.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
147 
148 
149 CONTAINS
150 
151 
152 !--------------------------------------------------------------------------------
153 !:sdoc+:
154 !
155 ! NAME:
156 ! CRTM_Adjoint
157 !
158 ! PURPOSE:
159 ! Function that calculates the adjoint of top-of-atmosphere (TOA)
160 ! radiances and brightness temperatures for an input atmospheric
161 ! profile or profile set and user specified satellites/channels.
162 !
163 ! CALLING SEQUENCE:
164 ! Error_Status = CRTM_Adjoint( Atmosphere , &
165 ! Surface , &
166 ! RTSolution_AD , &
167 ! Geometry , &
168 ! ChannelInfo , &
169 ! Atmosphere_AD , &
170 ! Surface_AD , &
171 ! RTSolution , &
172 ! Options = Options )
173 !
174 ! INPUTS:
175 ! Atmosphere: Structure containing the Atmosphere data.
176 ! UNITS: N/A
177 ! TYPE: CRTM_Atmosphere_type
178 ! DIMENSION: Rank-1 (n_Profiles)
179 ! ATTRIBUTES: INTENT(IN)
180 !
181 ! Surface: Structure containing the Surface data.
182 ! UNITS: N/A
183 ! TYPE: CRTM_Surface_type
184 ! DIMENSION: Same as input Atmosphere structure
185 ! ATTRIBUTES: INTENT(IN)
186 !
187 ! RTSolution_AD: Structure containing the RT solution adjoint inputs.
188 ! **NOTE: On EXIT from this function, the contents of
189 ! this structure may be modified (e.g. set to
190 ! zero.)
191 ! UNITS: N/A
192 ! TYPE: CRTM_RTSolution_type
193 ! DIMENSION: Rank-2 (n_Channels x n_Profiles)
194 ! ATTRIBUTES: INTENT(IN OUT)
195 !
196 ! Geometry: Structure containing the view geometry
197 ! information.
198 ! UNITS: N/A
199 ! TYPE: CRTM_Geometry_type
200 ! DIMENSION: Same as input Atmosphere argument
201 ! ATTRIBUTES: INTENT(IN)
202 !
203 ! ChannelInfo: Structure returned from the CRTM_Init() function
204 ! that contains the satellite/sensor channel index
205 ! information.
206 ! UNITS: N/A
207 ! TYPE: CRTM_ChannelInfo_type
208 ! DIMENSION: Rank-1 (n_Sensors)
209 ! ATTRIBUTES: INTENT(IN)
210 !
211 ! OPTIONAL INPUTS:
212 ! Options: Options structure containing the optional forward model
213 ! arguments for the CRTM.
214 ! UNITS: N/A
215 ! TYPE: CRTM_Options_type
216 ! DIMENSION: Same as input Atmosphere structure
217 ! ATTRIBUTES: INTENT(IN), OPTIONAL
218 !
219 ! OUTPUTS:
220 ! Atmosphere_AD: Structure containing the adjoint Atmosphere data.
221 ! **NOTE: On ENTRY to this function, the contents of
222 ! this structure should be defined (e.g.
223 ! initialized to some value based on the
224 ! position of this function in the call chain.)
225 ! UNITS: N/A
226 ! TYPE: CRTM_Atmosphere_type
227 ! DIMENSION: Same as input Atmosphere argument
228 ! ATTRIBUTES: INTENT(IN OUT)
229 !
230 ! Surface_AD: Structure containing the tangent-linear Surface data.
231 ! **NOTE: On ENTRY to this function, the contents of
232 ! this structure should be defined (e.g.
233 ! initialized to some value based on the
234 ! position of this function in the call chain.)
235 ! UNITS: N/A
236 ! TYPE: CRTM_Surface_type
237 ! DIMENSION: Same as input Atmosphere argument
238 ! ATTRIBUTES: INTENT(IN OUT)
239 !
240 ! RTSolution: Structure containing the solution to the RT equation
241 ! for the given inputs.
242 ! UNITS: N/A
243 ! TYPE: CRTM_RTSolution_type
244 ! DIMENSION: Same as input RTSolution_AD argument
245 ! ATTRIBUTES: INTENT(IN OUT)
246 !
247 ! FUNCTION RESULT:
248 ! Error_Status: The return value is an integer defining the error status.
249 ! The error codes are defined in the Message_Handler module.
250 ! If == SUCCESS the computation was sucessful
251 ! == FAILURE an unrecoverable error occurred
252 ! UNITS: N/A
253 ! TYPE: INTEGER
254 ! DIMENSION: Scalar
255 !
256 ! SIDE EFFECTS:
257 ! Note that the input adjoint arguments are modified upon exit, and
258 ! the output adjoint arguments must be defined upon entry. This is
259 ! a consequence of the adjoint formulation where, effectively, the
260 ! chain rule is being used and this function could reside anywhere
261 ! in the chain of derivative terms.
262 !
263 ! COMMENTS:
264 ! - The Options optional structure arguments contain
265 ! spectral information (e.g. emissivity) that must have the same
266 ! spectral dimensionality (the "L" dimension) as the RTSolution
267 ! structures.
268 !
269 !:sdoc-:
270 !--------------------------------------------------------------------------------
271 
272  FUNCTION crtm_adjoint( &
273  Atmosphere , & ! FWD Input, M
274  Surface , & ! FWD Input, M
275  RTSolution_AD, & ! AD Input, L x M
276  Geometry , & ! Input, M
277  ChannelInfo , & ! Input, Scalar
278  Atmosphere_AD, & ! AD Output, M
279  Surface_AD , & ! AD Output, M
280  RTSolution , & ! FWD Output, L x M
281  Options ) & ! Optional FWD input, M
282  result( error_status )
283  ! Arguments
284  TYPE(crtm_atmosphere_type) , INTENT(IN) :: atmosphere(:) ! M
285  TYPE(crtm_surface_type) , INTENT(IN) :: surface(:) ! M
286  TYPE(crtm_rtsolution_type) , INTENT(IN OUT) :: rtsolution_ad(:,:) ! L x M
287  TYPE(crtm_geometry_type) , INTENT(IN) :: geometry(:) ! M
288  TYPE(crtm_channelinfo_type) , INTENT(IN) :: channelinfo(:) ! n_Sensors
289  TYPE(crtm_atmosphere_type) , INTENT(IN OUT) :: atmosphere_ad(:) ! M
290  TYPE(crtm_surface_type) , INTENT(IN OUT) :: surface_ad(:) ! M
291  TYPE(crtm_rtsolution_type) , INTENT(IN OUT) :: rtsolution(:,:) ! L x M
292  TYPE(crtm_options_type), OPTIONAL, INTENT(IN) :: options(:) ! M
293  ! Function result
294  INTEGER :: error_status
295  ! Local parameters
296  CHARACTER(*), PARAMETER :: routine_name = 'CRTM_Adjoint'
297  ! Local variables
298  CHARACTER(256) :: message
299  LOGICAL :: options_present
300  LOGICAL :: check_input
301  LOGICAL :: user_emissivity, user_direct_reflectivity, user_n_streams
302  LOGICAL :: user_antcorr, compute_antcorr
303  LOGICAL :: apply_nlte_correction
304  LOGICAL :: atmosphere_invalid, surface_invalid, geometry_invalid, options_invalid
305  INTEGER :: rt_algorithm_id
306  INTEGER :: ifov
307  INTEGER :: nc, na
308  INTEGER :: n, n_sensors, sensorindex
309  INTEGER :: l, n_channels, channelindex
310  INTEGER :: m, n_profiles
311  INTEGER :: j, ln
312  INTEGER :: n_full_streams, mth_azi
313  REAL(fp) :: source_za
314  REAL(fp) :: wavenumber
315  REAL(fp) :: transmittance, transmittance_ad
316  ! Local ancillary input structure
317  TYPE(crtm_ancillaryinput_type) :: ancillaryinput
318  ! Local options structure for default values
319  TYPE(crtm_options_type) :: default_options
320  ! Local atmosphere structure for extra layering
321  TYPE(crtm_atmosphere_type) :: atm, atm_ad
322  ! Component variables
323  TYPE(crtm_geometryinfo_type) :: geometryinfo
324  TYPE(crtm_predictor_type) :: predictor, predictor_ad
325  TYPE(crtm_atmoptics_type) :: atmoptics, atmoptics_ad
326  TYPE(crtm_sfcoptics_type) :: sfcoptics, sfcoptics_ad
327  ! Component variable internals
328  TYPE(crtm_pvar_type) :: pvar ! Predictor
329  TYPE(crtm_aavar_type) :: aavar ! AtmAbsorption
330  TYPE(csvar_type) :: csvar ! CloudScatter
331  TYPE(asvar_type) :: asvar ! AerosolScatter
332  TYPE(aovar_type) :: aovar ! AtmOptics
333  TYPE(rtv_type) :: rtv ! RTSolution
334  ! NLTE correction term predictors
335  TYPE(nlte_predictor_type) :: nlte_predictor, nlte_predictor_ad
336 
337 
338  ! ------
339  ! SET UP
340  ! ------
341  error_status = success
342 
343 
344  ! If no sensors or channels, simply return
345  n_sensors = SIZE(channelinfo)
346  n_channels = sum(crtm_channelinfo_n_channels(channelinfo))
347  IF ( n_sensors == 0 .OR. n_channels == 0 ) RETURN
348 
349 
350  ! Check spectral arrays
351  IF ( SIZE(rtsolution ,dim=1) < n_channels .OR. &
352  SIZE(rtsolution_ad,dim=1) < n_channels ) THEN
353  error_status = failure
354  WRITE( message,'("Output RTSolution structure arrays too small (",i0," and ",i0,&
355  &") to hold results for the number of requested channels (",i0,")")') &
356  SIZE(rtsolution,dim=1), SIZE(rtsolution_ad,dim=1), n_channels
357  CALL display_message( routine_name, message, error_status )
358  RETURN
359  END IF
360 
361 
362  ! Check the number of profiles
363  ! ...Number of atmospheric profiles.
364  n_profiles = SIZE(atmosphere)
365  ! ...Check the profile dimensionality of the other mandatory arguments
366  IF ( SIZE(surface) /= n_profiles .OR. &
367  SIZE(rtsolution_ad,dim=2) /= n_profiles .OR. &
368  SIZE(geometry) /= n_profiles .OR. &
369  SIZE(atmosphere_ad) /= n_profiles .OR. &
370  SIZE(surface_ad) /= n_profiles .OR. &
371  SIZE(rtsolution, dim=2) /= n_profiles ) THEN
372  error_status = failure
373  message = 'Inconsistent profile dimensionality for input arguments.'
374  CALL display_message( routine_name, message, error_status )
375  RETURN
376  END IF
377  ! ...Check the profile dimensionality of the other optional arguments
378  options_present = .false.
379  IF ( PRESENT(options) ) THEN
380  options_present = .true.
381  IF ( SIZE(options) /= n_profiles ) THEN
382  error_status = failure
383  message = 'Inconsistent profile dimensionality for Options optional input argument.'
384  CALL display_message( routine_name, message, error_status )
385  RETURN
386  END IF
387  END IF
388 
389 
390  ! Allocate the profile independent surface optics local structure
391  CALL crtm_sfcoptics_create( sfcoptics , max_n_angles, max_n_stokes )
392  CALL crtm_sfcoptics_create( sfcoptics_ad, max_n_angles, max_n_stokes )
393  IF ( (.NOT. crtm_sfcoptics_associated(sfcoptics )) .OR. &
394  (.NOT. crtm_sfcoptics_associated(sfcoptics_ad)) ) THEN
395  error_status = failure
396  message = 'Error allocating SfcOptics data structures'
397  CALL display_message( routine_name, message, error_status )
398  RETURN
399  END IF
400 
401 
402  ! ------------
403  ! PROFILE LOOP
404  ! ------------
405  profile_loop: DO m = 1, n_profiles
406 
407 
408  ! Check the cloud and aerosol coeff. data for cases with clouds and aerosol
409  IF( atmosphere(m)%n_Clouds > 0 .AND. .NOT. crtm_cloudcoeff_isloaded() )THEN
410  error_status = failure
411  WRITE( message,'("The CloudCoeff data must be loaded (with CRTM_Init routine) ", &
412  &"for the cloudy case profile #",i0)' ) m
413  CALL display_message( routine_name, message, error_status )
414  RETURN
415  END IF
416  IF( atmosphere(m)%n_Aerosols > 0 .AND. .NOT. crtm_aerosolcoeff_isloaded() )THEN
417  error_status = failure
418  WRITE( message,'("The AerosolCoeff data must be loaded (with CRTM_Init routine) ", &
419  &"for the aerosol case profile #",i0)' ) m
420  CALL display_message( routine_name, message, error_status )
421  RETURN
422  END IF
423 
424 
425  ! Copy over forward "non-variable" inputs to adjoint outputs
426  ! ...Atmosphere
427  atmosphere_ad(m)%Climatology = atmosphere(m)%Climatology
428  DO j = 1, atmosphere(m)%n_Absorbers
429  atmosphere_ad(m)%Absorber_ID(j) = atmosphere(m)%Absorber_ID(j)
430  atmosphere_ad(m)%Absorber_Units(j) = atmosphere(m)%Absorber_Units(j)
431  END DO
432  ! Loop over and assign cloud types
433  DO nc = 1, atmosphere(m)%n_Clouds
434  atmosphere_ad(m)%Cloud(nc)%Type = atmosphere(m)%Cloud(nc)%Type
435  END DO
436  ! Loop over and assign aerosol types
437  DO na = 1, atmosphere(m)%n_Aerosols
438  atmosphere_ad(m)%Aerosol(na)%Type = atmosphere(m)%Aerosol(na)%Type
439  END DO
440  ! ...Surface
441  surface_ad(m)%Land_Coverage = surface(m)%Land_Coverage
442  surface_ad(m)%Water_Coverage = surface(m)%Water_Coverage
443  surface_ad(m)%Snow_Coverage = surface(m)%Snow_Coverage
444  surface_ad(m)%Ice_Coverage = surface(m)%Ice_Coverage
445  surface_ad(m)%Land_Type = surface(m)%Land_Type
446  surface_ad(m)%Water_Type = surface(m)%Water_Type
447  surface_ad(m)%Snow_Type = surface(m)%Snow_Type
448  surface_ad(m)%Ice_Type = surface(m)%Ice_Type
449 
450 
451 
452  ! Check the optional Options structure argument
453  ! ...Specify default actions
454  check_input = default_options%Check_Input
455  user_emissivity = default_options%Use_Emissivity
456  user_antcorr = default_options%Use_Antenna_Correction
457  apply_nlte_correction = default_options%Apply_NLTE_Correction
458  rt_algorithm_id = default_options%RT_Algorithm_Id
459  user_n_streams = default_options%Use_N_Streams
460  ! ...Check the Options argument
461  IF (options_present) THEN
462  ! Override input checker with option
463  check_input = options(m)%Check_Input
464  ! Check if the supplied emissivity should be used
465  user_emissivity = options(m)%Use_Emissivity
466  IF ( options(m)%Use_Emissivity ) THEN
467  ! Are the channel dimensions consistent
468  IF ( options(m)%n_Channels < n_channels ) THEN
469  error_status = failure
470  WRITE( message,'( "Input Options channel dimension (", i0, ") is less ", &
471  &"than the number of requested channels (",i0, ")" )' ) &
472  options(m)%n_Channels, n_channels
473  CALL display_message( routine_name, message, error_status )
474  RETURN
475  END IF
476  ! Check if the supplied direct reflectivity should be used
477  user_direct_reflectivity = options(m)%Use_Direct_Reflectivity
478  END IF
479  ! Check if antenna correction should be attempted
480  user_antcorr = options(m)%Use_Antenna_Correction
481  ! Set NLTE correction option
482  apply_nlte_correction = options(m)%Apply_NLTE_Correction
483 
484 
485  ! Copy over ancillary input
486  ancillaryinput%SSU = options(m)%SSU
487  ancillaryinput%Zeeman = options(m)%Zeeman
488  ! Copy over surface optics input
489  sfcoptics%Use_New_MWSSEM = .NOT. options(m)%Use_Old_MWSSEM
490  ! Specify the RT algorithm
491  rt_algorithm_id = options(m)%RT_Algorithm_Id
492  ! Check if n_Streams should be used
493  user_n_streams = options(m)%Use_N_Streams
494  ! Check value for nstreams
495  IF ( user_n_streams ) THEN
496  IF ( options(m)%n_Streams <= 0 .OR. mod(options(m)%n_Streams,2) /= 0 .OR. &
497  options(m)%n_Streams > max_n_streams ) THEN
498  error_status = failure
499  WRITE( message,'( "Input Options n_Streams (", i0, ") is invalid" )' ) &
500  options(m)%n_Streams
501  CALL display_message( routine_name, message, error_status )
502  RETURN
503  END IF
504  END IF
505  END IF
506 
507 
508  ! Check the input data if required
509  IF ( check_input ) THEN
510  ! ...Mandatory inputs
511  atmosphere_invalid = .NOT. crtm_atmosphere_isvalid( atmosphere(m) )
512  surface_invalid = .NOT. crtm_surface_isvalid( surface(m) )
513  geometry_invalid = .NOT. crtm_geometry_isvalid( geometry(m) )
514  IF ( atmosphere_invalid .OR. surface_invalid .OR. geometry_invalid ) THEN
515  error_status = failure
516  WRITE( message,'("Input data check failed for profile #",i0)' ) m
517  CALL display_message( routine_name, message, error_status )
518  RETURN
519  END IF
520  ! ...Optional input
521  IF ( options_present ) THEN
522  options_invalid = .NOT. crtm_options_isvalid( options(m) )
523  IF ( options_invalid ) THEN
524  error_status = failure
525  WRITE( message,'("Options data check failed for profile #",i0)' ) m
526  CALL display_message( routine_name, message, error_status )
527  RETURN
528  END IF
529  END IF
530  END IF
531 
532 
533  ! Process geometry
534  ! ...Compute derived geometry
535  CALL crtm_geometryinfo_setvalue( geometryinfo, geometry=geometry(m) )
536  CALL crtm_geometryinfo_compute( geometryinfo )
537  ! ...Retrieve components into local variable
539  geometryinfo, &
540  ifov = ifov, &
541  source_zenith_angle = source_za )
542 
543 
544  ! Average surface skin temperature for multi-surface types
545  CALL crtm_compute_surfacet( surface(m), sfcoptics )
546 
547 
548  ! Add extra layers to current atmosphere profile
549  ! if necessary to handle upper atmosphere
550  error_status = crtm_atmosphere_addlayers( atmosphere(m), atm )
551  IF ( error_status /= success ) THEN
552  error_status = failure
553  WRITE( message,'("Error adding FWD extra layers to profile #",i0)' ) m
554  CALL display_message( routine_name, message, error_status )
555  RETURN
556  END IF
557  ! ...Check the total number of Atm layers
558  IF ( atm%n_Layers > max_n_layers ) THEN
559  error_status = failure
560  WRITE( message,'("Added layers [",i0,"] cause total [",i0,"] to exceed the ",&
561  &"maximum allowed [",i0,"] for profile #",i0)' ) &
562  atm%n_Added_Layers, atm%n_Layers, max_n_layers, m
563  CALL display_message( routine_name, message, error_status )
564  RETURN
565  END IF
566  ! ...Similarly extend a copy of the input adjoint atmosphere
567  atm_ad = crtm_atmosphere_addlayercopy( atmosphere_ad(m), atm%n_Added_Layers )
568  ! ...Allocate the atmospheric optics structures based on Atm extension
569  CALL crtm_atmoptics_create( atmoptics, &
570  atm%n_Layers , &
573  CALL crtm_atmoptics_create( atmoptics_ad, &
574  atm%n_Layers , &
577  IF ( .NOT. crtm_atmoptics_associated( atmoptics ) .OR. &
578  .NOT. crtm_atmoptics_associated( atmoptics_ad ) ) THEN
579  error_status = failure
580  WRITE( message,'("Error allocating AtmOptics data structures for profile #",i0)' ) m
581  CALL display_message( routine_name, message, error_status )
582  RETURN
583  END IF
584  IF (options_present) THEN
585  ! Set Scattering Switch
586  atmoptics%Include_Scattering = options(m)%Include_Scattering
587  atmoptics_ad%Include_Scattering = options(m)%Include_Scattering
588  END IF
589  ! ...Allocate the atmospheric optics internal structure
590  CALL aovar_create( aovar, atm%n_Layers )
591 
592 
593  ! Allocate the scattering internal variables if necessary
594  ! ...Cloud
595  IF ( atm%n_Clouds > 0 ) THEN
596  CALL csvar_create( csvar, &
599  atm%n_Layers , &
600  atm%n_Clouds )
601  END IF
602  ! ...Aerosol
603  IF ( atm%n_Aerosols > 0 ) THEN
604  CALL asvar_create( asvar, &
607  atm%n_Layers , &
608  atm%n_Aerosols )
609  END IF
610 
611 
612  ! -----------
613  ! SENSOR LOOP
614  ! -----------
615  ! Initialise channel counter for sensor(n)/channel(l) count
616  ln = 0
617 
618  sensor_loop: DO n = 1, n_sensors
619 
620 
621  ! Shorter name
622  sensorindex = channelinfo(n)%Sensor_Index
623 
624 
625  ! Check if antenna correction to be applied for current sensor
626  IF ( user_antcorr .AND. &
627  accoeff_associated( sc(sensorindex)%AC ) .AND. &
628  ifov /= 0 ) THEN
629  compute_antcorr = .true.
630  ELSE
631  compute_antcorr = .false.
632  END IF
633 
634 
635  ! Allocate the AtmAbsorption predictor structures
636  CALL crtm_predictor_create( &
637  predictor , &
638  atm%n_Layers, &
639  sensorindex , &
640  savefwv = 1 )
641  CALL crtm_predictor_create( &
642  predictor_ad, &
643  atm%n_Layers, &
644  sensorindex )
645  IF ( (.NOT. crtm_predictor_associated(predictor)) .OR. &
646  (.NOT. crtm_predictor_associated(predictor_ad)) ) THEN
647  error_status=failure
648  WRITE( message,'("Error allocating predictor structures for profile #",i0, &
649  &" and ",a," sensor.")' ) m, sc(sensorindex)%Sensor_Id
650  CALL display_message( routine_name, message, error_status )
651  RETURN
652  END IF
653  ! ...Compute forward model predictors
654  CALL crtm_compute_predictors( sensorindex , & ! Input
655  atm , & ! Input
656  geometryinfo , & ! Input
657  ancillaryinput, & ! Input
658  predictor , & ! Output
659  pvar ) ! Internal variable output
660 
661 
662  ! Allocate the RTV structure if necessary
663  IF( (atm%n_Clouds > 0 .OR. &
664  atm%n_Aerosols > 0 .OR. &
665  spccoeff_isvisiblesensor( sc(sensorindex) ) ) .and. atmoptics%Include_Scattering ) THEN
666  CALL rtv_create( rtv, max_n_angles, max_n_legendre_terms, atm%n_Layers )
667  IF ( .NOT. rtv_associated(rtv) ) THEN
668  error_status=failure
669  WRITE( message,'("Error allocating RTV structure for profile #",i0, &
670  &" and ",a," sensor.")' ) m, trim(sc(sensorindex)%Sensor_Id)
671  CALL display_message( routine_name, message, error_status )
672  RETURN
673  END IF
674  ! Assign algorithm selector
675  rtv%RT_Algorithm_Id = rt_algorithm_id
676  END IF
677 
678 
679  ! Compute NLTE correction predictors
680  IF ( apply_nlte_correction ) THEN
681  CALL compute_nlte_predictor( &
682  sc(sensorindex)%NC, & ! Input
683  atm , & ! Input
684  geometryinfo , & ! Input
685  nlte_predictor ) ! Output
686  END IF
687 
688 
689  ! ------------
690  ! CHANNEL LOOP
691  ! ------------
692  channel_loop: DO l = 1, channelinfo(n)%n_Channels
693 
694  ! Channel setup
695  ! ...Skip channel if requested
696  IF ( .NOT. channelinfo(n)%Process_Channel(l) ) cycle channel_loop
697  ! ...Shorter name
698  channelindex = channelinfo(n)%Channel_Index(l)
699  ! ...Increment the processed channel counter
700  ln = ln + 1
701  ! ...Assign sensor+channel information to output
702  rtsolution(ln,m)%Sensor_Id = channelinfo(n)%Sensor_Id
703  rtsolution(ln,m)%WMO_Satellite_Id = channelinfo(n)%WMO_Satellite_Id
704  rtsolution(ln,m)%WMO_Sensor_Id = channelinfo(n)%WMO_Sensor_Id
705  rtsolution(ln,m)%Sensor_Channel = channelinfo(n)%Sensor_Channel(l)
706  rtsolution_ad(ln,m)%Sensor_Id = rtsolution(ln,m)%Sensor_Id
707  rtsolution_ad(ln,m)%WMO_Satellite_Id = rtsolution(ln,m)%WMO_Satellite_Id
708  rtsolution_ad(ln,m)%WMO_Sensor_Id = rtsolution(ln,m)%WMO_Sensor_Id
709  rtsolution_ad(ln,m)%Sensor_Channel = rtsolution(ln,m)%Sensor_Channel
710 
711 
712  ! Initialisations
713  CALL crtm_atmoptics_zero( atmoptics )
714  transmittance_ad = zero
715 
716 
717  ! Determine the number of streams (n_Full_Streams) in up+downward directions
718  IF ( user_n_streams ) THEN
719  n_full_streams = options(m)%n_Streams
720  rtsolution(ln,m)%n_Full_Streams = n_full_streams + 2
721  rtsolution(ln,m)%Scattering_Flag = .true.
722  ELSE
723  n_full_streams = crtm_compute_nstreams( atm , & ! Input
724  sensorindex , & ! Input
725  channelindex , & ! Input
726  rtsolution(ln,m) ) ! Output
727  END IF
728  ! ...Transfer stream count to scattering structures
729  atmoptics%n_Legendre_Terms = n_full_streams
730  atmoptics_ad%n_Legendre_Terms = n_full_streams
731 
732 
733  ! Compute the gas absorption
734  CALL crtm_compute_atmabsorption( sensorindex , & ! Input
735  channelindex , & ! Input
736  ancillaryinput, & ! Input
737  predictor , & ! Input
738  atmoptics , & ! Output
739  aavar ) ! Internal variable output
740 
741 
742  ! Compute the clear-sky atmospheric transmittance
743  ! for use in FASTEM-X reflection correction
744  CALL crtm_compute_transmittance(atmoptics,transmittance)
745 
746 
747  ! Compute the molecular scattering properties
748  ! ...Solar radiation
749  IF( sc(sensorindex)%Solar_Irradiance(channelindex) > zero .AND. &
750  source_za < max_source_zenith_angle) THEN
751  rtv%Solar_Flag_true = .true.
752  END IF
753  ! ...Visible channel with solar radiation
754  IF( spccoeff_isvisiblesensor( sc(sensorindex) ) .AND. rtv%Solar_Flag_true ) THEN
755  rtv%Visible_Flag_true = .true.
756  ! Rayleigh phase function has 0, 1, 2 components.
757  IF( atmoptics%n_Legendre_Terms < 4 ) THEN
758  atmoptics%n_Legendre_Terms = 4
759  atmoptics_ad%n_Legendre_Terms = atmoptics%n_Legendre_Terms
760  rtsolution(ln,m)%Scattering_FLAG = .true.
761  rtsolution(ln,m)%n_Full_Streams = atmoptics%n_Legendre_Terms + 2
762  END IF
763  rtv%n_Azi = min( atmoptics%n_Legendre_Terms - 1, max_n_azimuth_fourier )
764  ! Get molecular scattering and extinction
765  wavenumber = sc(sensorindex)%Wavenumber(channelindex)
766  error_status = crtm_compute_moleculescatter( &
767  wavenumber, &
768  atm , &
769  atmoptics )
770  IF ( error_status /= success ) THEN
771  WRITE( message,'("Error computing MoleculeScatter for ",a,&
772  &", channel ",i0,", profile #",i0)') &
773  trim(channelinfo(n)%Sensor_ID), &
774  channelinfo(n)%Sensor_Channel(l), &
775  m
776  CALL display_message( routine_name, message, error_status )
777  RETURN
778  END IF
779  ELSE
780  rtv%Visible_Flag_true = .false.
781  rtv%n_Azi = 0
782  END IF
783 
784 
785  ! Compute the cloud particle absorption/scattering properties
786  IF( atm%n_Clouds > 0 ) THEN
787  error_status = crtm_compute_cloudscatter( atm , & ! Input
788  sensorindex , & ! Input
789  channelindex, & ! Input
790  atmoptics , & ! Output
791  csvar ) ! Internal variable output
792  IF (error_status /= success) THEN
793  WRITE( message,'("Error computing CloudScatter for ",a,&
794  &", channel ",i0,", profile #",i0)' ) &
795  trim(channelinfo(n)%Sensor_ID), channelinfo(n)%Sensor_Channel(l), m
796  CALL display_message( routine_name, message, error_status )
797  RETURN
798  END IF
799  END IF
800 
801 
802  ! Compute the aerosol absorption/scattering properties
803  IF ( atm%n_Aerosols > 0 ) THEN
804  error_status = crtm_compute_aerosolscatter( atm , & ! Input
805  sensorindex , & ! Input
806  channelindex, & ! Input
807  atmoptics , & ! In/Output
808  asvar ) ! Internal variable output
809  IF ( error_status /= success ) THEN
810  WRITE( message,'("Error computing AerosolScatter for ",a,&
811  &", channel ",i0,", profile #",i0)' ) &
812  trim(channelinfo(n)%Sensor_ID), channelinfo(n)%Sensor_Channel(l), m
813  CALL display_message( routine_name, message, error_status )
814  RETURN
815  END IF
816  END IF
817 
818 
819  ! Compute the combined atmospheric optical properties
820  IF( atmoptics%Include_Scattering ) THEN
821  CALL crtm_combine_atmoptics( atmoptics, aovar )
822  END IF
823  ! ...Save vertically integrated scattering optical depth for output
824  rtsolution(ln,m)%SOD = atmoptics%Scattering_Optical_Depth
825 
826 
827  ! Turn off FASTEM-X reflection correction for scattering conditions
828  IF ( crtm_include_scattering(atmoptics) .AND. spccoeff_ismicrowavesensor( sc(sensorindex) ) ) THEN
829  sfcoptics%Transmittance = -one
830  ELSE
831  sfcoptics%Transmittance = transmittance
832  END IF
833 
834 
835  ! Fill the SfcOptics structure for the optional emissivity input case.
836  ! ...Indicate SfcOptics ARE to be computed
837  sfcoptics%Compute = .true.
838  ! ...Change SfcOptics emissivity/reflectivity contents/computation status
839  IF ( user_emissivity ) THEN
840  sfcoptics%Compute = .false.
841  sfcoptics%Emissivity(1,1) = options(m)%Emissivity(ln)
842  sfcoptics%Reflectivity(1,1,1,1) = one - options(m)%Emissivity(ln)
843  IF ( user_direct_reflectivity ) THEN
844  sfcoptics%Direct_Reflectivity(1,1) = options(m)%Direct_Reflectivity(ln)
845  ELSE
846  sfcoptics%Direct_Reflectivity(1,1) = sfcoptics%Reflectivity(1,1,1,1)
847  END IF
848  END IF
849 
850 
851  ! Fourier component loop for azimuth angles (VIS).
852  ! mth_Azi = 0 is for an azimuth-averaged value (IR, MW)
853  ! ...Initialise radiance
854  rtsolution(ln,m)%Radiance = zero
855  ! ...Initialise adjoint atmospheric optics
856  CALL crtm_atmoptics_zero( atmoptics_ad )
857 
858 
859 
860  ! ###################################################
861  ! TEMPORARY FIX : SENSOR-DEPENDENT AZIMUTH ANGLE LOOP
862  ! ###################################################
863  sensor_dependent_rtsolution: &
864  IF ( spccoeff_isinfraredsensor( sc(sensorindex) ) .OR. &
865  spccoeff_ismicrowavesensor( sc(sensorindex) ) ) THEN
866  ! ------------------------------
867  ! INFRARED and MICROWAVE sensors
868  ! ------------------------------
869 
870  ! Set dependent component counters
871  rtv%mth_Azi = 0
872  sfcoptics%mth_Azi = 0
873 
874  ! Solve the forward radiative transfer problem
875  error_status = crtm_compute_rtsolution( &
876  atm , & ! Input
877  surface(m) , & ! Input
878  atmoptics , & ! Input
879  sfcoptics , & ! Input
880  geometryinfo , & ! Input
881  sensorindex , & ! Input
882  channelindex , & ! Input
883  rtsolution(ln,m), & ! Output
884  rtv ) ! Internal variable output
885  IF ( error_status /= success ) THEN
886  WRITE( message,'( "Error computing RTSolution for ", a, &
887  &", channel ", i0,", profile #",i0)' ) &
888  trim(channelinfo(n)%Sensor_ID), channelinfo(n)%Sensor_Channel(l), m
889  CALL display_message( routine_name, message, error_status )
890  RETURN
891  END IF
892 
893  ! Compute non-LTE correction to radiance if required
894  IF ( apply_nlte_correction .AND. nlte_predictor_isactive(nlte_predictor) ) &
896  sc(sensorindex)%NC , & ! Input
897  channelindex , & ! Input
898  nlte_predictor , & ! Input
899  rtsolution(ln,m)%Radiance ) ! In/Output
900 
901  ! Convert the radiance to brightness temperature
903  sensorindex , & ! Input
904  channelindex , & ! Input
905  rtsolution(ln,m)%Radiance , & ! Input
906  rtsolution(ln,m)%Brightness_Temperature ) ! Output
907 
908  ! Compute Antenna correction to brightness temperature if required
909  IF ( compute_antcorr ) THEN
910  CALL crtm_compute_antcorr( &
911  geometryinfo , & ! Input
912  sensorindex , & ! Input
913  channelindex , & ! Input
914  rtsolution(ln,m) ) ! Output
916  geometryinfo , & ! Input
917  sensorindex , & ! Input
918  channelindex , & ! Input
919  rtsolution_ad(ln,m) ) ! Output
920  END IF
921 
922  ! Compute the Planck temperature adjoijnt
924  sensorindex , & ! Input
925  channelindex , & ! Input
926  rtsolution(ln,m)%Radiance , & ! Input
927  rtsolution_ad(ln,m)%Brightness_Temperature, & ! Input
928  rtsolution_ad(ln,m)%Radiance ) ! Output
929  rtsolution_ad(ln,m)%Brightness_Temperature = zero
930 
931  ! Compute non-LTE correction adjoint if required
932  IF ( apply_nlte_correction .AND. nlte_predictor_isactive(nlte_predictor) ) &
934  sc(sensorindex)%NC , & ! Input
935  channelindex , & ! Input
936  rtsolution_ad(ln,m)%Radiance, & ! Input
937  nlte_predictor_ad ) ! Output
938 
939  ! The adjoint of the radiative transfer
940  error_status = crtm_compute_rtsolution_ad( &
941  atm , & ! FWD Input
942  surface(m) , & ! FWD Input
943  atmoptics , & ! FWD Input
944  sfcoptics , & ! FWD Input
945  rtsolution(ln,m) , & ! FWD Input
946  rtsolution_ad(ln,m), & ! AD Input
947  geometryinfo , & ! Input
948  sensorindex , & ! Input
949  channelindex , & ! Input
950  atm_ad , & ! AD Output
951  surface_ad(m) , & ! AD Output
952  atmoptics_ad , & ! AD Output
953  sfcoptics_ad , & ! AD Output
954  rtv ) ! Internal variable input
955  IF ( error_status /= success ) THEN
956  WRITE( message,'( "Error computing RTSolution_AD for ", a, &
957  &", channel ", i0,", profile #",i0)' ) &
958  trim(channelinfo(n)%Sensor_ID), channelinfo(n)%Sensor_Channel(l), m
959  CALL display_message( routine_name, message, error_status )
960  RETURN
961  END IF
962 
963 
964  ELSE sensor_dependent_rtsolution
965  ! --------------
966  ! VISIBLE sensor
967  ! --------------
968  ! ...Fourier expansion over azimuth angle
969  azimuth_fourier_loop: DO mth_azi = 0, rtv%n_Azi
970 
971  ! Set dependent component counters
972  rtv%mth_Azi = mth_azi
973  sfcoptics%mth_Azi = mth_azi
974 
975  ! Solve the forward radiative transfer problem
976  error_status = crtm_compute_rtsolution( &
977  atm , & ! Input
978  surface(m) , & ! Input
979  atmoptics , & ! Input
980  sfcoptics , & ! Input
981  geometryinfo , & ! Input
982  sensorindex , & ! Input
983  channelindex , & ! Input
984  rtsolution(ln,m), & ! Output
985  rtv ) ! Internal variable output
986  IF ( error_status /= success ) THEN
987  WRITE( message,'( "Error computing RTSolution for ", a, &
988  &", channel ", i0,", profile #",i0)' ) &
989  trim(channelinfo(n)%Sensor_ID), channelinfo(n)%Sensor_Channel(l), m
990  CALL display_message( routine_name, message, error_status )
991  RETURN
992  END IF
993 
994  ! The adjoint of the radiative transfer
995  error_status = crtm_compute_rtsolution_ad( &
996  atm , & ! FWD Input
997  surface(m) , & ! FWD Input
998  atmoptics , & ! FWD Input
999  sfcoptics , & ! FWD Input
1000  rtsolution(ln,m) , & ! FWD Input
1001  rtsolution_ad(ln,m), & ! AD Input
1002  geometryinfo , & ! Input
1003  sensorindex , & ! Input
1004  channelindex , & ! Input
1005  atm_ad , & ! AD Output
1006  surface_ad(m) , & ! AD Output
1007  atmoptics_ad , & ! AD Output
1008  sfcoptics_ad , & ! AD Output
1009  rtv ) ! Internal variable input
1010  IF ( error_status /= success ) THEN
1011  WRITE( message,'( "Error computing RTSolution_AD for ", a, &
1012  &", channel ", i0,", profile #",i0)' ) &
1013  trim(channelinfo(n)%Sensor_ID), channelinfo(n)%Sensor_Channel(l), m
1014  CALL display_message( routine_name, message, error_status )
1015  RETURN
1016  END IF
1017  END DO azimuth_fourier_loop
1018 
1019  ! Still want to convert the final FORWARD radiance to brightness temperature
1020  CALL crtm_planck_temperature( &
1021  sensorindex , & ! Input
1022  channelindex , & ! Input
1023  rtsolution(ln,m)%Radiance , & ! Input
1024  rtsolution(ln,m)%Brightness_Temperature ) ! Output
1025 
1026  END IF sensor_dependent_rtsolution
1027  ! ###################################################
1028  ! TEMPORARY FIX : SENSOR-DEPENDENT AZIMUTH ANGLE LOOP
1029  ! ###################################################
1030 
1031 
1032  ! Compute the adjoint of the combined atmospheric optical properties
1033  IF( atmoptics%Include_Scattering ) THEN
1034  CALL crtm_combine_atmoptics_ad( atmoptics, atmoptics_ad, aovar )
1035  END IF
1036 
1037 
1038  ! Compute the adjoint aerosol absorption/scattering properties
1039  IF ( atm%n_Aerosols > 0 ) THEN
1040  error_status = crtm_compute_aerosolscatter_ad( atm , & ! FWD Input
1041  atmoptics , & ! FWD Input
1042  atmoptics_ad, & ! AD Input
1043  sensorindex , & ! Input
1044  channelindex, & ! Input
1045  atm_ad , & ! AD Output
1046  asvar ) ! Internal variable input
1047  IF ( error_status /= success ) THEN
1048  WRITE( message,'("Error computing AerosolScatter_AD for ",a,&
1049  &", channel ",i0,", profile #",i0)' ) &
1050  trim(channelinfo(n)%Sensor_ID), channelinfo(n)%Sensor_Channel(l), m
1051  CALL display_message( routine_name, message, error_status )
1052  RETURN
1053  END IF
1054  END IF
1055 
1056 
1057  ! Compute the adjoint cloud absorption/scattering properties
1058  IF ( atm%n_Clouds > 0 ) THEN
1059  error_status = crtm_compute_cloudscatter_ad( atm , & ! FWD Input
1060  atmoptics , & ! FWD Input
1061  atmoptics_ad, & ! AD Input
1062  sensorindex , & ! Input
1063  channelindex, & ! Input
1064  atm_ad , & ! AD Output
1065  csvar ) ! Internal variable input
1066  IF ( error_status /= success ) THEN
1067  WRITE( message,'("Error computing CloudScatter_AD for ",a,&
1068  &", channel ",i0,", profile #",i0)' ) &
1069  trim(channelinfo(n)%Sensor_ID), channelinfo(n)%Sensor_Channel(l), m
1070  CALL display_message( routine_name, message, error_status )
1071  RETURN
1072  END IF
1073  END IF
1074 
1075 
1076  ! Compute the adjoint molecular scattering properties
1077  IF( rtv%Visible_Flag_true ) THEN
1078  wavenumber = sc(sensorindex)%Wavenumber(channelindex)
1079  error_status = crtm_compute_moleculescatter_ad( &
1080  wavenumber , &
1081  atmoptics_ad, &
1082  atm_ad )
1083  IF ( error_status /= success ) THEN
1084  WRITE( message,'("Error computing MoleculeScatter_AD for ",a,&
1085  &", channel ",i0,", profile #",i0)' ) &
1086  trim(channelinfo(n)%Sensor_ID), &
1087  channelinfo(n)%Sensor_Channel(l), &
1088  m
1089  CALL display_message( routine_name, message, error_status )
1090  RETURN
1091  END IF
1092  END IF
1093 
1094 
1095  ! Compute the adjoint of the total atmospheric transmittance
1096  IF ( crtm_no_scattering(atmoptics) .AND. spccoeff_ismicrowavesensor(sc(sensorindex)) ) THEN
1097  transmittance_ad = sfcoptics_ad%transmittance
1098  sfcoptics_ad%transmittance = zero
1099  CALL crtm_compute_transmittance_ad(atmoptics,transmittance_ad,atmoptics_ad)
1100  END IF
1101 
1102 
1103  ! Compute the adjoint gaseous absorption
1104  CALL crtm_compute_atmabsorption_ad( sensorindex , & ! Input
1105  channelindex , & ! Input
1106  predictor , & ! FWD Input
1107  atmoptics_ad , & ! AD Input
1108  predictor_ad , & ! AD Output
1109  aavar ) ! Internal variable input
1110  END DO channel_loop
1111 
1112 
1113  ! Adjoint of the NLTE correction predictor calculations
1114  IF ( apply_nlte_correction ) THEN
1116  nlte_predictor , & ! Input
1117  nlte_predictor_ad, & ! Input
1118  atm_ad ) ! Output
1119  END IF
1120 
1121 
1122  ! Adjoint of the predictor calculations
1123  CALL crtm_compute_predictors_ad( sensorindex , & ! Input
1124  atm , & ! FWD Input
1125  predictor , & ! FWD Input
1126  predictor_ad , & ! AD Input
1127  ancillaryinput, & ! Input
1128  atm_ad , & ! AD Output
1129  pvar ) ! Internal variable input
1130 
1131 
1132  ! Deallocate local sensor dependent data structures
1133  ! ...RTV structure
1134  IF ( rtv_associated(rtv) ) CALL rtv_destroy(rtv)
1135  ! ...Predictor structures
1136  CALL crtm_predictor_destroy( predictor )
1137  CALL crtm_predictor_destroy( predictor_ad )
1138 
1139  END DO sensor_loop
1140 
1141 
1142  ! Postprocess some input data
1143  ! ...Adjoint of average surface skin temperature for multi-surface types
1144  CALL crtm_compute_surfacet_ad( surface(m), sfcoptics_ad, surface_ad(m) )
1145  ! ...Adjoint of the atmosphere layer addition
1146  error_status = crtm_atmosphere_addlayers_ad( atmosphere(m), atm_ad, atmosphere_ad(m) )
1147  IF ( error_status /= success ) THEN
1148  error_status = failure
1149  WRITE( message,'("Error adding AD extra layers to profile #",i0)' ) m
1150  CALL display_message( routine_name, message, error_status )
1151  RETURN
1152  END IF
1153 
1154 
1155  ! Deallocate local sensor independent data structures
1156  ! ...Atmospheric optics
1157  CALL crtm_atmoptics_destroy( atmoptics )
1158  CALL crtm_atmoptics_destroy( atmoptics_ad )
1159 
1160  END DO profile_loop
1161 
1162 
1163  ! Destroy any remaining structures
1164  CALL crtm_sfcoptics_destroy( sfcoptics )
1165  CALL crtm_sfcoptics_destroy( sfcoptics_ad )
1166  CALL crtm_atmosphere_destroy( atm_ad )
1167  CALL crtm_atmosphere_destroy( atm )
1168 
1169  END FUNCTION crtm_adjoint
1170 
1171 
1172 !--------------------------------------------------------------------------------
1173 !:sdoc+:
1174 !
1175 ! NAME:
1176 ! CRTM_Adjoint_Version
1177 !
1178 ! PURPOSE:
1179 ! Subroutine to return the module version information.
1180 !
1181 ! CALLING SEQUENCE:
1182 ! CALL CRTM_Adjoint_Version( Id )
1183 !
1184 ! OUTPUTS:
1185 ! Id: Character string containing the version Id information
1186 ! for the module.
1187 ! UNITS: N/A
1188 ! TYPE: CHARACTER(*)
1189 ! DIMENSION: Scalar
1190 ! ATTRIBUTES: INTENT(OUT)
1191 !
1192 !:sdoc-:
1193 !--------------------------------------------------------------------------------
1194 
1195  SUBROUTINE crtm_adjoint_version( Id )
1196  CHARACTER(*), INTENT(OUT) :: id
1197  id = module_version_id
1198  END SUBROUTINE crtm_adjoint_version
1199 
1200 END MODULE crtm_adjoint_module
integer function, public crtm_compute_aerosolscatter_ad(Atm, AScat, AScat_AD, SensorIndex, ChannelIndex, Atm_AD, ASV)
integer function, public crtm_adjoint(Atmosphere, Surface, RTSolution_AD, Geometry, ChannelInfo, Atmosphere_AD, Surface_AD, RTSolution, Options)
subroutine, public crtm_compute_transmittance(atmoptics, transmittance)
logical function, public crtm_aerosolcoeff_isloaded()
integer, parameter, public max_n_azimuth_fourier
elemental type(crtm_atmosphere_type) function, public crtm_atmosphere_addlayercopy(atm, n_Added_Layers)
logical function, public crtm_cloudcoeff_isloaded()
integer, parameter, public failure
integer, parameter, public set
real(fp), parameter, public zero
integer, parameter, public warning
integer, parameter, public max_n_phase_elements
subroutine, public crtm_combine_atmoptics(AtmOptics, AOvar)
logical function, public crtm_options_isvalid(self)
integer, parameter, public fp
Definition: Type_Kinds.f90:124
subroutine, public crtm_adjoint_version(Id)
elemental subroutine, public crtm_atmosphere_destroy(Atm)
integer, parameter, public max_n_angles
real(fp), parameter, public scattering_albedo_threshold
integer function, public crtm_compute_moleculescatter_ad(Wavenumber, AtmOptics_AD, Atmosphere_AD, Message_Log)
elemental subroutine, public crtm_geometryinfo_setvalue(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)
logical function, public crtm_atmosphere_isvalid(Atm)
subroutine, public crtm_combine_atmoptics_ad(AtmOptics, AtmOptics_AD, AOvar)
elemental subroutine, public crtm_atmoptics_destroy(self)
elemental subroutine, public csvar_create(self, n_Legendre_Terms, n_Phase_Elements, n_Layers, n_Clouds)
elemental subroutine, public crtm_geometryinfo_compute(gInfo)
elemental subroutine, public crtm_predictor_create(self, n_Layers, SensorIndex, SaveFWV)
pure logical function, public crtm_include_scattering(atmoptics)
integer, parameter, public max_n_legendre_terms
elemental subroutine, public crtm_sfcoptics_create(SfcOptics, n_Angles, n_Stokes)
integer function, public crtm_compute_rtsolution(Atmosphere, Surface, AtmOptics, SfcOptics, GeometryInfo, SensorIndex, ChannelIndex, RTSolution, RTV)
elemental logical function, public crtm_atmoptics_associated(self)
real(fp), parameter, public max_source_zenith_angle
elemental subroutine, public rtv_create(RTV, n_Angles, n_Legendre_Terms, n_Layers)
Definition: RTV_Define.f90:408
elemental subroutine, public crtm_atmoptics_zero(self)
integer, parameter, public max_n_streams
pure logical function, public crtm_no_scattering(atmoptics)
integer, parameter, public max_n_stokes
integer function, public crtm_compute_aerosolscatter(Atm, SensorIndex, ChannelIndex, AScat, ASV)
subroutine, public crtm_compute_surfacet_ad(Surface, SfcOptics_AD, Surface_AD)
subroutine, public crtm_planck_temperature_ad(n, l, Radiance, Temperature_AD, Radiance_AD)
integer function, public crtm_compute_cloudscatter(Atm, SensorIndex, ChannelIndex, CScat, CSV)
integer, parameter, public not_set
real(fp), parameter, public one
recursive subroutine, public display_message(Routine_Name, Message, Error_State, Message_Log)
integer function, public crtm_compute_moleculescatter(Wavenumber, Atmosphere, AtmOptics, Message_Log)
elemental logical function, public csvar_associated(self)
integer function, public crtm_atmosphere_addlayers_ad(Atm_In, Atm_Out_AD, Atm_In_AD)
subroutine, public crtm_compute_surfacet(Surface, SfcOptics)
subroutine, public compute_nlte_predictor_ad(NLTE_Predictor, NLTE_Predictor_AD, Atm_AD)
subroutine, public crtm_compute_antcorr(gI, n, l, RT)
elemental subroutine, public asvar_destroy(self)
elemental logical function, public crtm_sfcoptics_associated(SfcOptics)
elemental subroutine, public csvar_destroy(self)
integer function, public crtm_compute_nstreams(Atmosphere, SensorIndex, ChannelIndex, RTSolution)
elemental subroutine, public crtm_atmoptics_create(self, n_Layers, n_Legendre_Terms, n_Phase_Elements)
logical function, public crtm_surface_isvalid(Sfc)
logical function, public crtm_geometry_isvalid(geo)
integer function, public crtm_compute_cloudscatter_ad(Atm, CScat, CScat_AD, SensorIndex, ChannelIndex, Atm_AD, CSV)
elemental subroutine, public crtm_predictor_destroy(self)
subroutine, public crtm_compute_transmittance_ad(atmoptics, transmittance_AD, atmoptics_AD)
subroutine, public crtm_compute_predictors(SensorIndex, Atmosphere, GeometryInfo, AncillaryInput, Predictor, iVar)
subroutine, public compute_nlte_correction_ad(NLTECoeff, ChannelIndex, Radiance_AD, NLTE_Predictor_AD)
integer function, public crtm_compute_rtsolution_ad(Atmosphere, Surface, AtmOptics, SfcOptics, RTSolution, RTSolution_AD, GeometryInfo, SensorIndex, ChannelIndex, Atmosphere_AD, Surface_AD, AtmOptics_AD, SfcOptics_AD, RTV)
type(spccoeff_type), dimension(:), allocatable, save, public sc
elemental logical function, public asvar_associated(self)
integer, parameter, public max_n_layers
subroutine, public compute_nlte_correction(NLTECoeff, ChannelIndex, NLTE_Predictor, Radiance)
subroutine, public crtm_compute_atmabsorption_ad(SensorIndex, ChannelIndex, Predictor, AtmOptics_AD, Predictor_AD, iVar)
subroutine, public crtm_compute_atmabsorption(SensorIndex, ChannelIndex, AncillaryInput, Predictor, AtmOptics, iVar)
elemental subroutine, public crtm_sfcoptics_destroy(SfcOptics)
subroutine, public crtm_compute_predictors_ad(SensorIndex, Atmosphere, Predictor, Predictor_AD, AncillaryInput, Atmosphere_AD, iVar)
integer function, public crtm_atmosphere_addlayers(Atm_In, Atm_Out)
subroutine, public crtm_planck_temperature(n, l, Radiance, Temperature)
elemental integer function, public crtm_channelinfo_n_channels(ChannelInfo)
subroutine, public compute_nlte_predictor(NLTECoeff, Atm, gInfo, NLTE_Predictor)
elemental logical function, public crtm_predictor_associated(self)
#define min(a, b)
Definition: mosaic_util.h:32
elemental logical function, public rtv_associated(RTV)
Definition: RTV_Define.f90:314
elemental subroutine, public asvar_create(self, n_Legendre_Terms, n_Phase_Elements, n_Layers, n_Aerosols)
subroutine, public crtm_compute_antcorr_ad(gI, n, l, RT_AD)
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)
character(*), parameter module_version_id
elemental logical function, public accoeff_associated(ACCoeff)
elemental subroutine, public rtv_destroy(RTV)
Definition: RTV_Define.f90:348
integer function, public crtm_get_pressurelevelidx(Atm, Level_Pressure)
elemental logical function, public nltecoeff_associated(NLTECoeff)