3 use da_control
, only
: obs_qc_pointer
,max_ob_levels
,missing_r
, missing_data
, &
4 check_max_iv_print
, check_max_iv_unit
, v_interp_p
, v_interp_h
, &
5 check_max_iv
, missing
, max_error_uv
, max_error_t
, rootproc
, &
6 max_error_p
,max_error_q
, sfc_assi_options
, no_buddies
, fails_error_max
, &
7 fails_buddy_check
, check_buddy
, check_buddy_print
, check_buddy_unit
, &
8 buddy_weight
, max_buddy_uv
, max_buddy_t
, max_buddy_p
, max_buddy_rh
, &
9 max_stheight_diff
,test_dm_exact
, anal_type_verify
, &
10 kms
,kme
,kts
,kte
,sfc_assi_options_1
,sfc_assi_options_2
, num_procs
, comm
, &
11 trace_use_dull
, sound
, sonde_sfc
, position_lev_dependant
, max_ext_its
,qcstat_conv_unit
,ob_vars
, &
12 convert_fd2uv
,convert_uv2fd
,max_error_spd
,max_error_dir
,max_omb_spd
,max_omb_dir
,pi
,qc_rej_both
, &
13 wind_sd_sound
, wind_stats_sd
, write_rej_obs_conv
14 use da_grid_definitions
, only
: da_ffdduv
,da_ffdduv_model
, da_ffdduv_diagnose
17 ! use mpi, only : mpi_integer, mpi_real8, mpi_max
19 use da_define_structures
, only
: maxmin_type
, iv_type
, y_type
, jo_type
, &
20 bad_data_type
, x_type
, number_type
, bad_data_type
21 use module_domain
, only
: domain
22 use da_interpolation
, only
: da_to_zk
, da_interp_lin_3d
, &
23 da_interp_lin_3d_adj
, da_interp_lin_2d
, da_interp_lin_2d_adj
, da_interp_lin_2d_partial
24 use da_statistics
, only
: da_stats_calculate
25 use da_tools
, only
: da_max_error_qc
, da_residual
, da_obs_sfc_correction
, da_convert_zk
,&
26 da_buddy_qc
, da_get_print_lvl
27 use da_par_util
, only
: da_proc_stats_combine
, &
28 da_deallocate_global_sound
, da_to_global_sound
, da_to_global_sonde_sfc
, &
29 da_deallocate_global_sonde_sfc
30 use da_par_util1
, only
: da_proc_sum_int
31 use da_physics
, only
: da_sfc_pre
, da_transform_xtopsfc
, &
32 da_transform_xtopsfc_adj
, da_uv_to_sd_lin
, da_uv_to_sd_adj
33 use da_tracing
, only
: da_trace_entry
, da_trace_exit
35 ! The "stats_sound_type" is ONLY used locally in da_sound:
37 type residual_sound1_type
40 real :: t
! temperature
41 real :: q
! specific humidity
42 end type residual_sound1_type
44 type maxmin_sound_stats_type
45 type (maxmin_type
) :: u
, v
, t
, q
46 end type maxmin_sound_stats_type
49 type (maxmin_sound_stats_type
) :: maximum
, minimum
50 type (residual_sound1_type
) :: average
, rms_err
51 end type stats_sound_type
53 ! The "stats_sonde_sfc_type" is ONLY used locally in da_sonde_sfc:
55 type residual_sonde_sfc1_type
58 real :: t
! temperature
60 real :: q
! specific humidity
61 end type residual_sonde_sfc1_type
63 type maxmin_sonde_sfc_stats_type
64 type (maxmin_type
) :: u
, v
, t
, p
, q
65 end type maxmin_sonde_sfc_stats_type
67 type stats_sonde_sfc_type
68 type (maxmin_sonde_sfc_stats_type
) :: maximum
, minimum
69 type (residual_sonde_sfc1_type
) :: average
, rms_err
70 end type stats_sonde_sfc_type
78 #
include "da_ao_stats_sound.inc"
79 #
include "da_jo_and_grady_sound.inc"
80 #
include "da_jo_sound_uvtq.inc"
81 #
include "da_residual_sound.inc"
82 #
include "da_oi_stats_sound.inc"
83 #
include "da_print_stats_sound.inc"
84 #
include "da_transform_xtoy_sound.inc"
85 #
include "da_transform_xtoy_sound_adj.inc"
86 #
include "da_check_max_iv_sound.inc"
87 #
include "da_get_innov_vector_sound.inc"
88 #
include "da_calculate_grady_sound.inc"
89 #
include "da_check_buddy_sound.inc"
91 #
include "da_ao_stats_sonde_sfc.inc"
92 #
include "da_jo_and_grady_sonde_sfc.inc"
93 #
include "da_jo_sonde_sfc_uvtq.inc"
94 #
include "da_residual_sonde_sfc.inc"
95 #
include "da_oi_stats_sonde_sfc.inc"
96 #
include "da_print_stats_sonde_sfc.inc"
97 #
include "da_transform_xtoy_sonde_sfc.inc"
98 #
include "da_transform_xtoy_sonde_sfc_adj.inc"
99 #
include "da_get_innov_vector_sonde_sfc.inc"
100 #
include "da_check_max_iv_sonde_sfc.inc"
101 #
include "da_calculate_grady_sonde_sfc.inc"