da_define_structures.f90

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