da_define_structures.f90

References to this file elsewhere.
1 module da_define_structures
2 
3    !---------------------------------------------------------------------------
4    ! Purpose: Collection of routines to define and allocate structures.
5    !---------------------------------------------------------------------------
6 
7    use module_domain, only: vp_type, x_type
8 
9    use da_control, only : anal_type_randomcv, stdout, max_fgat_time, &
10       vert_corr, global, vert_evalue,print_detail_be, maxsensor, &
11       max_ob_levels, trace_use, num_ob_indexes, kms, kme, &
12       vert_corr_1, vert_corr_2, vert_evalue_global, &
13       put_rand_seed, seed_array1, seed_array2, missing_r, &
14       sound, synop, pilot, satem, geoamv, polaramv, airep, gpspw, gpsref, &
15       metar, ships, ssmi_rv, ssmi_tb, ssmt1, ssmt2, qscat, profiler, buoy, bogus, &
16       pseudo, radar, radiance, airsr, sonde_sfc, trace_use_dull
17 
18    use da_tracing, only : da_trace_entry, da_trace_exit
19    use da_tools_serial, only : da_array_print
20 
21    use da_reporting, only : da_error, message
22 
23    implicit none
24    
25    !--------------------------------------------------------------------------
26    ! [2.0] Background field structure definition:
27    !--------------------------------------------------------------------------
28 
29    type xbx_type
30       character (len=4):: mminlu
31 
32       integer          :: fft_pad_i          ! Padding to get 2**p 3**q 5**r. (p>=1)
33       integer          :: fft_pad_j          ! Padding to get 2**p 3**q 5**r.
34 
35       integer          :: pad_num            ! Splitted fft_pad_i on this processor.
36       integer          :: pad_inc            ! Pad increment (split over v2y).
37       integer, pointer :: pad_loc(:)         ! pad location on this processor.
38       integer, pointer :: pad_pos(:)         ! pad position beyond ide for this processor.
39 
40       integer          :: fft_ix             ! x-direction FFT number, in 2**p 3**q 5**r.
41       integer          :: fft_jy             ! y-direction FFT number, in 2**p 3**q 5**r.
42 
43       integer, pointer :: fft_factors_x(:)   ! FFT factors in x direction.
44       integer, pointer :: fft_factors_y(:)   ! FFT factors in y direction.
45 
46       real, pointer    :: trig_functs_x(:)   ! Trig functions in x direction.
47       real, pointer    :: trig_functs_y(:)   ! Trig functions in y direction.
48 
49       real             :: psac_mean          ! Mean pressure.
50       real, pointer    :: latc_mean(:)       ! Mean latitude.
51 
52       real, pointer    :: fft_coeffs(:,:)    ! FFT Coefficients
53 
54       real             :: fft_adjoint_factor ! FFT Adjoint factor
55       ! spectral transform related variables
56       integer          :: inc                ! Vector array increment 
57       integer          :: ni
58       integer          :: nj
59       integer          :: nk
60       integer          :: max_wavenumber
61       integer          :: lenr
62       integer          :: lensav
63       integer          :: lenwrk
64       integer          :: alp_size
65       real, pointer       :: wsave(:)          ! Primes for FFT.
66       real, pointer       :: lon(:)            ! Longitude (radians).
67       real, pointer       :: sinlon(:)         ! sine(longitude).
68       real, pointer       :: coslon(:)         ! cosine(longitude).
69       real, pointer       :: lat(:)            ! Latitude (radians, from south).
70       real, pointer       :: sinlat(:)         ! sine(latitude).
71       real, pointer       :: coslat(:)         ! cosine(latitude).
72       real, pointer       :: int_wgts(:)       ! Legendre integration weights.
73       real, pointer       :: alp(:)            ! Associated Legendre Polynomial.
74    end type xbx_type
75 
76    !--------------------------------------------------------------------------
77    ! [3.0] Innovation vector structure definition:
78    !--------------------------------------------------------------------------
79 
80    ! [3.1] Generic sub-structures used in iv_type:
81 
82    type field_type
83       real                   :: inv             ! Innovation vector
84       integer                :: qc              ! Observation QC
85       real                   :: error           ! Observational error
86    end type field_type
87 
88    type model_loc_type
89       type (field_type)       :: slp            ! Pressure in Pa
90       ! type (field_type)       :: psfc           ! Pressure in Pa
91       ! Remove the following in future (needed now for obs i/o only):
92       type (field_type)       :: pw             ! Toatl precipitable water cm
93 
94       real                    :: x
95       real                    :: y
96       integer                 :: i
97       integer                 :: j
98       real                    :: dx
99       real                    :: dxm
100       real                    :: dy
101       real                    :: dym
102       logical                 :: proc_domain
103       ! obs_global_index is the original index of this obs in the serial 
104       ! code.  It is used to reassemble obs in serial-code-order to replicate 
105       ! summation order for bitwise-exact testing of distributed-memory 
106       ! parallel configurations.  
107       integer                 :: obs_global_index
108    end type model_loc_type
109 
110    type each_level_type
111       real                    :: height         ! Height in m
112       integer                 :: height_qc      ! Height QC
113       real                    :: zk             ! k-coordinates
114       type (field_type)       :: u              ! Wind x-component in m/s
115       type (field_type)       :: v              ! Wind y-component in m/s
116       type (field_type)       :: p              ! Pressure in Pa
117       type (field_type)       :: t              ! Temperature in K
118       type (field_type)       :: q              ! Mixing ratio (kg/kg).
119       type (field_type)       :: rh             ! Relative humidity (%).
120       type (field_type)       :: td             ! dew-point in K
121       type (field_type)       :: Speed          ! Wind speed m/s
122    end type each_level_type
123 
124    type radar_each_level_type
125       real                   :: height         ! Height in m
126       integer                :: height_qc      ! Height QC
127       real                   :: zk             ! MM5 k-coordinates
128       type (field_type)      :: rv
129       type (field_type)      :: rf
130    end type radar_each_level_type
131 
132    type info_type
133       character (len = 40)   :: name          ! Station name
134       character (len = 12)   :: platform      ! Instrument platform
135       character (len =  5)   :: id            ! 5 digit station identifer
136       character (len = 19)   :: date_char     ! CCYY-MM-DD_HH:MM:SS date
137       integer                :: levels        ! number of levels
138       real                   :: lat           ! Latitude in degree
139       real                   :: lon           ! Longitude in degree
140       real                   :: elv           ! Elevation in m
141       real                   :: pstar         ! Surface pressure
142    end type info_type
143 
144    type infa_type
145       integer                             :: max_lev
146       integer                             :: nlocal
147       integer                             :: ntotal
148       integer                             :: plocal(0:max_fgat_time)
149       integer                             :: ptotal(0:max_fgat_time)
150       integer                             :: n1
151       integer                             :: n2
152       character (len = 40) , allocatable  :: name(:)       ! Station name
153       character (len = 12), allocatable   :: platform(:)   ! Instrument platform
154       character (len =  5), allocatable   :: id(:)         ! 5 digit station identifer
155       character (len = 19), allocatable   :: date_char(:)  ! CCYY-MM-DD_HH:MM:SS date
156       integer, allocatable                :: levels(:)     ! number of levels
157       real, allocatable                   :: lat(:,:)      ! Latitude in degree
158       real, allocatable                   :: lon(:,:)      ! Longitude in degree
159       real, allocatable                   :: elv(:)        ! Elevation in m
160       real, allocatable                   :: pstar(:)      ! Surface pressure
161       type (field_type), allocatable :: slp(:)         ! Pressure in Pa
162       ! type (field_type)       :: psfc(:)           ! Pressure in Pa
163       ! Remove the following in future (needed now for obs i/o only):
164       type (field_type), allocatable :: pw(:)          ! Total precipitable water cm
165 
166       real, allocatable       :: x  (:,:)
167       real, allocatable       :: y  (:,:)
168       integer, allocatable    :: i  (:,:)
169       integer, allocatable    :: j  (:,:)
170       integer, allocatable    :: k  (:,:)
171       real, allocatable       :: dx (:,:)
172       real, allocatable       :: dxm(:,:)
173       real, allocatable       :: dy (:,:)
174       real, allocatable       :: dym(:,:)
175       real, allocatable       :: dz (:,:)
176       real, allocatable       :: dzm(:,:)
177       real, allocatable       :: zk(:,:)
178       logical, allocatable    :: proc_domain(:,:)
179       ! obs_global_index is the original index of this obs in the serial 
180       ! code.  It is used to reassemble obs in serial-code-order to replicate 
181       ! summation order for bitwise-exact testing of distributed-memory 
182       ! parallel configurations.  
183       integer, allocatable                 :: obs_global_index(:)
184    end type infa_type
185 
186    type stn_loc_type
187       real                    :: lon                  ! radar site loc
188       real                    :: lat                  ! radar site loc
189       real                    :: elv                  ! radar site loc
190       real                    :: x                    ! radar site loc
191       real                    :: y                    ! radar site loc
192       real                    :: zk                   ! radar site loc
193    end type stn_loc_type
194  
195    type radar_type
196       type (stn_loc_type)     :: stn_loc
197 
198       real, pointer           :: model_p(:)
199       real, pointer           :: model_rho(:)
200       real, pointer           :: model_qrn(:)
201       real                    :: model_ps
202 
203       real                  , pointer :: height   (:) ! Height in m
204       integer               , pointer :: height_qc(:) ! Height QC
205 
206       type (field_type)     , pointer :: rv       (:) ! Radial Velocity
207       type (field_type)     , pointer :: rf       (:) ! Reflectivity
208    end type radar_type
209 
210    type multi_level_type
211       type (info_type)                        :: info
212       type (model_loc_type)                   :: loc
213       type (each_level_type)                  :: each(max_ob_levels)
214    end type multi_level_type
215 
216    type radar_stn_type
217       character (len = 5)    :: platform      ! Data type
218       character (len = 12)   :: name          ! Station name
219       character (len = 19)   :: date_char     ! CCYY-MM-DD_HH:MM:SS date
220       integer                :: numobs        ! number of Obs
221       integer                :: levels        ! number of levels
222       real                   :: lat           ! Latitude in degree
223       real                   :: lon           ! Longitude in degree
224       real                   :: elv           ! Elevation in m
225    end type radar_stn_type
226 
227    type radar_multi_level_type
228       type (radar_stn_type)                   :: stn
229       type (info_type)                        :: info
230       type (model_loc_type)                   :: loc
231       type (radar_each_level_type)            :: each(max_ob_levels)
232    end type radar_multi_level_type
233 
234    ! [3.2] Innovation vector structure:
235 
236    type airep_type
237       real                  , pointer :: h        (:) ! Height in m
238       real                  , pointer :: p        (:) ! Height QC
239       type (field_type)     , pointer :: u        (:) ! u-wind.
240       type (field_type)     , pointer :: v        (:) ! v-wind.
241       type (field_type)     , pointer :: t        (:) ! temperature.
242    end type airep_type
243 
244    type pilot_type
245       real                  , pointer :: p        (:) ! Height in m
246       type (field_type)     , pointer :: u        (:) ! u-wind.
247       type (field_type)     , pointer :: v        (:) ! v-wind.
248    end type pilot_type
249 
250    type bogus_type
251       real                  , pointer :: h        (:) ! Height in m
252       real                  , pointer :: p        (:) ! pressure.
253       type (field_type)     , pointer :: u        (:) ! u-wind.
254       type (field_type)     , pointer :: v        (:) ! v-wind.
255       type (field_type)     , pointer :: t        (:) ! temperature.
256       type (field_type)     , pointer :: q        (:) ! q.
257       type (field_type)               :: slp          ! sea level pressure.
258    end type bogus_type
259 
260    type satem_type
261       real                            :: ref_p        ! Reference pressure
262       real                  , pointer :: p        (:) ! Multi-level pressure
263 
264       type (field_type)     , pointer :: thickness(:)     ! Thickness.
265       type (field_type)     , pointer :: org_thickness(:) ! To store original Thickness info.
266    end type satem_type
267 
268    type geoamv_type
269       real                  , pointer :: p        (:) ! Height in Pa
270       type (field_type)     , pointer :: u        (:) ! u-wind.
271       type (field_type)     , pointer :: v        (:) ! v-wind.
272    end type geoamv_type
273 
274    type polaramv_type
275       real                  , pointer :: p        (:) ! Height in Pa
276       type (field_type)     , pointer :: u        (:) ! u-wind.
277       type (field_type)     , pointer :: v        (:) ! v-wind.
278    end type polaramv_type
279 
280    type gpsref_type
281       real             , pointer :: h  (:)      ! Multi-level height
282       type (field_type), pointer :: ref(:)      ! GPS Refractivity
283       type (field_type), pointer :: p  (:)      ! Retrieved P from Ref.
284       type (field_type), pointer :: t  (:)      ! Retrieved T from Ref.
285       type (field_type), pointer :: q  (:)      ! From NCEP analysis.
286    end type gpsref_type
287 
288    type synop_type
289       real                    :: h              ! Height in m
290       type (field_type)       :: u              ! u-wind.
291       type (field_type)       :: v              ! v-wind.
292       type (field_type)       :: t              ! temperature.
293       type (field_type)       :: p              ! pressure.
294       type (field_type)       :: q              ! q.
295    end type synop_type
296 
297    type sound_type
298       real                  , pointer :: h        (:) ! Height in m
299       real                  , pointer :: p        (:) ! pressure.
300 
301       type (field_type)     , pointer :: u        (:) ! u-wind.
302       type (field_type)     , pointer :: v        (:) ! v-wind.
303       type (field_type)     , pointer :: t        (:) ! temperature.
304       type (field_type)     , pointer :: q        (:) ! q.
305    end type sound_type
306 
307    type airsr_type
308       real                  , pointer :: h        (:) ! Height in m
309       real                  , pointer :: p        (:) ! pressure.
310       type (field_type)     , pointer :: t        (:) ! temperature.
311       type (field_type)     , pointer :: q        (:) ! q.
312    end type airsr_type
313 
314    type gpspw_type
315       type (field_type)       :: tpw  ! Toatl precipitable water cm from GPS
316    end type gpspw_type
317 
318    type ssmi_rv_type
319       type (field_type)       :: Speed          ! Wind speed in m/s
320       type (field_type)       :: tpw            ! Toatl precipitable water cm
321    end type ssmi_rv_type
322 
323    type ssmi_tb_type
324 
325       type (field_type)       :: tb19v          ! Brightness T (k) 19V
326       type (field_type)       :: tb19h          ! Brightness T (k) 19H
327       type (field_type)       :: tb22v          ! Brightness T (k) 22V
328       type (field_type)       :: tb37v          ! Brightness T (k) 37V
329       type (field_type)       :: tb37h          ! Brightness T (k) 37H
330       type (field_type)       :: tb85v          ! Brightness T (k) 85V
331       type (field_type)       :: tb85h          ! Brightness T (k) 85H
332    end type ssmi_tb_type
333    
334    type ssmt1_type   
335       real                  , pointer :: h        (:) ! Height in m
336       real                  , pointer :: p        (:) ! Pressure in Pa.
337       type (field_type)     , pointer :: t        (:) ! temperature.
338    end type ssmt1_type
339 
340    type ssmt2_type
341       real                  , pointer :: h        (:) ! Height in m
342       real                  , pointer :: p        (:) ! Pressure in Pa.
343       type (field_type)     , pointer :: rh       (:) ! Relative humidity.
344    end type ssmt2_type
345 
346    type pseudo_type
347       type (field_type)       :: u              ! u-wind.
348       type (field_type)       :: v              ! v-wind.
349       type (field_type)       :: t              ! Temperature.
350       type (field_type)       :: p              ! Pressure.
351       type (field_type)       :: q              ! Specific Humidity.
352    end type pseudo_type
353 
354    type qscat_type
355       real                    :: h              ! Height in m
356       type (field_type)       :: u              ! u-wind.
357       type (field_type)       :: v              ! v-wind.
358    end type qscat_type
359 
360    type instid_type
361       ! Instrument triplet, follow the convension of RTTOV
362       integer              :: platform_id, satellite_id, sensor_id
363       integer              :: rad_monitoring ! 0 (monitor_off): assimilating
364                                              !    (default in Registry.wrfvar),
365                                              ! 1 (monitor_on):  monitoring
366                                              ! monitor_on and monitor_off defined in da_control.f90
367       character(len=20)    :: rttovid_string
368       integer              :: num_rad, nchan, nlevels
369       integer              :: nchannels, nfrequencies,nbtout
370       integer              :: num_rad_glo
371       integer, pointer     :: ssmis_subinst(:)
372       integer, pointer     :: ichan(:)
373       real,    pointer     :: tb_inv(:,:)
374       integer, pointer     :: tb_qc(:,:)
375       real,    pointer     :: tb_error(:,:)
376       real,    pointer     :: tb_xb(:,:) 
377       integer, pointer     :: scanpos(:)
378       integer, pointer     :: scanline(:)
379       integer, pointer     :: cloud_flag(:,:)
380       real,    pointer     :: satzen(:) 
381       real,    pointer     :: satazi(:) 
382       real,    pointer     :: solzen(:) 
383       real,    pointer     :: solazi(:) 
384       real,    pointer     :: t(:,:)
385       real,    pointer     :: q(:,:)
386       real,    pointer     :: mr(:,:)
387       real,    pointer     :: tm(:,:)
388       real,    pointer     :: qm(:,:)
389       real,    pointer     :: qrn(:,:)
390       real,    pointer     :: qcw(:,:)
391       real,    pointer     :: qci(:,:)
392       real,    pointer     :: qsn(:,:)
393       real,    pointer     :: qgr(:,:)
394       real,    pointer     :: qhl(:,:)
395       real,    pointer     :: pm(:,:)
396       real,    pointer     :: rcw(:,:) ! cloud water effectiv radius
397       real,    pointer     :: rci(:,:) ! cloud ice effective radius
398       real,    pointer     :: rrn(:,:) ! rain effective radius
399       real,    pointer     :: rsn(:,:) ! snow effective radius
400       real,    pointer     :: rgr(:,:) ! graupel effective radius
401       real,    pointer     :: rhl(:,:) ! hail effective radius
402       real,    pointer     :: pf(:,:)  ! full level pressure for CRTM
403       real,    pointer     :: emiss(:,:)
404       real,    pointer     :: u10(:)
405       real,    pointer     :: v10(:)
406       real,    pointer     :: t2m(:)
407       real,    pointer     :: q2m(:)
408       real,    pointer     :: mr2m(:)
409       real,    pointer     :: psfc(:)
410       real,    pointer     :: ps(:)
411       real,    pointer     :: ts(:)
412       real,    pointer     :: smois(:)
413       real,    pointer     :: tslb(:)
414       real,    pointer     :: snowh(:)
415       integer, pointer     :: isflg(:)
416       integer, pointer     :: ifgat(:)
417       integer, pointer     :: landsea_mask(:)
418       real,    pointer     :: elevation(:)
419       real,    pointer     :: soiltyp(:)
420       real,    pointer     :: vegtyp(:)
421       real,    pointer     :: vegfra(:)
422       real,    pointer     :: clwp(:)
423       ! real,    pointer     :: ps_jacobian(:,:)
424       ! real,    pointer     :: t_jacobian(:,:,:)
425       ! real,    pointer     :: q_jacobian(:,:,:)
426       real,    pointer     :: water_coverage(:)
427       real,    pointer     :: land_coverage(:)
428       real,    pointer     :: ice_coverage(:)
429       real,    pointer     :: snow_coverage(:)
430 
431       type (infa_type) :: info
432    end type instid_type
433 
434    type iv_type
435       integer :: nstats(num_ob_indexes)
436 
437       integer :: time
438 
439       integer :: num_inst, total_rad_pixel, total_rad_channel
440 
441       real    :: synop_ef_u, synop_ef_v, synop_ef_t, synop_ef_p, synop_ef_q
442       real    :: metar_ef_u, metar_ef_v, metar_ef_t, metar_ef_p, metar_ef_q
443       real    :: ships_ef_u, ships_ef_v, ships_ef_t, ships_ef_p, ships_ef_q
444       real    :: geoamv_ef_u, geoamv_ef_v
445       real    :: polaramv_ef_u, polaramv_ef_v
446       real    :: gpspw_ef_tpw
447       real    :: sound_ef_u, sound_ef_v, sound_ef_t, sound_ef_q
448       real    :: airep_ef_u, airep_ef_v, airep_ef_t
449       real    :: pilot_ef_u, pilot_ef_v
450       real    :: ssmir_ef_speed, ssmir_ef_tpw
451       real    :: satem_ef_thickness, ssmt1_ef_t, ssmt2_ef_rh
452       real    :: gpsref_ef_ref, gpsref_ef_p, gpsref_ef_t, gpsref_ef_q
453       real    :: qscat_ef_u, qscat_ef_v
454       real    :: profiler_ef_u, profiler_ef_v
455       real    :: buoy_ef_u, buoy_ef_v, buoy_ef_t, buoy_ef_p, buoy_ef_q
456       real    :: radar_ef_rv, radar_ef_rf
457       real    :: bogus_ef_u, bogus_ef_v, bogus_ef_t, bogus_ef_p, bogus_ef_q, bogus_ef_slp
458       real    :: airsr_ef_t,  airsr_ef_q
459 
460       type (infa_type) :: info(num_ob_indexes)
461 
462       type (airsr_type)    , pointer :: airsr(:)
463       type (sound_type)    , pointer :: sound(:)
464       type (synop_type)    , pointer :: sonde_sfc(:)
465       type (airep_type)    , pointer :: airep(:)
466       type (pilot_type)    , pointer :: pilot(:)
467       type (satem_type)    , pointer :: satem(:)
468       type (geoamv_type)   , pointer :: geoamv(:)
469       type (polaramv_type) , pointer :: polaramv(:)
470       type (synop_type)    , pointer :: synop(:)
471       type (synop_type)    , pointer :: metar(:)
472       type (synop_type)    , pointer :: ships(:)
473       type (gpspw_type)    , pointer :: gpspw(:)
474       type (gpsref_type)   , pointer :: gpsref(:)
475       type (ssmi_tb_type)  , pointer :: ssmi_tb(:)
476       type (ssmi_rv_type)  , pointer :: ssmi_rv(:)
477       type (ssmt1_type)    , pointer :: ssmt1(:)
478       type (ssmt2_type)    , pointer :: ssmt2(:)
479       type (pseudo_type)   , pointer :: pseudo(:)
480       type (qscat_type)    , pointer :: qscat(:)
481       type (synop_type)    , pointer :: buoy(:)
482       type (pilot_type)    , pointer :: profiler(:)
483       type (bogus_type)    , pointer :: bogus(:)
484       type (radar_type)    , pointer :: radar(:)
485       type (instid_type)   , pointer :: instid(:)
486 
487       real :: missing
488       real :: ptop
489    end type iv_type
490 
491    type number_type
492       integer                    :: bad
493       integer                    :: miss
494       integer                    :: use
495    end type number_type
496 
497    type bad_info_type
498       type (number_type)         :: num
499       integer                    :: nn(100000)
500       integer                    :: kk(100000)
501    end type bad_info_type
502 
503    type bad_data_type
504       type (bad_info_type)       :: u
505       type (bad_info_type)       :: v
506       type (bad_info_type)       :: t
507       type (bad_info_type)       :: p
508       type (bad_info_type)       :: q
509       type (bad_info_type)       :: tpw
510       type (bad_info_type)       :: Speed
511       type (bad_info_type)       :: gpsref
512       type (bad_info_type)       :: thickness
513       type (bad_info_type)       :: rh
514       type (bad_info_type)       :: rv
515       type (bad_info_type)       :: rf
516       type (bad_info_type)       :: slp
517       type (bad_info_type)       :: rad
518    end type bad_data_type
519 
520    type count_obs_number_type
521       integer                                 :: num_used
522       integer                                 :: num_outside_iyjx
523       integer                                 :: num_max_err_chk
524       integer                                 :: num_missing
525    end type count_obs_number_type
526 
527    !--------------------------------------------------------------------------
528    ! [3.0] Observation/residual structure definition:
529    !--------------------------------------------------------------------------
530 
531    type residual_synop_type
532       real :: u                                 ! u-wind.
533       real :: v                                 ! v-wind.
534       real :: t                                 ! temperature.
535       real :: p                                 ! pressure.
536       real :: q                                 ! q.
537    end type residual_synop_type
538 
539    type residual_qscat_type
540       real :: u                                 ! u-wind.
541       real :: v                                 ! v-wind.
542    end type residual_qscat_type
543 
544    type residual_geoamv_type
545       real, pointer :: u(:)                     ! u-wind.
546       real, pointer :: v(:)                     ! v-wind.
547    end type residual_geoamv_type
548 
549    type residual_polaramv_type
550       real, pointer :: u(:)                     ! u-wind.
551       real, pointer :: v(:)                     ! v-wind.
552    end type residual_polaramv_type
553 
554    type residual_gpspw_type
555       real :: tpw                               ! Total precipitable water.
556    end type residual_gpspw_type
557 
558    type residual_sound_type
559       real, pointer :: u(:)                     ! u-wind.
560       real, pointer :: v(:)                     ! v-wind.
561       real, pointer :: t(:)                     ! temperature.
562       real, pointer :: q(:)                     ! specific humidity.
563    end type residual_sound_type
564 
565    type residual_airsr_type
566       real, pointer :: t(:)                     ! temperature.
567       real, pointer :: q(:)                     ! specific humidity.
568    end type residual_airsr_type
569 
570    type residual_airep_type
571       real, pointer :: u(:)                     ! u-wind.
572       real, pointer :: v(:)                     ! v-wind.
573       real, pointer :: t(:)                     ! temperature.
574    end type residual_airep_type
575 
576    type residual_pilot_type
577       real, pointer :: u(:)                     ! u-wind.
578       real, pointer :: v(:)                     ! v-wind.
579    end type residual_pilot_type
580 
581    type residual_bogus_type
582       real, pointer :: u(:)                     ! u-wind.
583       real, pointer :: v(:)                     ! v-wind.
584       real, pointer :: t(:)                     ! temperature.
585       real, pointer :: q(:)                     ! specific humidity.
586       real          :: slp                      ! sea-level pressure.
587    end type residual_bogus_type
588 
589    type residual_satem_type
590       real, pointer :: thickness(:)             ! Thickness.
591    end type residual_satem_type
592 
593    type residual_gpsref_type
594       real, pointer :: ref(:)         ! GPS Refractivity
595       real, pointer :: p  (:)         ! GPS Retrived p from Refractivity
596       real, pointer :: t  (:)         ! GPS Retrived t from Refractivity
597       real, pointer :: q  (:)         ! q from NCEP used by CDAAC in retrieval
598    end type residual_gpsref_type
599 
600    type residual_ssmi_rv_type
601       real                    :: tpw      ! Toatl precipitable water cm
602       real                    :: Speed    ! Wind speed m/s
603    end type residual_ssmi_rv_type
604 
605    type residual_ssmi_tb_type
606       real                    :: tb19v          ! Brightness T (k) 19V
607       real                    :: tb19h          ! Brightness T (k) 19H
608       real                    :: tb22v          ! Brightness T (k) 22V
609       real                    :: tb37v          ! Brightness T (k) 37V
610       real                    :: tb37h          ! Brightness T (k) 37H
611       real                    :: tb85v          ! Brightness T (k) 85V
612       real                    :: tb85h          ! Brightness T (k) 85H
613    end type residual_ssmi_tb_type
614    
615    type residual_ssmt1_type
616       real, pointer :: t(:)                       ! temperature.
617    end type residual_ssmt1_type
618    
619    type residual_ssmt2_type
620       real, pointer :: rh(:)                      ! Relative Humidity.
621    end type residual_ssmt2_type
622 
623    type residual_pseudo_type
624       real :: u                                   ! u-wind.
625       real :: v                                   ! v-wind.
626       real :: t                                   ! temperature.
627       real :: p                                   ! pressure.
628       real :: q                                   ! specific humidity.
629    end type residual_pseudo_type
630 
631    type residual_radar_type
632       real, pointer :: rv(:)                    ! rv
633       real, pointer :: rf(:)                    ! rf
634    end type residual_radar_type
635 
636    type residual_instid_type
637       integer                          :: num_rad
638       integer                          :: nchan
639       integer, pointer                 :: ichan (:)
640       real, pointer                    :: tb(:,:)
641    end type residual_instid_type
642 
643    type y_type
644       integer :: nlocal(num_ob_indexes)
645       integer :: ntotal(num_ob_indexes)
646 
647       integer :: num_inst
648 
649       type (residual_synop_type),    pointer :: synop(:)
650       type (residual_synop_type),    pointer :: metar(:) ! Same as synop type
651       type (residual_synop_type),    pointer :: ships(:) ! Same as synop type
652       type (residual_geoamv_type),   pointer :: geoamv(:)
653       type (residual_polaramv_type), pointer :: polaramv(:)
654       type (residual_gpspw_type),    pointer :: gpspw (:)
655       type (residual_gpsref_type),   pointer :: gpsref(:)
656       type (residual_sound_type),    pointer :: sound(:)
657       type (residual_airsr_type),    pointer :: airsr(:)
658       type (residual_bogus_type),    pointer :: bogus(:)
659       type (residual_synop_type),    pointer :: sonde_sfc(:) ! Same as synop type
660       type (residual_airep_type),    pointer :: airep(:)
661       type (residual_pilot_type),    pointer :: pilot(:)
662       type (residual_satem_type),    pointer :: satem(:)
663       type (residual_ssmi_tb_type),  pointer :: ssmi_tb(:)
664       type (residual_ssmi_rv_type),  pointer :: ssmi_rv(:)
665       type (residual_ssmt1_type),    pointer :: ssmt1(:)
666       type (residual_ssmt2_type),    pointer :: ssmt2(:)
667       type (residual_pseudo_type),   pointer :: pseudo(:)
668       type (residual_qscat_type),    pointer :: qscat(:)
669       type (residual_synop_type),    pointer :: buoy(:) ! Same as synop type
670       type (residual_pilot_type),    pointer :: profiler(:) ! Same as pilot type
671       type (residual_radar_type),    pointer :: radar(:)
672       type (residual_instid_type),   pointer :: instid(:)
673    end type y_type
674 
675    !--------------------------------------------------------------------------
676    ! [4.0] Control variable structure:
677    !--------------------------------------------------------------------------
678 
679    ! Max/Min type:
680 
681    type maxmin_type
682       real                       :: value
683       integer                    :: n, l
684    end type maxmin_type
685 
686    !--------------------------------------------------------------------------
687    ! [5.0] Control variable structure:
688    !--------------------------------------------------------------------------
689    
690    type jo_type_rad
691       integer, pointer :: num_ichan(:)
692       real, pointer    :: jo_ichan(:)
693    end type jo_type_rad
694 
695    type jo_type
696       real                :: total
697       real                :: synop_u, synop_v, synop_t, synop_p, synop_q
698       real                :: metar_u, metar_v, metar_t, metar_p, metar_q
699       real                :: ships_u, ships_v, ships_t, ships_p, ships_q
700       real                :: geoamv_u, geoamv_v
701       real                :: polaramv_u, polaramv_v
702       real                :: gpspw_tpw, satem_thickness, gpsref_ref
703       real                :: sound_u, sound_v, sound_t, sound_q
704       real                :: sonde_sfc_u, sonde_sfc_v, sonde_sfc_t, &
705                              sonde_sfc_p, sonde_sfc_q
706       real                :: airep_u, airep_v, airep_t
707       real                :: pilot_u, pilot_v
708       real                :: ssmir_speed, ssmir_tpw
709       real                :: ssmi_tb19v, ssmi_tb19h, ssmi_tb22v, ssmi_tb37v, &
710                              ssmi_tb37h, ssmi_tb85v, ssmi_tb85h
711       real                :: ssmt1_t, ssmt2_rh
712       real                :: pseudo_u, pseudo_v, pseudo_t, pseudo_p, pseudo_q
713       real                :: qscat_u, qscat_v
714       real                :: profiler_u, profiler_v
715       real                :: buoy_u, buoy_v, buoy_t, buoy_p, buoy_q
716       real                :: radar_rv, radar_rf
717       real                :: bogus_u, bogus_v, bogus_t, bogus_q, bogus_slp
718       real                :: airsr_t, airsr_q
719       type(jo_type_rad), pointer       :: rad(:)
720    end type jo_type
721 
722    type j_type
723       real             :: total
724       real             :: jb
725       real             :: jc
726       real             :: je
727       type (jo_type)   :: jo
728    end type j_type
729 
730    type cv_type
731       integer :: size        ! Total size of control variable.
732       integer :: size_jb     ! Size of CV array for Jb term.
733       integer :: size_je     ! Size of CV array for Je term.
734       integer :: size1c      ! Complex size of CV array of 1st variable error.
735       integer :: size2c      ! Complex size of CV array of 2nd variable error.
736       integer :: size3c      ! Complex size of CV array of 3rd variable error.
737       integer :: size4c      ! Complex size of CV array of 4th variable error.
738       integer :: size5c      ! Complex size of CV array of 5th variable error.
739       integer :: size_alphac ! Size of alpha control variable (complex).
740       integer :: size1       ! Size of CV array of 1st variable error.
741       integer :: size2       ! Size of CV array of 2nd variable error.
742       integer :: size3       ! Size of CV array of 3rd variable error.
743       integer :: size4       ! Size of CV array of 4th variable error.
744       integer :: size5       ! Size of CV array of 5th variable error.
745    end type cv_type
746 
747    type be_subtype
748       integer           :: mz          ! Vertical truncation of errors.
749       integer           :: max_wave    ! Global only - horizontal spectral truncation.
750       character*5       :: name        ! Variable name.
751       real, pointer     :: rf_alpha(:) ! RF scale length.
752       real, pointer     :: val(:,:)    ! Local Standard dev./sqrt(eigenvalue).
753       real, pointer     :: evec(:,:,:) ! Local Vertical eigenvectors.
754       real, pointer     :: val_g(:)    ! Global Standard dev./sqrt(eigenvalue).
755       real, pointer     :: evec_g(:,:) ! Global Vertical eigenvectors.
756       real, pointer     :: power(:,:)  ! Power spectrum
757    end type be_subtype
758 
759    type be_type
760       integer           :: ne
761       integer           :: max_wave           ! Smallest spectral mode (global).
762       integer           :: mix
763       integer           :: mjy
764       type (be_subtype) :: v1
765       type (be_subtype) :: v2
766       type (be_subtype) :: v3
767       type (be_subtype) :: v4
768       type (be_subtype) :: v5
769       type (be_subtype) :: alpha
770       real, pointer     :: pb_vert_reg(:,:,:)
771 
772       ! Control variable space errors:
773       type (cv_type)    :: cv
774 
775       real, pointer     :: reg_chi(:,:)
776       real, pointer     :: reg_t  (:,:,:)
777       real, pointer     :: reg_ps (:,:)
778    end type be_type
779 
780    ! Analysis_Stats maximum-minumum structure.
781 
782    type maxmin_field_type
783       real                         :: value
784       integer                      :: i, j
785    end type maxmin_field_type
786 
787    ! vp_type is defined in the Registry
788    ! x_type  is defined in the Registry
789    ! The framework allocates the (local-grid) xa structure.
790    ! The framework allocates the (local-grid) xb structure.
791    ! The framework (de)allocates the vv structure.
792    ! The framework (de)allocates the vp structure.
793 
794 contains
795 
796 #include "da_allocate_background_errors.inc"
797 #include "da_allocate_observations.inc"
798 #include "da_allocate_y.inc"
799 #include "da_deallocate_background_errors.inc"
800 #include "da_deallocate_observations.inc"
801 #include "da_deallocate_y.inc"
802 #include "da_zero_x.inc"
803 #include "da_zero_vp_type.inc"
804 #include "da_initialize_cv.inc"
805 #include "da_random_seed.inc"
806 #include "da_gauss_noise.inc"
807 
808 end module da_define_structures
809