Merge remote-tracking branch 'origin/release-v4.6.1'
[WRF.git] / var / da / da_radiance / da_crtm.f90
blobdd1a538842ef910fada8e308e15181e3d30b803d
1 module da_crtm
3 !---------------------------------------------------------------------------
4 ! Purpose: module for CRTM radiance data assimilation.
5 !---------------------------------------------------------------------------
7 #ifdef CRTM
9 use module_domain, only : x_type, domain
10 use da_define_structures, only : y_type, iv_type
12 use module_radiance, only : CRTM_RTSolution_type,CRTM_ChannelInfo_type, &
13 CRTM_Atmosphere_type, CRTM_Surface_type,CRTM_Geometry_type, &
14 CRTM_Adjoint,CRTM_Forward,CRTM_Tangent_Linear, &
15 CRTM_K_Matrix, CRTM_Planck_Temperature, CRTM_Planck_Temperature_TL, &
16 CRTM_Planck_Temperature_AD, CRTM_Planck_Radiance, &
17 CRTM_Atmosphere_Create,H2O_ID,GRAUPEL_CLOUD,ICE_CLOUD,HAIL_CLOUD, &
18 rain_cloud,snow_cloud,O3_ID, &
19 WATER_CLOUD, Sensor_Descriptor, MASS_MIXING_RATIO_UNITS, VOLUME_MIXING_RATIO_UNITS, &
20 crtm_atmosphere_destroy, crtm_sensor_name, &
21 crtm_surface_create,crtm_surface_destroy, &
22 crtm_surface_zero, CRTM_Atmosphere_zero, satinfo, &
23 crtm_platform_name, crtm_init, &
24 rttov_inst_name,rttov_platform_name, climatology_model_name, &
25 crtm_options_type, crtm_options_create, crtm_options_destroy, &
26 crtm_atmosphere_associated, crtm_surface_associated, &
27 crtm_options_associated, &
28 crtm_rtsolution_create, crtm_rtsolution_destroy, crtm_rtsolution_associated, &
29 crtm_irlandcoeff_classification
31 use da_control, only : trace_use, crtm_cloud, gravity,stdout, biascorr, &
32 biasprep, qc_rad,missing_r,rtminit_sensor,rtminit_nsensor, filename_len, &
33 use_error_factor_rad,read_biascoef, analysis_date,time_window_max, &
34 time_window_min,num_fgat_time,rtminit_platform, print_detail_rad, &
35 rtminit_satid, global,kms,kme,ims,ime,jms,jme,kts,kte,use_clddet, use_clddet_zz,&
36 use_crtm_kmatrix, use_varbc, freeze_varbc, use_pseudo_rad, &
37 use_antcorr, time_slots, use_satcv, use_simulated_rad, simulated_rad_io, &
38 simulated_rad_ngrid, interp_option, use_mspps_emis, use_mspps_ts, calc_weightfunc, &
39 its,ite,jts,jte, &
40 crtm_coef_path, crtm_irwater_coef, crtm_mwwater_coef, crtm_irland_coef, crtm_visland_coef, &
41 cloud_cv_options
42 use da_interpolation, only : da_interp_lin_2d_partial,da_interp_lin_2d_adj_partial, &
43 da_interp_2d_partial
44 use da_physics, only: da_trop_wmo
45 use module_dm, only : wrf_dm_sum_real, wrf_dm_sum_reals
46 use da_radiance1, only : da_biasprep,da_detsurtyp,da_biascorr, &
47 da_biasprep,da_cld_eff_radius, da_mspps_emis, da_mspps_ts
49 use da_reporting, only : da_error, message, da_warning, da_message
50 use da_tools_serial, only : da_free_unit, da_get_unit
51 use da_tools, only: da_get_time_slots, da_eof_decomposition
52 use da_tracing, only : da_trace_entry, da_trace_exit
54 TYPE (CRTM_ChannelInfo_type), allocatable, save :: ChannelInfo(:)
56 ! parameters for mapping land surface types for CRTM classification schemes
57 ! land_type applicable for IR and VIS sensors
58 ! vegetation_type and soil_type applicable for Microwave sensors
59 integer, parameter :: n_soil_type = 16 ! wrf num_soil_cat
60 integer, parameter :: USGS_n_type = 24
61 integer, parameter :: IGBP_n_type = 20
62 ! mapping to CRTM land surface subtypes for microwave sensors
63 ! soil type mapping for GFS classification scheme
64 ! REL-2.1.3.CRTM_User_Guide.pdf table 4.15
65 integer, parameter :: wrf_to_crtm_soil(n_soil_type) = &
66 (/ 1, 1, 4, 2, 2, 8, 7, 2, 6, 5, 2, 3, 8, 1, 6, 9 /)
67 ! vegetation type mapping for GFS classification scheme
68 ! REL-2.1.3.CRTM_User_Guide.pdf table 4.16
69 integer, parameter :: usgs_to_crtm_mw(USGS_n_type) = &
70 (/ 7, 12, 12, 12, 12, 12, 7, 9, 8, 6, &
71 2, 5, 1, 4, 3, 0, 8, 8, 11, 10, &
72 10, 10, 11, 13 /)
73 integer, parameter :: igbp_to_crtm_mw(IGBP_n_type) = &
74 (/ 4, 1, 5, 2, 3, 8, 9, 6, 6, 7, &
75 8, 12, 7, 12, 13, 11, 0, 10, 10, 11 /)
77 contains
79 #include "da_transform_xtoy_crtm.inc"
80 #include "da_transform_xtoy_crtm_adj.inc"
81 #include "da_get_innov_vector_crtm.inc"
82 #include "da_crtm_tl.inc"
83 #include "da_crtm_k.inc"
84 #include "da_crtm_direct.inc"
85 #include "da_crtm_ad.inc"
86 #include "da_crtm_init.inc"
87 #include "da_crtm_sensor_descriptor.inc"
88 #include "da_det_crtm_climat.inc"
90 #endif
92 end module da_crtm