updated top-level README and version_decl for V4.5 (#1847)
[WRF.git] / var / da / da_radiance / module_radiance.f90
blob2fbfdd0a9cda3aff5b20a356a13d8ca667545d46
1 module module_radiance
3 !---------------------------------------------------------------------------
4 ! Purpose: module for radiance data assimilation.
5 !---------------------------------------------------------------------------
7 use da_control, only : pi, use_landem, t_landem, t_kelvin
8 use da_reporting, only : da_error,message
10 #ifdef RTTOV
11 use rttov_const, only : &
12 errorstatus_success, &
13 errorstatus_fatal, &
14 gas_id_watervapour, &
15 sensor_id_ir, &
16 sensor_id_mw, &
17 sensor_id_hi, &
18 sensor_id_po
19 use rttov_types, only : &
20 rttov_options, &
21 rttov_opts_rt_ir, &
22 rttov_coefs, &
23 rttov_profile, &
24 rttov_transmission, &
25 rttov_radiance, &
26 rttov_chanprof, &
27 rttov_emissivity
28 use parkind1, only : jpim, jprb
29 use mod_rttov_emis_atlas, only : &
30 rttov_emis_atlas_data, &
31 atlas_type_mw, &
32 atlas_type_ir
33 #endif
35 #ifdef CRTM
36 ! -- Modules to define CRTM constants etc.
37 !USE Type_Kinds
38 !USE Error_Handler
39 !USE CRTM_Utility
41 ! -- CRTM RT_models modules
42 USE CRTM_Module, only : graupel_cloud, rain_cloud, snow_cloud,crtm_adjoint, &
43 crtm_atmosphere_create, crtm_surface_create, &
44 crtm_atmosphere_destroy, crtm_surface_destroy, &
45 crtm_forward,crtm_init,crtm_k_matrix, &
46 crtm_tangent_linear, h2o_id,hail_cloud,ice_cloud, &
47 o3_id, water_cloud, crtm_rtsolution_type, crtm_channelinfo_type, &
48 crtm_atmosphere_type, crtm_surface_type, crtm_geometry_type, &
49 crtm_surface_zero, crtm_atmosphere_zero, crtm_destroy, &
50 climatology_model_name, &
51 crtm_options_type, crtm_options_create, crtm_options_destroy, &
52 crtm_rtsolution_create, crtm_rtsolution_destroy, crtm_rtsolution_associated, &
53 crtm_irlandcoeff_classification
54 USE CRTM_Atmosphere_Define, only: crtm_atmosphere_associated, &
55 MASS_MIXING_RATIO_UNITS, VOLUME_MIXING_RATIO_UNITS
56 USE CRTM_Surface_Define, only: crtm_surface_associated
57 USE CRTM_Options_Define, only: crtm_options_associated
59 USE CRTM_SensorInfo
60 USE CRTM_Planck_Functions, only : CRTM_Planck_Temperature, &
61 CRTM_Planck_Radiance, CRTM_Planck_Temperature_TL, &
62 CRTM_Planck_Temperature_AD
63 #endif
65 use gsi_kinds , only : r_kind,r_double,i_kind,r_single
66 use gsi_constants , only : deg2rad, rad2deg, &
67 init_constants_derived, &
68 one, three, zero, half, &
69 one_tenth, two, four
71 ! use irsse_model, only: forward_irsse
72 implicit none
74 real, parameter :: q2ppmv = 1.60771704e+6 ! q_mixratio_to_ppmv
76 ! cf. RTTOV-11 Users Guide Table 2
77 ! index 19 is sentinel3 in Table 2, here we keep it as tiros for
78 ! WRFDA backward compatibility
79 Character (len=8), Parameter :: rttov_platform_name(1:37) = &
80 & (/ 'noaa ', 'dmsp ', 'meteosat', 'goes ', 'gms ', &
81 & 'fy2 ', 'trmm ', 'ers ', 'eos ', 'metop ', &
82 & 'envisat ', 'msg ', 'fy1 ', 'adeos ', 'mtsat ', &
83 & 'coriolis', 'jpss ', 'gifts ', 'tiros ', 'meghatr ', &
84 & 'kalpana ', 'reserved', 'fy3 ', 'coms ', 'meteor-m', &
85 & 'gosat ', 'calipso ', 'reserved', 'gcom-w ', 'nimbus ', &
86 & 'himawari', 'mtg ', 'saral ', 'metop-ng', 'landsat ', &
87 & 'jason ', 'gpm '/)
88 ! cf. RTTOV-11 Users Guide Table 3
89 ! List of instruments !!!! HIRS is number 0
90 CHARACTER(LEN=8), dimension(0:88):: rttov_inst_name = &
91 & (/ 'hirs ', 'msu ', 'ssu ', 'amsua ', 'amsub ', &
92 & 'avhrr ', 'ssmi ', 'vtpr1 ', 'vtpr2 ', 'tmi ', &
93 & 'ssmis ', 'airs ', 'hsb ', 'modis ', 'atsr ', &
94 & 'mhs ', 'iasi ', 'amsre ', 'imager ', 'atms ', &
95 & 'mviri ', 'seviri ', 'imager ', 'sounder ', 'imager ', &
96 & 'vissr ', 'mvisr ', 'cris ', 'cmis ', 'viirs ', &
97 & 'windsat ', 'gifts ', 'ssmt1 ', 'ssmt2 ', 'saphir ', &
98 & 'madras ', 'ssmisz ', 'vhrr ', 'imager ', 'sounder ', &
99 & 'mwts ', 'mwhs ', 'iras ', 'mwri ', 'abi ', &
100 & 'mi ', 'msumr ', 'tansofts', 'iir ', 'mwr ', &
101 & 'dummyir ', 'dummymw ', 'dummyhi ', 'dummypo ', 'scams ', &
102 & 'smmr ', 'ahi ', 'irs ', 'altika ', 'iasing ', &
103 & 'tm ', 'fci ', 'amsr ', 'amsr2 ', 'vissr ', &
104 & 'slstr ', 'tirs ', 'amr ', 'oli ', 'iris ', &
105 & 'ici ', 'gmi ', 'mwts2 ', 'mwhs2 ', 'aster ', &
106 & 'hatpro ', 'mtvzagy ', 'metimage', 'mws ', 'mwi ', &
107 & 'epic ', 'mrir ', 'si ', 'mrfirs ', 'mbfiri ', &
108 & 'lhr ', 'ismar ', 'mersi1 ', 'mersi2 ' /)
110 ! cf. rttov_platform_name above and CRTM: v2.1.3 User Guide Table B.1
111 ! n=noaa; f=dmsp; g=goes; eos-2/1=aqua/terra;
112 ! xxxxxxxx means crtm does not have corresponding coefficient file.
113 ! For satellite names that can not be directly mapped here to names
114 ! used in crtm coeff names, they will be re-set in
115 ! da_crtm_sensor_descriptor.inc
116 Character (len=8), Parameter :: crtm_platform_name(1:37) = &
117 & (/ 'n ', 'f ', 'm ', 'g ', 'gms ', &
118 & 'xxxxxxxx', 'trmm ', 'ers ', 'eos ', 'metop ', &
119 & 'envisat ', 'msg ', 'xxxxxxxx', 'xxxxxxxx', 'mt ', &
120 & 'coriolis', 'npp ', 'gifts ', 'tiros ', 'meghat ', &
121 & 'kalpana ', 'tiros ', 'fy3 ', 'coms ', 'xxxxxxxx', &
122 & 'xxxxxxxx', 'xxxxxxxx', 'reserved', 'gcom-w ', 'xxxxxxxx', &
123 & 'himawari', 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx', &
124 & 'xxxxxxxx', 'gpm '/)
125 ! cf. rttov_inst_name above and CRTM: v2.1.3 User Guide Table B.1
126 ! List of instruments !!!! HIRS is number 0
127 ! xxxxxxxx means crtm does not have corresponding coefficient file.
128 ! For instrument names that can not be directly mapped here to names
129 ! used in crtm coeff names, they will be re-set in
130 ! da_crtm_sensor_descriptor.inc
131 Character (len=8), Dimension(0:88) :: crtm_sensor_name = &
132 & (/ 'hirs ', 'msu ', 'ssu ', 'amsua ', 'amsub ', &
133 & 'avhrr ', 'ssmi ', 'xxxxxxxx', 'spare ', 'tmi ', &
134 & 'ssmis ', 'airs ', 'hsb ', 'modis ', 'atsr ', &
135 & 'mhs ', 'iasi ', 'amsre ', 'imgr ', 'atms ', &
136 & 'mviri ', 'seviri ', 'imgr ', 'sndr ', 'imgr ', &
137 & 'vissr ', 'xxxxxxxx', 'cris ', 'spare ', 'viirs ', &
138 & 'windsat ', 'xxxxxxxx', 'ssmt1 ', 'ssmt2 ', 'saphir ', &
139 & 'madras ', 'spare ', 'imgr ', 'reserved', 'reserved', &
140 & 'mwts ', 'mwhs ', 'iras ', 'mwri ', 'abi ', &
141 & 'xxxxxxxx', 'xxxxxxxx', 'reserved', 'xxxxxxxx', 'xxxxxxxx', &
142 & 'reserved', 'reserved', 'reserved', 'reserved', 'xxxxxxxx', &
143 & 'xxxxxxxx', 'ahi ', 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx', &
144 & 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx', 'amsr2 ', 'vissr ', &
145 & 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx', &
146 & 'xxxxxxxx', 'gmi ', 'xxxxxxxx', 'mwhs2 ', 'xxxxxxxx', &
147 & 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx', &
148 & 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx', &
149 & 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx', 'xxxxxxxx'/)
151 #ifdef RTTOV
152 type (rttov_coefs), allocatable :: coefs(:) ! coefficients structure
153 type (rttov_options), allocatable :: opts(:) ! options structure
154 type (rttov_opts_rt_ir), allocatable :: opts_rt_ir(:) ! options structure
155 type (rttov_emis_atlas_data) :: atlas
156 integer(jpim), allocatable :: atlas_type(:), atlas_id(:)
157 #endif
159 type satinfo_type
160 integer, pointer :: ichan(:) ! channel index
161 integer, pointer :: iuse (:) ! usage flag (-1: not use) from radiance info file
162 real , pointer :: error(:) ! error Standard Deviation from radiance info file
163 real , pointer :: error_cld(:) ! error Standard Deviation for cloudy radiance from radiance info file
164 real , pointer :: polar(:) ! polarisation (0:ver; 1:hori) from radiance info file
165 real , pointer :: error_factor(:) ! error tuning factor ! from error tuning file
166 ! new air mass bias correction coefs.
167 real , pointer :: scanbias(:,:) ! scan bias without latitude band variation
168 real , pointer :: scanbias_b(:,:,:) ! scan bias with latitude band variation
169 real , pointer :: bcoef(:,:) ! airmass predictor bias coefficients
170 real , pointer :: bcoef0(:) ! airmass constant coefficient
171 real , pointer :: error_std(:) ! error standard deviation
172 real , pointer :: BTLim(:) ! for all-sky radiances, "BTLim" for each channel (Harnish et al. 2016)
173 real , pointer :: ca1(:) ! for all-sky radiances, symmetric cloud amount below which we set obs error to clear-sky obs error.
174 real , pointer :: ca2(:) ! for all-sky radiances, symmetric cloud amount above which we set obs error to fully cloudy obs error.
175 real , pointer :: clearSkyBias(:) ! for all-sky radiances, bias correction determined offline based on only clear pixels.
176 end type satinfo_type
178 type (satinfo_type), pointer :: satinfo(:)
180 CHARACTER( 80 ), allocatable, save :: Sensor_Descriptor(:)
182 end module module_radiance