Merge remote-tracking branch 'origin/release-v4.5.2'
[WRF.git] / var / da / da_define_structures / da_define_structures.f90
blob7d3249e4c007b1bd1696e80e02547fbc03767598
1 module da_define_structures
3 !---------------------------------------------------------------------------
4 ! Purpose: Collection of routines to define and allocate structures.
5 ! Update: Multivariate BE option (cv_options=6)
6 ! Syed RH Rizvi (MMM/NESL/NCAR) Date: 02/01/2010
8 ! Note: Please acknowledge author/institute in work that uses this code.
9 !---------------------------------------------------------------------------
11 #if (WRF_CHEM != 1)
12 use module_domain, only: vp_type, x_type
13 #else
14 use module_domain, only: vp_type, x_type, xchem_type
15 #endif
17 use da_control, only : anal_type_randomcv, stdout, max_fgat_time, &
18 vert_corr, global, vert_evalue,print_detail_be, maxsensor, &
19 max_ob_levels, trace_use, num_ob_indexes, kms, kme, kde, &
20 vert_corr_1, vert_corr_2, vert_evalue_global, cv_options, do_normalize, use_rf, &
21 put_rand_seed, seed_array1, seed_array2, missing_r, &
22 sound, synop, pilot, satem, geoamv, polaramv, airep, gpspw, gpsref, gpseph, &
23 metar, ships, ssmi_rv, ssmi_tb, ssmt1, ssmt2, qscat, profiler, buoy, bogus, &
24 mtgirs, tamdar, tamdar_sfc, pseudo, radar, radiance, airsr, sonde_sfc, rain, &
25 #if (WRF_CHEM == 1)
26 chemic_surf, chem_cv_options, &
27 #endif
28 trace_use_dull,comm, num_pseudo
29 use da_control, only : cloud_cv_options, use_cv_w
30 use da_control, only : pseudo_uvtpq
31 use da_control, only : use_radar_rhv, use_radar_rqv
33 #if (WRF_CHEM == 1)
34 use module_state_description, only : PARAM_FIRST_SCALAR, num_chem, num_chemic_surf
35 #endif
37 use da_tracing, only : da_trace_entry, da_trace_exit
38 use da_tools_serial, only : da_array_print
40 use da_reporting, only : da_error, da_warning, da_message, message
41 use da_wavelet, only : nij,ws
43 implicit none
45 !--------------------------------------------------------------------------
46 ! [2.0] Background field structure definition:
47 !--------------------------------------------------------------------------
49 type xbx_type
50 character (len=256) :: mminlu
52 integer :: fft_pad_i ! Padding to get 2**p 3**q 5**r. (p>=1)
53 integer :: fft_pad_j ! Padding to get 2**p 3**q 5**r.
55 integer :: pad_num ! Splitted fft_pad_i on this processor.
56 integer :: pad_inc ! Pad increment (split over v2y).
57 integer, pointer :: pad_loc(:) ! pad location on this processor.
58 integer, pointer :: pad_pos(:) ! pad position beyond ide for this processor.
60 integer :: fft_ix ! x-direction FFT number, in 2**p 3**q 5**r.
61 integer :: fft_jy ! y-direction FFT number, in 2**p 3**q 5**r.
63 integer, pointer :: fft_factors_x(:) ! FFT factors in x direction.
64 integer, pointer :: fft_factors_y(:) ! FFT factors in y direction.
66 real, pointer :: trig_functs_x(:) ! Trig functions in x direction.
67 real, pointer :: trig_functs_y(:) ! Trig functions in y direction.
69 real :: psac_mean ! Mean pressure.
70 real, pointer :: latc_mean(:) ! Mean latitude.
72 real, pointer :: fft_coeffs(:,:) ! FFT Coefficients
74 real :: fft_adjoint_factor ! FFT Adjoint factor
75 ! spectral transform related variables
76 integer :: inc ! Vector array increment
77 integer :: ni
78 integer :: nj
79 integer :: nk
80 integer :: max_wavenumber
81 integer :: lenr
82 integer :: lensav
83 integer :: lenwrk
84 integer :: alp_size
85 real, pointer :: wsave(:) ! Primes for FFT.
86 real, pointer :: lon(:) ! Longitude (radians).
87 real, pointer :: sinlon(:) ! sine(longitude).
88 real, pointer :: coslon(:) ! cosine(longitude).
89 real, pointer :: lat(:) ! Latitude (radians, from south).
90 real, pointer :: sinlat(:) ! sine(latitude).
91 real, pointer :: coslat(:) ! cosine(latitude).
92 real, pointer :: int_wgts(:) ! Legendre integration weights.
93 real, pointer :: alp(:) ! Associated Legendre Polynomial.
94 end type xbx_type
96 !--------------------------------------------------------------------------
97 ! [3.0] Innovation vector structure definition:
98 !--------------------------------------------------------------------------
100 ! [3.1] Generic sub-structures used in iv_type:
102 type field_type
103 real :: inv ! Innovation vector
104 integer :: qc ! Observation QC
105 real :: error ! Observational error
106 real :: sens ! Sensitivity vector
107 real :: imp ! Impact vector
108 end type field_type
110 type model_loc_type
111 type (field_type) :: slp ! Pressure in Pa
112 ! type (field_type) :: psfc ! Pressure in Pa
113 ! Remove the following in future (needed now for obs i/o only):
114 type (field_type) :: pw ! Toatl precipitable water cm
116 real :: x
117 real :: y
118 integer :: i
119 integer :: j
120 real :: dx
121 real :: dxm
122 real :: dy
123 real :: dym
124 logical :: proc_domain
125 ! obs_global_index is the original index of this obs in the serial
126 ! code. It is used to reassemble obs in serial-code-order to replicate
127 ! summation order for bitwise-exact testing of distributed-memory
128 ! parallel configurations.
129 integer :: obs_global_index
130 end type model_loc_type
132 type each_level_type
133 real :: height ! Height in m
134 integer :: height_qc ! Height QC
135 real :: zk ! k-coordinates
136 type (field_type) :: u ! Wind x-component in m/s
137 type (field_type) :: v ! Wind y-component in m/s
138 type (field_type) :: p ! Pressure in Pa
139 type (field_type) :: t ! Temperature in K
140 type (field_type) :: q ! Mixing ratio (kg/kg).
141 type (field_type) :: rh ! Relative humidity (%).
142 type (field_type) :: td ! dew-point in K
143 type (field_type) :: Speed ! Wind speed m/s
144 end type each_level_type
146 type radar_each_level_type
147 real :: height ! Height in m
148 integer :: height_qc ! Height QC
149 real :: zk ! MM5 k-coordinates
150 type (field_type) :: rv
151 type (field_type) :: rf
152 end type radar_each_level_type
154 type info_type
155 character (len = 40) :: name ! Station name
156 character (len = 12) :: platform ! Instrument platform
157 character (len = 40) :: id ! 5 digit station identifer
158 character (len = 19) :: date_char ! CCYY-MM-DD_HH:MM:SS date
159 integer :: levels ! number of levels
160 real :: lat ! Latitude in degree
161 real :: lon ! Longitude in degree
162 real :: elv ! Elevation in m
163 real :: pstar ! Surface pressure
164 real :: dhr ! obs time minus analysis time in hour
165 end type info_type
167 type infa_type
168 integer :: max_lev
169 integer :: nlocal
170 integer :: ntotal
171 integer :: thin_nlocal
172 integer :: thin_ntotal
173 integer :: plocal(0:max_fgat_time)
174 integer :: ptotal(0:max_fgat_time)
175 integer :: thin_plocal(0:max_fgat_time)
176 integer :: thin_ptotal(0:max_fgat_time)
177 integer :: n1
178 integer :: n2
179 character (len = 40) , allocatable :: name(:) ! Station name
180 character (len = 12), allocatable :: platform(:) ! Instrument platform
181 character (len = 40), allocatable :: id(:) ! 5 digit station identifer
182 character (len = 19), allocatable :: date_char(:) ! CCYY-MM-DD_HH:MM:SS date
183 integer, allocatable :: levels(:) ! number of levels
184 real, allocatable :: lat(:,:) ! Latitude in degree
185 real, allocatable :: lon(:,:) ! Longitude in degree
186 real, allocatable :: elv(:) ! Elevation in m
187 real, allocatable :: pstar(:) ! Surface pressure
188 type (field_type), allocatable :: slp(:) ! Pressure in Pa
189 ! type (field_type) :: psfc(:) ! Pressure in Pa
190 ! Remove the following in future (needed now for obs i/o only):
191 type (field_type), allocatable :: pw(:) ! Total precipitable water cm
193 real, allocatable :: x (:,:)
194 real, allocatable :: y (:,:)
195 integer, allocatable :: i (:,:)
196 integer, allocatable :: j (:,:)
197 integer, allocatable :: k (:,:)
198 real, allocatable :: dx (:,:)
199 real, allocatable :: dxm(:,:)
200 real, allocatable :: dy (:,:)
201 real, allocatable :: dym(:,:)
202 real, allocatable :: dz (:,:)
203 real, allocatable :: dzm(:,:)
204 real, allocatable :: zk(:,:)
205 logical, allocatable :: proc_domain(:,:)
206 logical, allocatable :: thinned(:,:)
207 ! obs_global_index is the original index of this obs in the serial
208 ! code. It is used to reassemble obs in serial-code-order to replicate
209 ! summation order for bitwise-exact testing of distributed-memory
210 ! parallel configurations.
211 integer, allocatable :: obs_global_index(:)
212 end type infa_type
214 type stn_loc_type
215 real :: lon ! radar site loc
216 real :: lat ! radar site loc
217 real :: elv ! radar site loc
218 real :: x ! radar site loc
219 real :: y ! radar site loc
220 real :: zk ! radar site loc
221 end type stn_loc_type
223 type radar_type
224 type (stn_loc_type) :: stn_loc
226 real, pointer :: model_p(:)
227 real, pointer :: model_t(:)
228 real, pointer :: model_rho(:)
229 real, pointer :: model_qrn(:)
230 real, pointer :: model_qcl(:)
231 real, pointer :: model_qci(:)
232 real, pointer :: model_qsn(:)
233 real, pointer :: model_qgr(:)
234 real, pointer :: model_zmm(:) ! reflectivity in mm^6 mm^-3
235 real :: model_ps
237 real , pointer :: height (:) ! Height in m
238 integer , pointer :: height_qc(:) ! Height QC
240 type (field_type) , pointer :: rv (:) ! Radial Velocity
241 type (field_type) , pointer :: rf (:) ! Reflectivity
242 type (field_type) , pointer :: zmm (:) ! Reflectivity (mm^6 mm^-3)
243 type (field_type) , pointer :: rcl (:) !
244 type (field_type) , pointer :: rci (:) !
245 real , pointer :: rclo (:)
246 real , pointer :: rcio (:)
247 type (field_type) , pointer :: rrn (:) => null() ! qrain
248 type (field_type) , pointer :: rsn (:) => null() ! qsnow
249 type (field_type) , pointer :: rgr (:) => null() ! qgraupel
250 type (field_type) , pointer :: rqv (:) => null()
251 real , pointer :: rrno (:) => null()
252 real , pointer :: rsno (:) => null()
253 real , pointer :: rgro (:) => null()
254 real , pointer :: rqvo (:) => null()
255 end type radar_type
257 type multi_level_type
258 type (info_type) :: info
259 type (model_loc_type) :: loc
260 type (each_level_type) :: each(max_ob_levels)
261 end type multi_level_type
263 type multi_level_type_BUFR
264 type (info_type) :: info
265 type (model_loc_type) :: loc
266 type (each_level_type), pointer :: each(:)
267 end type multi_level_type_BUFR
269 type radar_stn_type
270 character (len = 5) :: platform ! Data type
271 character (len = 12) :: name ! Station name
272 character (len = 19) :: date_char ! CCYY-MM-DD_HH:MM:SS date
273 integer :: numobs ! number of Obs
274 integer :: levels ! number of levels
275 real :: lat ! Latitude in degree
276 real :: lon ! Longitude in degree
277 real :: elv ! Elevation in m
278 end type radar_stn_type
280 type radar_multi_level_type
281 type (radar_stn_type) :: stn
282 type (info_type) :: info
283 type (model_loc_type) :: loc
284 type (radar_each_level_type) :: each(max_ob_levels)
285 end type radar_multi_level_type
287 type rain_stn_type
288 character (len = 5) :: platform ! Data type
289 character (len = 12) :: name ! Station name
290 character (len = 19) :: date_char ! CCYY-MM-DD_HH:MM:SS date
291 integer :: numobs ! number of Obs
292 integer :: levels ! number of levels
293 real :: lat ! Latitude in degree
294 real :: lon ! Longitude in degree
295 real :: elv ! Elevation in
296 end type rain_stn_type
298 type rain_type
299 real :: height
300 integer :: height_qc
301 type (stn_loc_type) :: stn_loc
302 type (field_type) :: model_rainc
303 type (field_type) :: model_rainnc
304 type (field_type) :: rain
305 end type rain_type
307 type rain_each_type
308 real :: height ! Height in m
309 integer :: height_qc ! Height QC
310 real :: zk ! MM5 k-coordinates
311 type (field_type) :: rain
312 end type rain_each_type
314 type rain_single_level_type
315 type (rain_stn_type) :: stn
316 type (info_type) :: info
317 type (model_loc_type) :: loc
318 type (rain_each_type) :: each(1)
319 end type rain_single_level_type
321 #if (WRF_CHEM == 1)
323 type chemic_surf_type
324 real :: height ! Height in m
325 integer :: height_qc ! Height QC
326 real :: zk ! k-coordinates
327 type (field_type), pointer :: chem(:) ! Concentration measurement for multiple species and platforms
328 end type chemic_surf_type
330 type singl_level_type
331 type (info_type) :: info
332 type (model_loc_type) :: loc
333 !!! type (chemic_surf_type) :: each
334 type (field_type), pointer :: chem(:)
335 end type singl_level_type
337 #endif
339 ! [3.2] Innovation vector structure:
341 type airep_type
342 real , pointer :: h (:) ! Height in m
343 real , pointer :: p (:) ! pressure
344 type (field_type) , pointer :: u (:) ! u-wind.
345 type (field_type) , pointer :: v (:) ! v-wind.
346 type (field_type) , pointer :: t (:) ! temperature.
347 type (field_type) , pointer :: q (:) ! specific humidity.
348 end type airep_type
350 type pilot_type
351 real , pointer :: h (:) ! Height in m
352 real , pointer :: p (:) ! pressure
353 type (field_type) , pointer :: u (:) ! u-wind.
354 type (field_type) , pointer :: v (:) ! v-wind.
355 end type pilot_type
357 type bogus_type
358 real , pointer :: h (:) ! Height in m
359 real , pointer :: p (:) ! pressure.
360 type (field_type) , pointer :: u (:) ! u-wind.
361 type (field_type) , pointer :: v (:) ! v-wind.
362 type (field_type) , pointer :: t (:) ! temperature.
363 type (field_type) , pointer :: q (:) ! q.
364 type (field_type) :: slp ! sea level pressure.
365 end type bogus_type
367 type satem_type
368 real :: ref_p ! Reference pressure
369 real , pointer :: p (:) ! Multi-level pressure
371 type (field_type) , pointer :: thickness(:) ! Thickness.
372 type (field_type) , pointer :: org_thickness(:) ! To store original Thickness info.
373 end type satem_type
375 type geoamv_type
376 real , pointer :: p (:) ! Height in Pa
377 type (field_type) , pointer :: u (:) ! u-wind.
378 type (field_type) , pointer :: v (:) ! v-wind.
379 end type geoamv_type
381 type polaramv_type
382 real , pointer :: p (:) ! Height in Pa
383 type (field_type) , pointer :: u (:) ! u-wind.
384 type (field_type) , pointer :: v (:) ! v-wind.
385 end type polaramv_type
387 type gpsref_type
388 real , pointer :: h (:) ! Multi-level height
389 type (field_type), pointer :: ref(:) ! GPS Refractivity
390 type (field_type), pointer :: p (:) ! Retrieved P from Ref.
391 type (field_type), pointer :: t (:) ! Retrieved T from Ref.
392 type (field_type), pointer :: q (:) ! From NCEP analysis.
393 end type gpsref_type
395 type gpseph_type
396 integer :: level1 ! lowest_level
397 integer :: level2 ! highest_level
398 real :: rfict ! Local curvature radius of the reference ellipsoid for the occultation point
399 real , pointer :: h (:) ! Multi-level height
400 type (field_type), pointer :: eph(:) ! GPS excess phase
401 type (field_type), pointer :: ref(:) ! GPS Refractivity
402 real, pointer :: azim(:) ! Azimuth angle of the occultation plane at tangent point
403 real, pointer :: lat(:) ! Latitude of perigee point
404 real, pointer :: lon(:) ! Longitude of perigee point
405 end type gpseph_type
407 type synop_type
408 real :: h ! Height in m
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 ! q.
414 end type synop_type
416 type sound_type
417 real , pointer :: h (:) ! Height in m
418 real , pointer :: p (:) ! pressure.
420 type (field_type) , pointer :: u (:) ! u-wind.
421 type (field_type) , pointer :: v (:) ! v-wind.
422 type (field_type) , pointer :: t (:) ! temperature.
423 type (field_type) , pointer :: q (:) ! q.
424 end type sound_type
426 type mtgirs_type
427 real , pointer :: h (:) ! Height in m
428 real , pointer :: p (:) ! pressure.
430 type (field_type) , pointer :: u (:) ! u-wind.
431 type (field_type) , pointer :: v (:) ! v-wind.
432 type (field_type) , pointer :: t (:) ! temperature.
433 type (field_type) , pointer :: q (:) ! q.
434 end type mtgirs_type
436 type tamdar_type
437 real , pointer :: h (:) ! Height in m
438 real , pointer :: p (:) ! pressure.
440 type (field_type) , pointer :: u (:) ! u-wind.
441 type (field_type) , pointer :: v (:) ! v-wind.
442 type (field_type) , pointer :: t (:) ! temperature.
443 type (field_type) , pointer :: q (:) ! q.
444 end type tamdar_type
446 type varbc_tamdar_type
447 character(len=40) :: fmt_param ! Format of parameter table
448 integer :: nmaxpred ! Max. No. of predictors
449 integer :: nphase ! No. of flight phases
450 integer :: nair ! No. of aircrafts in table
451 integer :: npred ! No. of predictors
452 integer :: nmaxobs ! Max Obs No.
453 integer , pointer :: nobs (:,:)! Obs No. in proc
454 integer , pointer :: nobs_sum(:,:)! Total Obs No.
455 integer , pointer :: tail_id (:)! Tail ID of aircrafts
456 integer , pointer :: obs_sn(:,:,:)! Serial No. of Obs in proc
457 integer , pointer :: ifuse (:,:)! run varbc or not
458 integer , pointer :: index (:,:,:)! Index in CV
459 real , pointer :: pred (:,:,:)! Predictors
460 real , pointer :: param (:,:,:)! Parameters
461 real , pointer :: bgerr (:,:,:)! Bkg err in Hessian
462 real , pointer :: vtox(:,:,:,:)! Transformation of CV
463 end type varbc_tamdar_type
465 type airsr_type
466 real , pointer :: h (:) ! Height in m
467 real , pointer :: p (:) ! pressure.
468 type (field_type) , pointer :: t (:) ! temperature.
469 type (field_type) , pointer :: q (:) ! q.
470 end type airsr_type
472 type gpspw_type
473 type (field_type) :: tpw ! Toatl precipitable water cm from GPS
474 end type gpspw_type
476 type ssmi_rv_type
477 type (field_type) :: Speed ! Wind speed in m/s
478 type (field_type) :: tpw ! Toatl precipitable water cm
479 end type ssmi_rv_type
481 type ssmi_tb_type
483 type (field_type) :: tb19v ! Brightness T (k) 19V
484 type (field_type) :: tb19h ! Brightness T (k) 19H
485 type (field_type) :: tb22v ! Brightness T (k) 22V
486 type (field_type) :: tb37v ! Brightness T (k) 37V
487 type (field_type) :: tb37h ! Brightness T (k) 37H
488 type (field_type) :: tb85v ! Brightness T (k) 85V
489 type (field_type) :: tb85h ! Brightness T (k) 85H
490 end type ssmi_tb_type
492 type ssmt1_type
493 real , pointer :: h (:) ! Height in m
494 real , pointer :: p (:) ! Pressure in Pa.
495 type (field_type) , pointer :: t (:) ! temperature.
496 end type ssmt1_type
498 type ssmt2_type
499 real , pointer :: h (:) ! Height in m
500 real , pointer :: p (:) ! Pressure in Pa.
501 type (field_type) , pointer :: rh (:) ! Relative humidity.
502 end type ssmt2_type
504 type pseudo_type
505 type (field_type) :: u ! u-wind.
506 type (field_type) :: v ! v-wind.
507 type (field_type) :: t ! Temperature.
508 type (field_type) :: p ! Pressure.
509 type (field_type) :: q ! Specific Humidity.
510 end type pseudo_type
512 type qscat_type
513 real :: h ! Height in m
514 type (field_type) :: u ! u-wind.
515 type (field_type) :: v ! v-wind.
516 end type qscat_type
518 type varbc_info_type
519 integer :: platform_id, satellite_id, sensor_id
520 integer :: npredmax
521 integer :: gammapred
522 integer :: nchanl
523 integer, pointer :: nbgerr(:)
524 real, pointer :: pred(:,:)
525 real, pointer :: pred_mean(:)
526 real, pointer :: pred_std(:)
527 end type varbc_info_type
529 type varbc_type
530 integer :: nobs
531 integer :: npred
532 integer :: ichanl
533 integer, pointer :: pred_use(:)
534 integer, pointer :: ipred(:)
535 integer, pointer :: index(:)
536 real, pointer :: param(:)
537 real, pointer :: bgerr(:)
538 real, pointer :: vtox(:,:)
539 end type varbc_type
540 type clddet_geoir_type
541 real :: RTCT, RFMFT, TEMPIR, terr_hgt
542 real :: tb_stddev_10, tb_stddev_13,tb_stddev_14
543 real :: CIRH2O
544 !real, allocatable :: CIRH2O(:,:,:)
545 end type clddet_geoir_type
546 type superob_type
547 real, allocatable :: tb_obs(:,:)
548 type(clddet_geoir_type), allocatable :: cld_qc(:)
549 end type superob_type
550 type cv_index_type
551 integer :: ts
552 integer :: nclouds
553 integer :: ncv
554 integer, pointer :: cc(:)
555 real, pointer :: vtox(:,:)
556 end type cv_index_type
558 type instid_type
559 ! Instrument triplet, follow the convension of RTTOV
560 integer :: platform_id, satellite_id, sensor_id
561 integer :: rad_monitoring ! 0 (monitor_off): assimilating
562 ! (default in Registry.wrfvar),
563 ! 1 (monitor_on): monitoring
564 ! monitor_on and monitor_off defined in da_control.f90
565 character(len=20) :: rttovid_string
566 character(len=20) :: rttovid_string_coef
567 integer :: num_rad, nchan, nlevels
568 integer :: num_rad_glo
569 integer, pointer :: ichan(:)
570 real, pointer :: tb_inv(:,:)
571 integer, pointer :: tb_qc(:,:)
572 real, pointer :: tb_error(:,:)
573 real, pointer :: tb_xb(:,:)
574 real, pointer :: tb_xb_clr(:,:)
575 real, pointer :: tb_sens(:,:)
576 real, pointer :: tb_imp(:,:)
577 real, pointer :: rad_xb(:,:)
578 real, pointer :: rad_obs(:,:)
579 real, pointer :: rad_ovc(:,:,:)
580 integer, pointer :: scanpos(:)
581 integer, pointer :: scanline(:)
582 integer, pointer :: cloud_flag(:,:)
583 integer, pointer :: cloudflag(:)
584 integer, pointer :: rain_flag(:)
585 real, allocatable :: cloud_frac(:)
586 real, pointer :: satzen(:)
587 real, pointer :: satazi(:)
588 real, pointer :: solzen(:)
589 real, pointer :: solazi(:)
590 real, pointer :: tropt(:) !! Tropopause temperature, K.
591 real, pointer :: t(:,:)
592 real, pointer :: q(:,:)
593 real, pointer :: mr(:,:)
594 real, pointer :: tm(:,:)
595 real, pointer :: qm(:,:)
596 real, pointer :: lod(:,:,:) ! layer_optical_depth
597 real, pointer :: trans(:,:,:) ! layer transmittance
598 real, pointer :: der_trans(:,:,:) ! d(transmittance)/dp
599 real, pointer :: kmin_t(:)
600 real, pointer :: kmax_p(:)
601 real, pointer :: sensitivity_ratio(:,:,:)
602 real, pointer :: p_chan_level(:,:)
603 real, pointer :: qrn(:,:)
604 real, pointer :: qcw(:,:)
605 real, pointer :: qci(:,:)
606 real, pointer :: qsn(:,:)
607 real, pointer :: qgr(:,:)
608 real, pointer :: qhl(:,:)
609 real, pointer :: pm(:,:)
610 real, pointer :: rcw(:,:) ! cloud water effectiv radius
611 real, pointer :: rci(:,:) ! cloud ice effective radius
612 real, pointer :: rrn(:,:) ! rain effective radius
613 real, pointer :: rsn(:,:) ! snow effective radius
614 real, pointer :: rgr(:,:) ! graupel effective radius
615 real, pointer :: rhl(:,:) ! hail effective radius
616 real, pointer :: pf(:,:) ! full level pressure for CRTM
617 real, pointer :: emiss(:,:)
618 real, pointer :: u10(:)
619 real, pointer :: v10(:)
620 real, pointer :: t2m(:)
621 real, pointer :: q2m(:)
622 real, pointer :: mr2m(:)
623 real, pointer :: psfc(:)
624 real, pointer :: ps(:)
625 real, pointer :: ts(:)
626 real, pointer :: smois(:)
627 real, pointer :: tslb(:)
628 real, pointer :: snowh(:)
629 integer, pointer :: isflg(:)
630 integer, pointer :: ifgat(:)
631 integer, pointer :: landsea_mask(:)
632 integer, pointer :: surftype(:) ! RTTOV only, 0:land, 1:sea, 2:sea-ice
633 real, pointer :: snow_frac(:) ! RTTOV only
634 real, pointer :: elevation(:)
635 real, pointer :: soiltyp(:)
636 real, pointer :: vegtyp(:)
637 real, pointer :: vegfra(:)
638 real, pointer :: clwp(:) ! model/guess clwp
639 real, pointer :: cip(:) ! model/guess cloud-ice path
640 real, pointer :: clw(:) ! currently AMSR2 only
641 real, pointer :: ps_jacobian(:,:) ! only RTTOV
642 real, pointer :: ts_jacobian(:,:) ! only over water CRTM
643 real, pointer :: windspeed_jacobian(:,:) ! only MV and over water CRTM
644 real, pointer :: emiss_jacobian(:,:)
645 real, pointer :: gamma_jacobian(:,:)
646 real, pointer :: t_jacobian(:,:,:)
647 real, pointer :: q_jacobian(:,:,:)
648 real, pointer :: lod_jacobian(:,:,:)
649 real, pointer :: trans_jacobian(:,:,:)
650 real, pointer :: water_jacobian(:,:,:) ! water content jacobian
651 real, pointer :: ice_jacobian(:,:,:)
652 real, pointer :: rain_jacobian(:,:,:)
653 real, pointer :: snow_jacobian(:,:,:)
654 real, pointer :: graupel_jacobian(:,:,:)
655 real, pointer :: hail_jacobian(:,:,:)
656 real, pointer :: water_r_jacobian(:,:,:) ! effective radius jacobian
657 real, pointer :: ice_r_jacobian(:,:,:)
658 real, pointer :: rain_r_jacobian(:,:,:)
659 real, pointer :: snow_r_jacobian(:,:,:)
660 real, pointer :: graupel_r_jacobian(:,:,:)
661 real, pointer :: hail_r_jacobian(:,:,:)
662 real, pointer :: water_coverage(:)
663 real, pointer :: land_coverage(:)
664 real, pointer :: ice_coverage(:)
665 real, pointer :: snow_coverage(:)
666 integer, pointer :: crtm_climat(:) ! CRTM only
667 integer :: superob_width = 1
668 type (varbc_info_type) :: varbc_info
669 type (varbc_type),pointer :: varbc(:)
670 type (cv_index_type), pointer :: cv_index(:)
671 type (infa_type) :: info
672 type (superob_type), allocatable :: superob(:,:)
673 end type instid_type
675 type iv_type
676 integer :: nstats(num_ob_indexes)
678 integer :: time
680 integer :: num_inst, total_rad_pixel, total_rad_channel
682 real :: synop_ef_u, synop_ef_v, synop_ef_t, synop_ef_p, synop_ef_q
683 real :: metar_ef_u, metar_ef_v, metar_ef_t, metar_ef_p, metar_ef_q
684 real :: ships_ef_u, ships_ef_v, ships_ef_t, ships_ef_p, ships_ef_q
685 real :: geoamv_ef_u, geoamv_ef_v
686 real :: polaramv_ef_u, polaramv_ef_v
687 real :: gpspw_ef_tpw
688 real :: sound_ef_u, sound_ef_v, sound_ef_t, sound_ef_q
689 real :: mtgirs_ef_u, mtgirs_ef_v, mtgirs_ef_t, mtgirs_ef_q
690 real :: tamdar_ef_u, tamdar_ef_v, tamdar_ef_t, tamdar_ef_q
691 real :: tamdar_sfc_ef_u, tamdar_sfc_ef_v, tamdar_sfc_ef_t, tamdar_sfc_ef_p, tamdar_sfc_ef_q
692 real :: airep_ef_u, airep_ef_v, airep_ef_t, airep_ef_q
693 real :: pilot_ef_u, pilot_ef_v
694 real :: ssmir_ef_speed, ssmir_ef_tpw
695 real :: satem_ef_thickness, ssmt1_ef_t, ssmt2_ef_rh
696 real :: gpsref_ef_ref, gpsref_ef_p, gpsref_ef_t, gpsref_ef_q
697 real :: gpseph_ef_eph
698 real :: qscat_ef_u, qscat_ef_v
699 real :: profiler_ef_u, profiler_ef_v
700 real :: buoy_ef_u, buoy_ef_v, buoy_ef_t, buoy_ef_p, buoy_ef_q
701 real :: radar_ef_rv, radar_ef_rf, radar_ef_rr
702 real :: bogus_ef_u, bogus_ef_v, bogus_ef_t, bogus_ef_p, bogus_ef_q, bogus_ef_slp
703 real :: airsr_ef_t, airsr_ef_q
704 real :: rain_ef_r
705 #if (WRF_CHEM == 1)
706 real :: chemic_surf_ef
707 #endif
709 type (infa_type) :: info(num_ob_indexes)
711 type (airsr_type) , pointer :: airsr(:)
712 type (sound_type) , pointer :: sound(:)
713 type (synop_type) , pointer :: sonde_sfc(:)
714 type (airep_type) , pointer :: airep(:)
715 type (pilot_type) , pointer :: pilot(:)
716 type (satem_type) , pointer :: satem(:)
717 type (geoamv_type) , pointer :: geoamv(:)
718 type (polaramv_type) , pointer :: polaramv(:)
719 type (synop_type) , pointer :: synop(:)
720 type (synop_type) , pointer :: metar(:)
721 type (synop_type) , pointer :: ships(:)
722 type (gpspw_type) , pointer :: gpspw(:)
723 type (gpsref_type) , pointer :: gpsref(:)
724 type (gpseph_type) , pointer :: gpseph(:)
725 type (ssmi_tb_type) , pointer :: ssmi_tb(:)
726 type (ssmi_rv_type) , pointer :: ssmi_rv(:)
727 type (ssmt1_type) , pointer :: ssmt1(:)
728 type (ssmt2_type) , pointer :: ssmt2(:)
729 type (pseudo_type) , pointer :: pseudo(:)
730 type (qscat_type) , pointer :: qscat(:)
731 type (synop_type) , pointer :: buoy(:)
732 type (pilot_type) , pointer :: profiler(:)
733 type (bogus_type) , pointer :: bogus(:)
734 type (radar_type) , pointer :: radar(:)
735 type (instid_type) , pointer :: instid(:)
736 type (mtgirs_type) , pointer :: mtgirs(:)
737 type (tamdar_type) , pointer :: tamdar(:)
738 type (synop_type) , pointer :: tamdar_sfc(:)
739 type (rain_type) , pointer :: rain(:)
740 #if (WRF_CHEM == 1)
741 type (chemic_surf_type), pointer :: chemic_surf(:)
742 #endif
744 type (varbc_tamdar_type) :: varbc_tamdar
746 real :: missing
747 real :: ptop
748 end type iv_type
750 type number_type
751 integer :: bad
752 integer :: miss
753 integer :: use
754 end type number_type
756 type bad_info_type
757 type (number_type) :: num
758 integer :: nn(100000)
759 integer :: kk(100000)
760 end type bad_info_type
762 type bad_data_type
763 type (bad_info_type) :: u
764 type (bad_info_type) :: v
765 type (bad_info_type) :: t
766 type (bad_info_type) :: p
767 type (bad_info_type) :: q
768 type (bad_info_type) :: tpw
769 type (bad_info_type) :: Speed
770 type (bad_info_type) :: gpsref
771 type (bad_info_type) :: gpseph
772 type (bad_info_type) :: thickness
773 type (bad_info_type) :: rh
774 type (bad_info_type) :: rv
775 type (bad_info_type) :: rf
776 type (bad_info_type) :: rrn
777 type (bad_info_type) :: rsn
778 type (bad_info_type) :: rgr
779 type (bad_info_type) :: rcl
780 type (bad_info_type) :: rci
781 type (bad_info_type) :: rqv
782 type (bad_info_type) :: slp
783 type (bad_info_type) :: rad
784 type (bad_info_type) :: rain
785 #if (WRF_CHEM == 1)
786 type (bad_info_type) :: chemic_surf
787 #endif
788 end type bad_data_type
790 type count_obs_number_type
791 integer :: num_used
792 integer :: num_outside_iyjx
793 integer :: num_max_err_chk
794 integer :: num_missing
795 end type count_obs_number_type
797 !--------------------------------------------------------------------------
798 ! [3.0] Observation/residual structure definition:
799 !--------------------------------------------------------------------------
801 type residual_synop_type
802 real :: u ! u-wind.
803 real :: v ! v-wind.
804 real :: t ! temperature.
805 real :: p ! pressure.
806 real :: q ! q.
807 end type residual_synop_type
809 type residual_qscat_type
810 real :: u ! u-wind.
811 real :: v ! v-wind.
812 end type residual_qscat_type
814 type residual_geoamv_type
815 real, pointer :: u(:) ! u-wind.
816 real, pointer :: v(:) ! v-wind.
817 end type residual_geoamv_type
819 type residual_polaramv_type
820 real, pointer :: u(:) ! u-wind.
821 real, pointer :: v(:) ! v-wind.
822 end type residual_polaramv_type
824 type residual_gpspw_type
825 real :: tpw ! Total precipitable water.
826 end type residual_gpspw_type
828 type residual_sound_type
829 real, pointer :: u(:) ! u-wind.
830 real, pointer :: v(:) ! v-wind.
831 real, pointer :: t(:) ! temperature.
832 real, pointer :: q(:) ! specific humidity.
833 end type residual_sound_type
835 type residual_mtgirs_type
836 real, pointer :: u(:) ! u-wind.
837 real, pointer :: v(:) ! v-wind.
838 real, pointer :: t(:) ! temperature.
839 real, pointer :: q(:) ! specific humidity.
840 end type residual_mtgirs_type
842 type residual_tamdar_type
843 real, pointer :: u(:) ! u-wind.
844 real, pointer :: v(:) ! v-wind.
845 real, pointer :: t(:) ! temperature.
846 real, pointer :: q(:) ! specific humidity.
847 end type residual_tamdar_type
849 type residual_airsr_type
850 real, pointer :: t(:) ! temperature.
851 real, pointer :: q(:) ! specific humidity.
852 end type residual_airsr_type
854 type residual_airep_type
855 real, pointer :: u(:) ! u-wind.
856 real, pointer :: v(:) ! v-wind.
857 real, pointer :: t(:) ! temperature.
858 real, pointer :: q(:) ! specific humidity.
859 end type residual_airep_type
861 type residual_pilot_type
862 real, pointer :: u(:) ! u-wind.
863 real, pointer :: v(:) ! v-wind.
864 end type residual_pilot_type
866 type residual_bogus_type
867 real, pointer :: u(:) ! u-wind.
868 real, pointer :: v(:) ! v-wind.
869 real, pointer :: t(:) ! temperature.
870 real, pointer :: q(:) ! specific humidity.
871 real :: slp ! sea-level pressure.
872 end type residual_bogus_type
874 type residual_satem_type
875 real, pointer :: thickness(:) ! Thickness.
876 end type residual_satem_type
878 type residual_gpsref_type
879 real, pointer :: ref(:) ! GPS Refractivity
880 real, pointer :: p (:) ! GPS Retrived p from Refractivity
881 real, pointer :: t (:) ! GPS Retrived t from Refractivity
882 real, pointer :: q (:) ! q from NCEP used by CDAAC in retrieval
883 end type residual_gpsref_type
885 type residual_gpseph_type
886 real, pointer :: eph(:) ! excess phase
887 end type residual_gpseph_type
889 type residual_ssmi_rv_type
890 real :: tpw ! Toatl precipitable water cm
891 real :: Speed ! Wind speed m/s
892 end type residual_ssmi_rv_type
894 type residual_ssmi_tb_type
895 real :: tb19v ! Brightness T (k) 19V
896 real :: tb19h ! Brightness T (k) 19H
897 real :: tb22v ! Brightness T (k) 22V
898 real :: tb37v ! Brightness T (k) 37V
899 real :: tb37h ! Brightness T (k) 37H
900 real :: tb85v ! Brightness T (k) 85V
901 real :: tb85h ! Brightness T (k) 85H
902 end type residual_ssmi_tb_type
904 type residual_ssmt1_type
905 real, pointer :: t(:) ! temperature.
906 end type residual_ssmt1_type
908 type residual_ssmt2_type
909 real, pointer :: rh(:) ! Relative Humidity.
910 end type residual_ssmt2_type
912 type residual_pseudo_type
913 real :: u ! u-wind.
914 real :: v ! v-wind.
915 real :: t ! temperature.
916 real :: p ! pressure.
917 real :: q ! specific humidity.
918 end type residual_pseudo_type
920 type residual_radar_type
921 real, pointer :: rv(:) ! rv
922 real, pointer :: rf(:) ! rf
923 real, pointer :: rcl(:) !
924 real, pointer :: rci(:) !
925 real, pointer :: rrn(:) => null() ! rrain
926 real, pointer :: rsn(:) => null() ! rsnow
927 real, pointer :: rgr(:) => null() ! rgraupel
928 real, pointer :: rqv(:) => null()
929 end type residual_radar_type
931 type residual_instid_type
932 integer :: num_rad
933 integer :: nchan
934 integer, pointer :: ichan (:)
935 real, pointer :: tb(:,:)
936 end type residual_instid_type
938 type residual_rain_type
939 real :: rain
940 end type residual_rain_type
942 #if (WRF_CHEM == 1)
943 type residual_chem_surf_type
944 real, pointer :: chem(:) ! Concentration measurement for multiple species
945 ! real :: bc
946 ! real :: oc
947 ! real :: co
948 ! real :: co2
949 ! real :: ch4
950 end type residual_chem_surf_type
951 #endif
953 type y_type
954 integer :: nlocal(num_ob_indexes)
955 integer :: ntotal(num_ob_indexes)
957 integer :: num_inst
959 type (residual_synop_type), pointer :: synop(:)
960 type (residual_synop_type), pointer :: metar(:) ! Same as synop type
961 type (residual_synop_type), pointer :: ships(:) ! Same as synop type
962 type (residual_geoamv_type), pointer :: geoamv(:)
963 type (residual_polaramv_type), pointer :: polaramv(:)
964 type (residual_gpspw_type), pointer :: gpspw (:)
965 type (residual_gpsref_type), pointer :: gpsref(:)
966 type (residual_gpseph_type), pointer :: gpseph(:)
967 type (residual_sound_type), pointer :: sound(:)
968 type (residual_mtgirs_type), pointer :: mtgirs(:)
969 type (residual_tamdar_type), pointer :: tamdar(:)
970 type (residual_synop_type), pointer :: tamdar_sfc(:)
971 type (residual_airsr_type), pointer :: airsr(:)
972 type (residual_bogus_type), pointer :: bogus(:)
973 type (residual_synop_type), pointer :: sonde_sfc(:) ! Same as synop type
974 type (residual_airep_type), pointer :: airep(:)
975 type (residual_pilot_type), pointer :: pilot(:)
976 type (residual_satem_type), pointer :: satem(:)
977 type (residual_ssmi_tb_type), pointer :: ssmi_tb(:)
978 type (residual_ssmi_rv_type), pointer :: ssmi_rv(:)
979 type (residual_ssmt1_type), pointer :: ssmt1(:)
980 type (residual_ssmt2_type), pointer :: ssmt2(:)
981 type (residual_pseudo_type), pointer :: pseudo(:)
982 type (residual_qscat_type), pointer :: qscat(:)
983 type (residual_synop_type), pointer :: buoy(:) ! Same as synop type
984 type (residual_pilot_type), pointer :: profiler(:) ! Same as pilot type
985 type (residual_radar_type), pointer :: radar(:)
986 type (residual_instid_type), pointer :: instid(:)
987 type (residual_rain_type), pointer :: rain(:)
988 #if (WRF_CHEM == 1)
989 type (residual_chem_surf_type),pointer :: chemic_surf(:)
990 #endif
991 end type y_type
993 !--------------------------------------------------------------------------
994 ! [4.0] Control variable structure:
995 !--------------------------------------------------------------------------
997 ! Max/Min type:
999 type maxmin_type
1000 real :: value
1001 integer :: n, l
1002 end type maxmin_type
1004 !--------------------------------------------------------------------------
1005 ! [5.0] Control variable structure:
1006 !--------------------------------------------------------------------------
1008 type jo_type_rad
1009 integer, pointer :: num_ichan(:)
1010 real, pointer :: jo_ichan(:)
1011 end type jo_type_rad
1013 type jo_type
1014 real :: total
1015 real :: synop_u, synop_v, synop_t, synop_p, synop_q
1016 real :: metar_u, metar_v, metar_t, metar_p, metar_q
1017 real :: ships_u, ships_v, ships_t, ships_p, ships_q
1018 real :: geoamv_u, geoamv_v
1019 real :: polaramv_u, polaramv_v
1020 real :: gpspw_tpw, satem_thickness, gpsref_ref, gpseph_eph
1021 real :: sound_u, sound_v, sound_t, sound_q
1022 real :: sonde_sfc_u, sonde_sfc_v, sonde_sfc_t, &
1023 sonde_sfc_p, sonde_sfc_q
1024 real :: mtgirs_u, mtgirs_v, mtgirs_t, mtgirs_q
1025 real :: tamdar_u, tamdar_v, tamdar_t, tamdar_q
1026 real :: tamdar_sfc_u, tamdar_sfc_v, tamdar_sfc_t, &
1027 tamdar_sfc_p, tamdar_sfc_q
1028 real :: airep_u, airep_v, airep_t, airep_q
1029 real :: pilot_u, pilot_v
1030 real :: ssmir_speed, ssmir_tpw
1031 real :: ssmi_tb19v, ssmi_tb19h, ssmi_tb22v, ssmi_tb37v, &
1032 ssmi_tb37h, ssmi_tb85v, ssmi_tb85h
1033 real :: ssmt1_t, ssmt2_rh
1034 real :: pseudo_u, pseudo_v, pseudo_t, pseudo_p, pseudo_q
1035 real :: qscat_u, qscat_v
1036 real :: profiler_u, profiler_v
1037 real :: buoy_u, buoy_v, buoy_t, buoy_p, buoy_q
1038 real :: radar_rv, radar_rf, radar_rrn,radar_rsn,radar_rgr,radar_rcl,radar_rci,radar_rqv
1039 real :: bogus_u, bogus_v, bogus_t, bogus_q, bogus_slp
1040 real :: airsr_t, airsr_q
1041 real :: rain_r
1042 #if (WRF_CHEM == 1)
1043 real :: chemic_surf
1044 #endif
1045 type(jo_type_rad), pointer :: rad(:)
1046 end type jo_type
1048 type j_type
1049 real :: total
1050 real :: jb
1051 real :: jc
1052 real :: je
1053 real :: jp
1054 real :: js
1055 real :: jl
1056 real :: jd
1057 real :: jm
1058 real :: jt
1059 type (jo_type) :: jo
1060 end type j_type
1062 type cv_type
1063 integer :: size ! Total size of control variable.
1064 integer :: size_jb ! Size of CV array for Jb term.
1065 integer :: size_je ! Size of CV array for Je term.
1066 integer :: size_jp ! Size of CV array for Jp term.
1067 integer :: size_js ! Size of CV array for Js term.
1068 integer :: size_jl ! Size of CV array for Jl term.
1069 integer :: size_jt ! Size of CV array for Jt term.
1070 integer :: size1c ! Complex size of CV array of 1st variable error.
1071 integer :: size2c ! Complex size of CV array of 2nd variable error.
1072 integer :: size3c ! Complex size of CV array of 3rd variable error.
1073 integer :: size4c ! Complex size of CV array of 4th variable error.
1074 integer :: size5c ! Complex size of CV array of 5th variable error.
1076 integer :: size6c ! Complex size of CV array of 6th variable error.
1077 integer :: size7c ! Complex size of CV array of 7th variable error.
1078 integer :: size8c ! Complex size of CV array of 8th variable error.
1079 integer :: size9c ! Complex size of CV array of 9th variable error.
1080 integer :: size10c ! Complex size of CV array of 10th variable error.
1081 integer :: size11c ! Complex size of CV array of 11th variable error.
1083 integer :: size_alphac ! Size of alpha control variable (complex).
1084 integer :: size1 ! Size of CV array of 1st variable error.
1085 integer :: size2 ! Size of CV array of 2nd variable error.
1086 integer :: size3 ! Size of CV array of 3rd variable error.
1087 integer :: size4 ! Size of CV array of 4th variable error.
1088 integer :: size5 ! Size of CV array of 5th variable error.
1090 integer :: size6 ! Size of CV array of 6th variable error.
1091 integer :: size7 ! Size of CV array of 7th variable error.
1092 integer :: size8 ! Size of CV array of 8th variable error.
1093 integer :: size9 ! Size of CV array of 9th variable error.
1094 integer :: size10 ! Size of CV array of 10th variable error.
1095 integer :: size11i ! Size of CV array of 11th variable error.
1097 integer :: size1l ! Size of CV array of 1st variable lbc error.
1098 integer :: size2l ! Size of CV array of 2nd variable lbc error.
1099 integer :: size3l ! Size of CV array of 3rd variable lbc error.
1100 integer :: size4l ! Size of CV array of 4th variable lbc error.
1101 integer :: size5l ! Size of CV array of 5th variable lbc error.
1102 #if (WRF_CHEM == 1)
1103 integer,allocatable :: sizechemic (:) ! Size of CV array of chem variable error.
1104 #endif
1105 end type cv_type
1107 type qhat_type
1108 integer :: i
1109 real, allocatable:: values(:) ! qhat_type used in da_minimise_cg
1110 end type qhat_type
1112 type be_subtype
1113 integer :: mz ! Vertical truncation of errors.
1114 integer :: max_wave ! Global only - horizontal spectral truncation.
1115 character*10 :: name ! Variable name.
1116 real*8, pointer :: rf_alpha(:) ! RF scale length.
1117 real*8, pointer :: val(:,:) ! Local Standard dev./sqrt(eigenvalue).
1118 real*8, pointer :: evec(:,:,:) ! Local Vertical eigenvectors.
1119 real*8, pointer :: val_g(:) ! Global Standard dev./sqrt(eigenvalue).
1120 real*8, pointer :: evec_g(:,:) ! Global Vertical eigenvectors.
1121 real*8, pointer :: power(:,:) ! Power spectrum
1122 !_____For wavelet option:
1123 REAL, POINTER ::sd(:,:,:) ! 3D field std. dev.
1124 REAL, POINTER ::wsd(:,:,:) ! 3D wavelet std. dev.
1125 end type be_subtype
1127 type be_type
1128 integer :: ncv_mz ! number of variables for cv_mz
1129 integer, pointer :: cv_mz(:) ! array to hold mz of each cv
1130 integer :: ne
1131 integer :: max_wave ! Smallest spectral mode (global).
1132 integer :: mix
1133 integer :: mjy
1134 type (be_subtype) :: v1
1135 type (be_subtype) :: v2
1136 type (be_subtype) :: v3
1137 type (be_subtype) :: v4
1138 type (be_subtype) :: v5
1140 type (be_subtype) :: v6
1141 type (be_subtype) :: v7
1142 type (be_subtype) :: v8
1143 type (be_subtype) :: v9
1144 type (be_subtype) :: v10
1145 type (be_subtype) :: v11
1147 type (be_subtype) :: alpha
1148 real*8, pointer :: pb_vert_reg(:,:,:)
1149 #if (WRF_CHEM == 1)
1150 !integer :: ncv_mz_chem ! number of variables for cv_mz
1151 !integer, pointer :: cv_mz_chem(:) ! array to hold mz of each cv
1153 type (be_subtype),allocatable :: v12(:) ! Chem initial condition scaling factor CVs
1154 integer :: ncv_mz_chemic ! number of variables for cv_mz
1155 integer, pointer :: cv_mz_chemic(:) ! array to hold mz of each cv
1157 #endif
1159 ! Control variable space errors:
1160 type (cv_type) :: cv
1162 real, pointer :: reg_psi_chi (:,:)
1163 real, pointer :: reg_psi_t (:,:,:)
1164 real, pointer :: reg_psi_ps (:,:)
1165 real, pointer :: reg_psi_rh (:,:,:)
1166 real, pointer :: reg_chi_u_t (:,:,:)
1167 real, pointer :: reg_chi_u_ps (:,:)
1168 real, pointer :: reg_chi_u_rh (:,:,:)
1169 real, pointer :: reg_t_u_rh (:,:,:)
1170 real, pointer :: reg_ps_u_rh (:,:)
1172 !-----For cv option 3:
1173 INTEGER :: ndeg,nta
1174 REAL :: swidth
1175 REAL, POINTER :: be(:)
1176 REAL, POINTER :: rate(:)
1177 REAL, POINTER :: table(:,:)
1178 REAL, POINTER :: agvz(:,:,:,:)
1179 REAL, POINTER :: bvz(:,:,:)
1180 REAL, POINTER :: wgvz(:,:,:)
1181 REAL, POINTER :: slix(:,:,:,:)
1182 REAL, POINTER :: slipx(:,:)
1183 REAL, POINTER :: sljy(:,:,:,:)
1184 REAL, POINTER :: sljpy(:,:)
1185 REAL, POINTER :: vz(:,:,:,:)
1186 REAL, POINTER :: corz(:,:,:,:)
1187 REAL, POINTER :: corp(:,:)
1189 !_____For wavelet option:
1190 REAL, POINTER ::sd( :,:,:)! 4 3D & 1 2D field std. dev. sets.
1191 REAL, POINTER ::wsd(:,:,:)! 4 3D & 1 2D wavelet std. dev. sets.
1192 end type be_type
1194 ! Analysis_Stats maximum-minumum structure.
1196 type maxmin_field_type
1197 real :: value
1198 integer :: i, j
1199 end type maxmin_field_type
1201 ! vp_type is defined in the Registry
1202 ! x_type is defined in the Registry
1203 ! The framework allocates the (local-grid) xa structure.
1204 ! The framework allocates the (local-grid) xb structure.
1205 ! The framework (de)allocates the vv structure.
1206 ! The framework (de)allocates the vp structure.
1208 contains
1210 #include "da_allocate_background_errors.inc"
1211 #include "da_allocate_obs_info.inc"
1212 #include "da_allocate_observations.inc"
1213 #include "da_allocate_observations_rain.inc"
1214 #if (WRF_CHEM == 1)
1215 #include "da_allocate_observations_chem_sfc.inc"
1216 #endif
1217 #include "da_allocate_y.inc"
1218 #include "da_allocate_y_radar.inc"
1219 #include "da_allocate_y_rain.inc"
1220 #if (WRF_CHEM == 1)
1221 #include "da_allocate_y_chem_sfc.inc"
1222 #include "da_deallocate_y_chem_sfc.inc"
1223 #endif
1224 #include "da_deallocate_background_errors.inc"
1225 #include "da_deallocate_observations.inc"
1226 #include "da_deallocate_y.inc"
1227 #include "da_zero_x.inc"
1228 #include "da_zero_y.inc"
1229 #include "da_zero_vp_type.inc"
1230 #if (WRF_CHEM == 1)
1231 #include "da_zero_xchem_type.inc"
1232 #endif
1233 #include "da_initialize_cv.inc"
1234 #include "da_random_seed.inc"
1235 #include "da_gauss_noise.inc"
1237 end module da_define_structures