<HTML> <BODY BGCOLOR=#ccccdd LINK=#0000aa VLINK=#0000ff ALINK=#ff0000 ><BASE TARGET="bottom_target"><PRE>
<A NAME='MODULE_RADIANCE'><A href='../../html_code/radiance/module_radiance.f90.html#MODULE_RADIANCE' TARGET='top_target'><IMG SRC="../../gif/bar_purple.gif" border=0></A>

module module_radiance 15

   !---------------------------------------------------------------------------
   ! Purpose: module for radiance data assimilation. 
   !---------------------------------------------------------------------------

   use da_control, only : pi, use_landem, t_landem, t_kelvin
   use da_reporting, only : da_error,message

#ifdef RTTOV
   use rttov_const,  only : &amp;
            errorstatus_success, &amp;
            errorstatus_fatal,   &amp;
            gas_id_watervapour,  &amp;
            sensor_id_ir,        &amp;
            sensor_id_mw,        &amp;
            sensor_id_hi
   use rttov_types, only :  &amp;
         rttov_options,     &amp;
         rttov_opts_rt_ir,  &amp;
         rttov_coefs,       &amp;
         profile_type,      &amp;
         transmission_type, &amp;
         radiance_type,     &amp;
         rttov_chanprof,    &amp;
         rttov_emissivity
   use parkind1, only : jpim, jprb
#endif

#ifdef CRTM
  ! -- Modules to define CRTM constants etc.
   !USE Type_Kinds
   !USE Error_Handler
   !USE CRTM_Utility

  ! -- CRTM RT_models modules
   USE CRTM_Module, only : graupel_cloud, rain_cloud, snow_cloud,crtm_adjoint, &amp;
      crtm_atmosphere_create, crtm_surface_create, &amp;
      crtm_atmosphere_destroy, crtm_surface_destroy, &amp;
      crtm_forward,crtm_init,crtm_k_matrix, &amp;
      crtm_tangent_linear, h2o_id,hail_cloud,ice_cloud, &amp;
      o3_id, water_cloud, crtm_rtsolution_type, crtm_channelinfo_type, &amp;
      crtm_atmosphere_type, crtm_surface_type, crtm_geometry_type, &amp;
      crtm_surface_zero, crtm_atmosphere_zero, crtm_destroy, &amp;
      climatology_model_name, &amp;
      crtm_options_type, crtm_options_create, crtm_options_destroy, &amp;
      crtm_rtsolution_create, crtm_rtsolution_destroy, crtm_rtsolution_associated, &amp;
      crtm_irlandcoeff_classification
   USE CRTM_Atmosphere_Define, only: crtm_atmosphere_associated, &amp;
      MASS_MIXING_RATIO_UNITS, VOLUME_MIXING_RATIO_UNITS
   USE CRTM_Surface_Define, only: crtm_surface_associated
   USE CRTM_Options_Define, only: crtm_options_associated

   USE CRTM_SensorInfo
   USE CRTM_Planck_Functions, only : CRTM_Planck_Temperature, &amp;
      CRTM_Planck_Radiance, CRTM_Planck_Temperature_TL, &amp;
      CRTM_Planck_Temperature_AD
#endif

   use gsi_kinds      ,  only : r_kind,r_double,i_kind,r_single
   use gsi_constants  ,  only : deg2rad, rad2deg,       &amp;
                            init_constants_derived, &amp;
                            one, three, zero, half, &amp;
                            one_tenth, two, four

   ! use irsse_model, only: forward_irsse
   implicit none
   
   real, parameter             :: q2ppmv = 1.60771704e+6   ! q_mixratio_to_ppmv

  ! cf. RTTOV-11 Users Guide Table 2
  ! index 19 is sentinel3 in Table 2, here we keep it as tiros for 
  ! WRFDA backward compatibility
  Character (len=8), Parameter :: rttov_platform_name(1:35) =          &amp;
     &amp; (/ 'noaa    ', 'dmsp    ', 'meteosat', 'goes    ', 'gms     ',  &amp;
        &amp; 'fy2     ', 'trmm    ', 'ers     ', 'eos     ', 'metop   ',  &amp;
        &amp; 'envisat ', 'msg     ', 'fy1     ', 'adeos   ', 'mtsat   ',  &amp;
        &amp; 'coriolis', 'jpss    ', 'gifts   ', 'tiros   ', 'meghatr ',  &amp;
        &amp; 'kalpana ', 'reserved', 'fy3     ', 'coms    ', 'meteor-m',  &amp;
        &amp; 'gosat   ', 'calipso ', 'reserved', 'gcom-w  ', 'nimbus  ',  &amp;
        &amp; 'himawari', 'mtg     ', 'saral   ', 'metop-ng', 'landsat '/)

  ! cf. RTTOV-11 Users Guide Table 3
  ! List of instruments  !!!! HIRS is number 0
  Character (len=8), Dimension(0:65) :: rttov_inst_name  =             &amp;
     &amp; (/ 'hirs    ', 'msu     ', 'ssu     ', 'amsua   ', 'amsub   ',  &amp;
        &amp; 'avhrr   ', 'ssmi    ', 'vtpr1   ', 'spare   ', 'tmi     ',  &amp;
        &amp; 'ssmis   ', 'airs    ', 'hsb     ', 'modis   ', 'atsr    ',  &amp;
        &amp; 'mhs     ', 'iasi    ', 'amsre   ', 'imager  ', 'atms    ',  &amp;
        &amp; 'mviri   ', 'seviri  ', 'imager  ', 'sounder ', 'imager  ',  &amp;
        &amp; 'vissr   ', 'mvisr   ', 'cris    ', 'spare   ', 'viirs   ',  &amp;
        &amp; 'windsat ', 'gifts   ', 'ssmt1   ', 'ssmt2   ', 'saphir  ',  &amp;
        &amp; 'madras  ', 'spare   ', 'imager  ', 'reserved', 'reserved',  &amp;
        &amp; 'mwts    ', 'mwhs    ', 'iras    ', 'mwri    ', 'abi     ',  &amp;
        &amp; 'mi      ', 'msumr   ', 'reserved', 'iir     ', 'mwr     ',  &amp;
        &amp; 'reserved', 'reserved', 'reserved', 'reserved', 'scams   ',  &amp;
        &amp; 'smmr    ', 'ahi     ', 'irs     ', 'altika  ', 'iasing  ',  &amp;
        &amp; 'tm      ', 'fci     ', 'amsr1   ', 'amsr2   ', 'vissr   ',  &amp;
        &amp; 'slstr   '/)

  ! cf. rttov_platform_name above and CRTM: v2.1.3 User Guide Table B.1
  ! n=noaa; f=dmsp; g=goes; eos-2/1=aqua/terra;
  ! xxxxxxxx means crtm does not have corresponding coefficient file.
  ! For satellite names that can not be directly mapped here to names
  ! used in crtm coeff names, they will be re-set in
  ! da_crtm_sensor_descriptor.inc
  Character (len=8), Parameter :: crtm_platform_name(1:35) =           &amp;
     &amp; (/ 'n       ', 'f       ', 'm       ', 'g       ', 'gms     ',  &amp;
        &amp; 'xxxxxxxx', 'trmm    ', 'ers     ', 'eos     ', 'metop   ',  &amp;
        &amp; 'envisat ', 'msg     ', 'xxxxxxxx', 'xxxxxxxx', 'mt      ',  &amp;
        &amp; 'coriolis', 'npp     ', 'gifts   ', 'tiros   ', 'meghat  ',  &amp;
        &amp; 'kalpana ', 'tiros   ', 'fy3     ', 'coms    ', 'xxxxxxxx',  &amp;
        &amp; 'xxxxxxxx', 'xxxxxxxx', 'reserved', 'gcom-w  ', 'xxxxxxxx',  &amp;
        &amp; 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx'/)

  ! cf. rttov_inst_name above and CRTM: v2.1.3 User Guide Table B.1
  ! List of instruments  !!!! HIRS is number 0
  ! xxxxxxxx means crtm does not have corresponding coefficient file.
  ! For instrument names that can not be directly mapped here to names
  ! used in crtm coeff names, they will be re-set in
  ! da_crtm_sensor_descriptor.inc
  Character (len=8), Dimension(0:65) :: crtm_sensor_name  =            &amp;
     &amp; (/ 'hirs    ', 'msu     ', 'ssu     ', 'amsua   ', 'amsub   ',  &amp;
        &amp; 'avhrr   ', 'ssmi    ', 'xxxxxxxx', 'spare   ', 'tmi     ',  &amp;
        &amp; 'ssmis   ', 'airs    ', 'hsb     ', 'modis   ', 'atsr    ',  &amp;
        &amp; 'mhs     ', 'iasi    ', 'amsre   ', 'imgr    ', 'atms    ',  &amp;
        &amp; 'mviri   ', 'seviri  ', 'imgr    ', 'sndr    ', 'imgr    ',  &amp;
        &amp; 'vissr   ', 'xxxxxxxx', 'cris    ', 'spare   ', 'viirs   ',  &amp;
        &amp; 'windsat ', 'xxxxxxxx', 'ssmt1   ', 'ssmt2   ', 'saphir  ',  &amp;
        &amp; 'madras  ', 'spare   ', 'imgr    ', 'reserved', 'reserved',  &amp;
        &amp; 'mwts    ', 'mwhs    ', 'iras    ', 'mwri    ', 'abi     ',  &amp;
        &amp; 'xxxxxxxx', 'xxxxxxxx', 'reserved', 'xxxxxxxx', 'xxxxxxxx',  &amp;
        &amp; 'reserved', 'reserved', 'reserved', 'reserved', 'xxxxxxxx',  &amp;
        &amp; 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx',  &amp;
        &amp; 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx', 'amsr2   ', 'vissr   ',  &amp;
        &amp; 'xxxxxxxx'/)

#ifdef RTTOV
   type (rttov_coefs), allocatable   :: coefs(:)     ! coefficients structure
   type (rttov_options), allocatable :: opts(:)      ! options structure
   type (rttov_opts_rt_ir), allocatable :: opts_rt_ir(:) ! options structure
#endif

   type satinfo_type
      integer, pointer   :: ichan(:)      ! channel index
      integer, pointer   :: iuse (:)      ! usage flag (-1: not use) from GSI info file
      real   , pointer   :: error(:)      ! error Standard Deviation from GSI info file
      real   , pointer   :: polar(:)      ! polarisation (0:ver; 1:hori) from GSI info file
      real   , pointer   :: error_factor(:) ! error tuning factor ! from error tuning file
     ! new air mass bias correction coefs.
      real   , pointer   :: scanbias(:,:) ! scan bias without latitude band variation
      real   , pointer   :: scanbias_b(:,:,:) ! scan bias with latitude band variation
      real   , pointer   :: bcoef(:,:)   ! airmass predictor bias coefficients
      real   , pointer   :: bcoef0(:)    ! airmass constant coefficient
      real   , pointer   :: error_std(:) ! error standard deviation
   end type satinfo_type

   type (satinfo_type), pointer :: satinfo(:)

   CHARACTER( 80 ), allocatable, save :: Sensor_Descriptor(:)

end module module_radiance