Merge remote-tracking branch 'origin/release-v4.6.1'
[WRF.git] / var / da / da_define_structures / da_define_structures.f90
blob2ecff3eaaa913830fdf362c5b956da3af80bd7f0
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, lightning, 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 type lightning_stn_type
322 character (len = 5) :: platform ! Data type
323 character (len = 12) :: name ! Station name
324 character (len = 19) :: date_char ! CCYY-MM-DD_HH:MM:SS date
325 integer :: numobs ! number of Obs
326 integer :: levels ! number of levels
327 real :: lat ! Latitude in degree
328 real :: lon ! Longitude in degree
329 real :: elv ! Elevation in
330 end type lightning_stn_type
332 type lightning_type
333 type (stn_loc_type) :: stn_loc
334 real , pointer :: height (:) ! Height in m
335 integer , pointer :: height_qc(:) ! Height QC
336 type (field_type) , pointer :: w(:) ! Retrieved vertical velocity from flash rate
337 type (field_type) , pointer :: div(:) ! Retrieved convergence fileds from vertical velocity
338 type (field_type) , pointer :: qv(:) ! Retrieved vapor mixing ratio from flash rate
339 end type lightning_type
341 type lightning_each_level_type
342 real :: height ! Height in m
343 integer :: height_qc ! Height QC
344 real :: zk ! MM5 k-coordinates
345 type (field_type) :: w
346 type (field_type) :: div
347 type (field_type) :: qv
348 end type lightning_each_level_type
350 type lightning_multi_level_type
351 type (lightning_stn_type) :: stn
352 type (info_type) :: info
353 type (model_loc_type) :: loc
354 type (lightning_each_level_type) :: each(max_ob_levels)
355 end type lightning_multi_level_type
357 #if (WRF_CHEM == 1)
359 type chemic_surf_type
360 real :: height ! Height in m
361 integer :: height_qc ! Height QC
362 real :: zk ! k-coordinates
363 type (field_type), pointer :: chem(:) ! Concentration measurement for multiple species and platforms
364 end type chemic_surf_type
366 type singl_level_type
367 type (info_type) :: info
368 type (model_loc_type) :: loc
369 !!! type (chemic_surf_type) :: each
370 type (field_type), pointer :: chem(:)
371 end type singl_level_type
373 #endif
375 ! [3.2] Innovation vector structure:
377 type airep_type
378 real , pointer :: h (:) ! Height in m
379 real , pointer :: p (:) ! pressure
380 type (field_type) , pointer :: u (:) ! u-wind.
381 type (field_type) , pointer :: v (:) ! v-wind.
382 type (field_type) , pointer :: t (:) ! temperature.
383 type (field_type) , pointer :: q (:) ! specific humidity.
384 end type airep_type
386 type pilot_type
387 real , pointer :: h (:) ! Height in m
388 real , pointer :: p (:) ! pressure
389 type (field_type) , pointer :: u (:) ! u-wind.
390 type (field_type) , pointer :: v (:) ! v-wind.
391 end type pilot_type
393 type bogus_type
394 real , pointer :: h (:) ! Height in m
395 real , pointer :: p (:) ! pressure.
396 type (field_type) , pointer :: u (:) ! u-wind.
397 type (field_type) , pointer :: v (:) ! v-wind.
398 type (field_type) , pointer :: t (:) ! temperature.
399 type (field_type) , pointer :: q (:) ! q.
400 type (field_type) :: slp ! sea level pressure.
401 end type bogus_type
403 type satem_type
404 real :: ref_p ! Reference pressure
405 real , pointer :: p (:) ! Multi-level pressure
407 type (field_type) , pointer :: thickness(:) ! Thickness.
408 type (field_type) , pointer :: org_thickness(:) ! To store original Thickness info.
409 end type satem_type
411 type geoamv_type
412 real , pointer :: p (:) ! Height in Pa
413 type (field_type) , pointer :: u (:) ! u-wind.
414 type (field_type) , pointer :: v (:) ! v-wind.
415 end type geoamv_type
417 type polaramv_type
418 real , pointer :: p (:) ! Height in Pa
419 type (field_type) , pointer :: u (:) ! u-wind.
420 type (field_type) , pointer :: v (:) ! v-wind.
421 end type polaramv_type
423 type gpsref_type
424 real , pointer :: h (:) ! Multi-level height
425 type (field_type), pointer :: ref(:) ! GPS Refractivity
426 type (field_type), pointer :: p (:) ! Retrieved P from Ref.
427 type (field_type), pointer :: t (:) ! Retrieved T from Ref.
428 type (field_type), pointer :: q (:) ! From NCEP analysis.
429 end type gpsref_type
431 type gpseph_type
432 integer :: level1 ! lowest_level
433 integer :: level2 ! highest_level
434 real :: rfict ! Local curvature radius of the reference ellipsoid for the occultation point
435 real , pointer :: h (:) ! Multi-level height
436 type (field_type), pointer :: eph(:) ! GPS excess phase
437 type (field_type), pointer :: ref(:) ! GPS Refractivity
438 real, pointer :: azim(:) ! Azimuth angle of the occultation plane at tangent point
439 real, pointer :: lat(:) ! Latitude of perigee point
440 real, pointer :: lon(:) ! Longitude of perigee point
441 end type gpseph_type
443 type synop_type
444 real :: h ! Height in m
445 type (field_type) :: u ! u-wind.
446 type (field_type) :: v ! v-wind.
447 type (field_type) :: t ! temperature.
448 type (field_type) :: p ! pressure.
449 type (field_type) :: q ! q.
450 end type synop_type
452 type sound_type
453 real , pointer :: h (:) ! Height in m
454 real , pointer :: p (:) ! pressure.
456 type (field_type) , pointer :: u (:) ! u-wind.
457 type (field_type) , pointer :: v (:) ! v-wind.
458 type (field_type) , pointer :: t (:) ! temperature.
459 type (field_type) , pointer :: q (:) ! q.
460 end type sound_type
462 type mtgirs_type
463 real , pointer :: h (:) ! Height in m
464 real , pointer :: p (:) ! pressure.
466 type (field_type) , pointer :: u (:) ! u-wind.
467 type (field_type) , pointer :: v (:) ! v-wind.
468 type (field_type) , pointer :: t (:) ! temperature.
469 type (field_type) , pointer :: q (:) ! q.
470 end type mtgirs_type
472 type tamdar_type
473 real , pointer :: h (:) ! Height in m
474 real , pointer :: p (:) ! pressure.
476 type (field_type) , pointer :: u (:) ! u-wind.
477 type (field_type) , pointer :: v (:) ! v-wind.
478 type (field_type) , pointer :: t (:) ! temperature.
479 type (field_type) , pointer :: q (:) ! q.
480 end type tamdar_type
482 type varbc_tamdar_type
483 character(len=40) :: fmt_param ! Format of parameter table
484 integer :: nmaxpred ! Max. No. of predictors
485 integer :: nphase ! No. of flight phases
486 integer :: nair ! No. of aircrafts in table
487 integer :: npred ! No. of predictors
488 integer :: nmaxobs ! Max Obs No.
489 integer , pointer :: nobs (:,:)! Obs No. in proc
490 integer , pointer :: nobs_sum(:,:)! Total Obs No.
491 integer , pointer :: tail_id (:)! Tail ID of aircrafts
492 integer , pointer :: obs_sn(:,:,:)! Serial No. of Obs in proc
493 integer , pointer :: ifuse (:,:)! run varbc or not
494 integer , pointer :: index (:,:,:)! Index in CV
495 real , pointer :: pred (:,:,:)! Predictors
496 real , pointer :: param (:,:,:)! Parameters
497 real , pointer :: bgerr (:,:,:)! Bkg err in Hessian
498 real , pointer :: vtox(:,:,:,:)! Transformation of CV
499 end type varbc_tamdar_type
501 type airsr_type
502 real , pointer :: h (:) ! Height in m
503 real , pointer :: p (:) ! pressure.
504 type (field_type) , pointer :: t (:) ! temperature.
505 type (field_type) , pointer :: q (:) ! q.
506 end type airsr_type
508 type gpspw_type
509 type (field_type) :: tpw ! Toatl precipitable water cm from GPS
510 end type gpspw_type
512 type ssmi_rv_type
513 type (field_type) :: Speed ! Wind speed in m/s
514 type (field_type) :: tpw ! Toatl precipitable water cm
515 end type ssmi_rv_type
517 type ssmi_tb_type
519 type (field_type) :: tb19v ! Brightness T (k) 19V
520 type (field_type) :: tb19h ! Brightness T (k) 19H
521 type (field_type) :: tb22v ! Brightness T (k) 22V
522 type (field_type) :: tb37v ! Brightness T (k) 37V
523 type (field_type) :: tb37h ! Brightness T (k) 37H
524 type (field_type) :: tb85v ! Brightness T (k) 85V
525 type (field_type) :: tb85h ! Brightness T (k) 85H
526 end type ssmi_tb_type
528 type ssmt1_type
529 real , pointer :: h (:) ! Height in m
530 real , pointer :: p (:) ! Pressure in Pa.
531 type (field_type) , pointer :: t (:) ! temperature.
532 end type ssmt1_type
534 type ssmt2_type
535 real , pointer :: h (:) ! Height in m
536 real , pointer :: p (:) ! Pressure in Pa.
537 type (field_type) , pointer :: rh (:) ! Relative humidity.
538 end type ssmt2_type
540 type pseudo_type
541 type (field_type) :: u ! u-wind.
542 type (field_type) :: v ! v-wind.
543 type (field_type) :: t ! Temperature.
544 type (field_type) :: p ! Pressure.
545 type (field_type) :: q ! Specific Humidity.
546 end type pseudo_type
548 type qscat_type
549 real :: h ! Height in m
550 type (field_type) :: u ! u-wind.
551 type (field_type) :: v ! v-wind.
552 end type qscat_type
554 type varbc_info_type
555 integer :: platform_id, satellite_id, sensor_id
556 integer :: npredmax
557 integer :: gammapred
558 integer :: nchanl
559 integer, pointer :: nbgerr(:)
560 real, pointer :: pred(:,:)
561 real, pointer :: pred_mean(:)
562 real, pointer :: pred_std(:)
563 end type varbc_info_type
565 type varbc_type
566 integer :: nobs
567 integer :: npred
568 integer :: ichanl
569 integer, pointer :: pred_use(:)
570 integer, pointer :: ipred(:)
571 integer, pointer :: index(:)
572 real, pointer :: param(:)
573 real, pointer :: bgerr(:)
574 real, pointer :: vtox(:,:)
575 end type varbc_type
576 type clddet_geoir_type
577 real :: RTCT, RFMFT, TEMPIR, terr_hgt ! for both ABI and AHI
578 real :: tb_stddev_10, tb_stddev_13,tb_stddev_14 ! only for AHI
579 real :: CIRH2O ! for both ABI and AHI
580 real, allocatable :: CIRH2O_abi(:,:,:) ! only for ABI
581 real, allocatable :: tb_stddev_3x3(:) ! only for ABI
582 integer :: RFMFT_ij(2) ! only for ABI
583 end type clddet_geoir_type
584 type superob_type
585 real, allocatable :: tb_obs(:,:)
586 type(clddet_geoir_type), allocatable :: cld_qc(:)
587 end type superob_type
588 type cv_index_type
589 integer :: ts
590 integer :: nclouds
591 integer :: ncv
592 integer, pointer :: cc(:)
593 real, pointer :: vtox(:,:)
594 end type cv_index_type
596 type instid_type
597 ! Instrument triplet, follow the convension of RTTOV
598 integer :: platform_id, satellite_id, sensor_id
599 integer :: rad_monitoring ! 0 (monitor_off): assimilating
600 ! (default in Registry.wrfvar),
601 ! 1 (monitor_on): monitoring
602 ! monitor_on and monitor_off defined in da_control.f90
603 character(len=20) :: rttovid_string
604 character(len=20) :: rttovid_string_coef
605 integer :: num_rad, nchan, nlevels
606 integer :: num_rad_glo
607 integer, pointer :: ichan(:)
608 real, pointer :: tb_inv(:,:)
609 integer, pointer :: tb_qc(:,:)
610 real, pointer :: tb_error(:,:)
611 real, pointer :: tb_xb(:,:)
612 real, pointer :: tb_xb_clr(:,:)
613 real, pointer :: tb_sens(:,:)
614 real, pointer :: tb_imp(:,:)
615 real, pointer :: rad_xb(:,:)
616 real, pointer :: rad_obs(:,:)
617 real, pointer :: rad_ovc(:,:,:)
618 integer, pointer :: scanpos(:)
619 integer, pointer :: scanline(:)
620 integer, pointer :: cloud_flag(:,:)
621 integer, pointer :: cloudflag(:)
622 integer, pointer :: rain_flag(:)
623 real, pointer :: cloud_mod(:,:) ! only for ABI
624 real, pointer :: cloud_obs(:,:) ! only for ABI
625 real, allocatable :: cloud_frac(:)
626 real, pointer :: satzen(:)
627 real, pointer :: satazi(:)
628 real, pointer :: solzen(:)
629 real, pointer :: solazi(:)
630 real, pointer :: tropt(:) !! Tropopause temperature, K.
631 real, pointer :: t(:,:)
632 real, pointer :: q(:,:)
633 real, pointer :: mr(:,:)
634 real, pointer :: tm(:,:)
635 real, pointer :: qm(:,:)
636 real, pointer :: lod(:,:,:) ! layer_optical_depth
637 real, pointer :: trans(:,:,:) ! layer transmittance
638 real, pointer :: der_trans(:,:,:) ! d(transmittance)/dp
639 real, pointer :: kmin_t(:)
640 real, pointer :: kmax_p(:)
641 real, pointer :: sensitivity_ratio(:,:,:)
642 real, pointer :: p_chan_level(:,:)
643 real, pointer :: qrn(:,:)
644 real, pointer :: qcw(:,:)
645 real, pointer :: qci(:,:)
646 real, pointer :: qsn(:,:)
647 real, pointer :: qgr(:,:)
648 real, pointer :: qhl(:,:)
649 real, pointer :: pm(:,:)
650 real, pointer :: rcw(:,:) ! cloud water effectiv radius
651 real, pointer :: rci(:,:) ! cloud ice effective radius
652 real, pointer :: rrn(:,:) ! rain effective radius
653 real, pointer :: rsn(:,:) ! snow effective radius
654 real, pointer :: rgr(:,:) ! graupel effective radius
655 real, pointer :: rhl(:,:) ! hail effective radius
656 real, pointer :: pf(:,:) ! full level pressure for CRTM
657 real, pointer :: emiss(:,:)
658 real, pointer :: u10(:)
659 real, pointer :: v10(:)
660 real, pointer :: t2m(:)
661 real, pointer :: q2m(:)
662 real, pointer :: mr2m(:)
663 real, pointer :: psfc(:)
664 real, pointer :: ps(:)
665 real, pointer :: ts(:)
666 real, pointer :: smois(:)
667 real, pointer :: tslb(:)
668 real, pointer :: snowh(:)
669 integer, pointer :: isflg(:)
670 integer, pointer :: ifgat(:)
671 integer, pointer :: landsea_mask(:)
672 integer, pointer :: surftype(:) ! RTTOV only, 0:land, 1:sea, 2:sea-ice
673 real, pointer :: snow_frac(:) ! RTTOV only
674 real, pointer :: elevation(:)
675 real, pointer :: soiltyp(:)
676 real, pointer :: vegtyp(:)
677 real, pointer :: vegfra(:)
678 real, pointer :: clwp(:) ! model/guess clwp
679 real, pointer :: cip(:) ! model/guess cloud-ice path
680 real, pointer :: clw(:) ! currently AMSR2 only
681 real, pointer :: ps_jacobian(:,:) ! only RTTOV
682 real, pointer :: ts_jacobian(:,:) ! only over water CRTM
683 real, pointer :: windspeed_jacobian(:,:) ! only MV and over water CRTM
684 real, pointer :: emiss_jacobian(:,:)
685 real, pointer :: gamma_jacobian(:,:)
686 real, pointer :: t_jacobian(:,:,:)
687 real, pointer :: q_jacobian(:,:,:)
688 real, pointer :: lod_jacobian(:,:,:)
689 real, pointer :: trans_jacobian(:,:,:)
690 real, pointer :: water_jacobian(:,:,:) ! water content jacobian
691 real, pointer :: ice_jacobian(:,:,:)
692 real, pointer :: rain_jacobian(:,:,:)
693 real, pointer :: snow_jacobian(:,:,:)
694 real, pointer :: graupel_jacobian(:,:,:)
695 real, pointer :: hail_jacobian(:,:,:)
696 real, pointer :: water_r_jacobian(:,:,:) ! effective radius jacobian
697 real, pointer :: ice_r_jacobian(:,:,:)
698 real, pointer :: rain_r_jacobian(:,:,:)
699 real, pointer :: snow_r_jacobian(:,:,:)
700 real, pointer :: graupel_r_jacobian(:,:,:)
701 real, pointer :: hail_r_jacobian(:,:,:)
702 real, pointer :: water_coverage(:)
703 real, pointer :: land_coverage(:)
704 real, pointer :: ice_coverage(:)
705 real, pointer :: snow_coverage(:)
706 integer, pointer :: crtm_climat(:) ! CRTM only
707 integer :: superob_width = 1
708 type (varbc_info_type) :: varbc_info
709 type (varbc_type),pointer :: varbc(:)
710 type (cv_index_type), pointer :: cv_index(:)
711 type (infa_type) :: info
712 type (superob_type), allocatable :: superob(:,:)
713 end type instid_type
715 type iv_type
716 integer :: nstats(num_ob_indexes)
718 integer :: time
720 integer :: num_inst, total_rad_pixel, total_rad_channel
722 real :: synop_ef_u, synop_ef_v, synop_ef_t, synop_ef_p, synop_ef_q
723 real :: metar_ef_u, metar_ef_v, metar_ef_t, metar_ef_p, metar_ef_q
724 real :: ships_ef_u, ships_ef_v, ships_ef_t, ships_ef_p, ships_ef_q
725 real :: geoamv_ef_u, geoamv_ef_v
726 real :: polaramv_ef_u, polaramv_ef_v
727 real :: gpspw_ef_tpw
728 real :: sound_ef_u, sound_ef_v, sound_ef_t, sound_ef_q
729 real :: mtgirs_ef_u, mtgirs_ef_v, mtgirs_ef_t, mtgirs_ef_q
730 real :: tamdar_ef_u, tamdar_ef_v, tamdar_ef_t, tamdar_ef_q
731 real :: tamdar_sfc_ef_u, tamdar_sfc_ef_v, tamdar_sfc_ef_t, tamdar_sfc_ef_p, tamdar_sfc_ef_q
732 real :: airep_ef_u, airep_ef_v, airep_ef_t, airep_ef_q
733 real :: pilot_ef_u, pilot_ef_v
734 real :: ssmir_ef_speed, ssmir_ef_tpw
735 real :: satem_ef_thickness, ssmt1_ef_t, ssmt2_ef_rh
736 real :: gpsref_ef_ref, gpsref_ef_p, gpsref_ef_t, gpsref_ef_q
737 real :: gpseph_ef_eph
738 real :: qscat_ef_u, qscat_ef_v
739 real :: profiler_ef_u, profiler_ef_v
740 real :: buoy_ef_u, buoy_ef_v, buoy_ef_t, buoy_ef_p, buoy_ef_q
741 real :: radar_ef_rv, radar_ef_rf, radar_ef_rr
742 real :: bogus_ef_u, bogus_ef_v, bogus_ef_t, bogus_ef_p, bogus_ef_q, bogus_ef_slp
743 real :: airsr_ef_t, airsr_ef_q
744 real :: rain_ef_r
745 real :: lightning_ef_w, lightning_ef_div, lightning_ef_qv
746 #if (WRF_CHEM == 1)
747 real :: chemic_surf_ef
748 #endif
750 type (infa_type) :: info(num_ob_indexes)
752 type (airsr_type) , pointer :: airsr(:)
753 type (sound_type) , pointer :: sound(:)
754 type (synop_type) , pointer :: sonde_sfc(:)
755 type (airep_type) , pointer :: airep(:)
756 type (pilot_type) , pointer :: pilot(:)
757 type (satem_type) , pointer :: satem(:)
758 type (geoamv_type) , pointer :: geoamv(:)
759 type (polaramv_type) , pointer :: polaramv(:)
760 type (synop_type) , pointer :: synop(:)
761 type (synop_type) , pointer :: metar(:)
762 type (synop_type) , pointer :: ships(:)
763 type (gpspw_type) , pointer :: gpspw(:)
764 type (gpsref_type) , pointer :: gpsref(:)
765 type (gpseph_type) , pointer :: gpseph(:)
766 type (ssmi_tb_type) , pointer :: ssmi_tb(:)
767 type (ssmi_rv_type) , pointer :: ssmi_rv(:)
768 type (ssmt1_type) , pointer :: ssmt1(:)
769 type (ssmt2_type) , pointer :: ssmt2(:)
770 type (pseudo_type) , pointer :: pseudo(:)
771 type (qscat_type) , pointer :: qscat(:)
772 type (synop_type) , pointer :: buoy(:)
773 type (pilot_type) , pointer :: profiler(:)
774 type (bogus_type) , pointer :: bogus(:)
775 type (radar_type) , pointer :: radar(:)
776 type (instid_type) , pointer :: instid(:)
777 type (mtgirs_type) , pointer :: mtgirs(:)
778 type (tamdar_type) , pointer :: tamdar(:)
779 type (synop_type) , pointer :: tamdar_sfc(:)
780 type (rain_type) , pointer :: rain(:)
781 type (lightning_type), pointer :: lightning(:)
782 #if (WRF_CHEM == 1)
783 type (chemic_surf_type), pointer :: chemic_surf(:)
784 #endif
786 type (varbc_tamdar_type) :: varbc_tamdar
788 real :: missing
789 real :: ptop
790 end type iv_type
792 type number_type
793 integer :: bad
794 integer :: miss
795 integer :: use
796 end type number_type
798 type bad_info_type
799 type (number_type) :: num
800 integer :: nn(100000)
801 integer :: kk(100000)
802 end type bad_info_type
804 type bad_data_type
805 type (bad_info_type) :: u
806 type (bad_info_type) :: v
807 type (bad_info_type) :: t
808 type (bad_info_type) :: p
809 type (bad_info_type) :: q
810 type (bad_info_type) :: tpw
811 type (bad_info_type) :: Speed
812 type (bad_info_type) :: gpsref
813 type (bad_info_type) :: gpseph
814 type (bad_info_type) :: thickness
815 type (bad_info_type) :: rh
816 type (bad_info_type) :: rv
817 type (bad_info_type) :: rf
818 type (bad_info_type) :: rrn
819 type (bad_info_type) :: rsn
820 type (bad_info_type) :: rgr
821 type (bad_info_type) :: rcl
822 type (bad_info_type) :: rci
823 type (bad_info_type) :: rqv
824 type (bad_info_type) :: slp
825 type (bad_info_type) :: rad
826 type (bad_info_type) :: rain
827 type (bad_info_type) :: w
828 type (bad_info_type) :: div
829 #if (WRF_CHEM == 1)
830 type (bad_info_type) :: chemic_surf
831 #endif
832 end type bad_data_type
834 type count_obs_number_type
835 integer :: num_used
836 integer :: num_outside_iyjx
837 integer :: num_max_err_chk
838 integer :: num_missing
839 end type count_obs_number_type
841 !--------------------------------------------------------------------------
842 ! [3.0] Observation/residual structure definition:
843 !--------------------------------------------------------------------------
845 type residual_synop_type
846 real :: u ! u-wind.
847 real :: v ! v-wind.
848 real :: t ! temperature.
849 real :: p ! pressure.
850 real :: q ! q.
851 end type residual_synop_type
853 type residual_qscat_type
854 real :: u ! u-wind.
855 real :: v ! v-wind.
856 end type residual_qscat_type
858 type residual_geoamv_type
859 real, pointer :: u(:) ! u-wind.
860 real, pointer :: v(:) ! v-wind.
861 end type residual_geoamv_type
863 type residual_polaramv_type
864 real, pointer :: u(:) ! u-wind.
865 real, pointer :: v(:) ! v-wind.
866 end type residual_polaramv_type
868 type residual_gpspw_type
869 real :: tpw ! Total precipitable water.
870 end type residual_gpspw_type
872 type residual_sound_type
873 real, pointer :: u(:) ! u-wind.
874 real, pointer :: v(:) ! v-wind.
875 real, pointer :: t(:) ! temperature.
876 real, pointer :: q(:) ! specific humidity.
877 end type residual_sound_type
879 type residual_mtgirs_type
880 real, pointer :: u(:) ! u-wind.
881 real, pointer :: v(:) ! v-wind.
882 real, pointer :: t(:) ! temperature.
883 real, pointer :: q(:) ! specific humidity.
884 end type residual_mtgirs_type
886 type residual_tamdar_type
887 real, pointer :: u(:) ! u-wind.
888 real, pointer :: v(:) ! v-wind.
889 real, pointer :: t(:) ! temperature.
890 real, pointer :: q(:) ! specific humidity.
891 end type residual_tamdar_type
893 type residual_airsr_type
894 real, pointer :: t(:) ! temperature.
895 real, pointer :: q(:) ! specific humidity.
896 end type residual_airsr_type
898 type residual_airep_type
899 real, pointer :: u(:) ! u-wind.
900 real, pointer :: v(:) ! v-wind.
901 real, pointer :: t(:) ! temperature.
902 real, pointer :: q(:) ! specific humidity.
903 end type residual_airep_type
905 type residual_pilot_type
906 real, pointer :: u(:) ! u-wind.
907 real, pointer :: v(:) ! v-wind.
908 end type residual_pilot_type
910 type residual_bogus_type
911 real, pointer :: u(:) ! u-wind.
912 real, pointer :: v(:) ! v-wind.
913 real, pointer :: t(:) ! temperature.
914 real, pointer :: q(:) ! specific humidity.
915 real :: slp ! sea-level pressure.
916 end type residual_bogus_type
918 type residual_satem_type
919 real, pointer :: thickness(:) ! Thickness.
920 end type residual_satem_type
922 type residual_gpsref_type
923 real, pointer :: ref(:) ! GPS Refractivity
924 real, pointer :: p (:) ! GPS Retrived p from Refractivity
925 real, pointer :: t (:) ! GPS Retrived t from Refractivity
926 real, pointer :: q (:) ! q from NCEP used by CDAAC in retrieval
927 end type residual_gpsref_type
929 type residual_gpseph_type
930 real, pointer :: eph(:) ! excess phase
931 end type residual_gpseph_type
933 type residual_ssmi_rv_type
934 real :: tpw ! Toatl precipitable water cm
935 real :: Speed ! Wind speed m/s
936 end type residual_ssmi_rv_type
938 type residual_ssmi_tb_type
939 real :: tb19v ! Brightness T (k) 19V
940 real :: tb19h ! Brightness T (k) 19H
941 real :: tb22v ! Brightness T (k) 22V
942 real :: tb37v ! Brightness T (k) 37V
943 real :: tb37h ! Brightness T (k) 37H
944 real :: tb85v ! Brightness T (k) 85V
945 real :: tb85h ! Brightness T (k) 85H
946 end type residual_ssmi_tb_type
948 type residual_ssmt1_type
949 real, pointer :: t(:) ! temperature.
950 end type residual_ssmt1_type
952 type residual_ssmt2_type
953 real, pointer :: rh(:) ! Relative Humidity.
954 end type residual_ssmt2_type
956 type residual_pseudo_type
957 real :: u ! u-wind.
958 real :: v ! v-wind.
959 real :: t ! temperature.
960 real :: p ! pressure.
961 real :: q ! specific humidity.
962 end type residual_pseudo_type
964 type residual_radar_type
965 real, pointer :: rv(:) ! rv
966 real, pointer :: rf(:) ! rf
967 real, pointer :: rcl(:) !
968 real, pointer :: rci(:) !
969 real, pointer :: rrn(:) => null() ! rrain
970 real, pointer :: rsn(:) => null() ! rsnow
971 real, pointer :: rgr(:) => null() ! rgraupel
972 real, pointer :: rqv(:) => null()
973 end type residual_radar_type
975 type residual_lightning_type
976 real, pointer :: w(:)
977 real, pointer :: div(:)
978 real, pointer :: qv(:)
979 end type residual_lightning_type
981 type residual_instid_type
982 integer :: num_rad
983 integer :: nchan
984 integer, pointer :: ichan (:)
985 real, pointer :: tb(:,:)
986 end type residual_instid_type
988 type residual_rain_type
989 real :: rain
990 end type residual_rain_type
992 #if (WRF_CHEM == 1)
993 type residual_chem_surf_type
994 real, pointer :: chem(:) ! Concentration measurement for multiple species
995 ! real :: bc
996 ! real :: oc
997 ! real :: co
998 ! real :: co2
999 ! real :: ch4
1000 end type residual_chem_surf_type
1001 #endif
1003 type y_type
1004 integer :: nlocal(num_ob_indexes)
1005 integer :: ntotal(num_ob_indexes)
1007 integer :: num_inst
1009 type (residual_synop_type), pointer :: synop(:)
1010 type (residual_synop_type), pointer :: metar(:) ! Same as synop type
1011 type (residual_synop_type), pointer :: ships(:) ! Same as synop type
1012 type (residual_geoamv_type), pointer :: geoamv(:)
1013 type (residual_polaramv_type), pointer :: polaramv(:)
1014 type (residual_gpspw_type), pointer :: gpspw (:)
1015 type (residual_gpsref_type), pointer :: gpsref(:)
1016 type (residual_gpseph_type), pointer :: gpseph(:)
1017 type (residual_sound_type), pointer :: sound(:)
1018 type (residual_mtgirs_type), pointer :: mtgirs(:)
1019 type (residual_tamdar_type), pointer :: tamdar(:)
1020 type (residual_synop_type), pointer :: tamdar_sfc(:)
1021 type (residual_airsr_type), pointer :: airsr(:)
1022 type (residual_bogus_type), pointer :: bogus(:)
1023 type (residual_synop_type), pointer :: sonde_sfc(:) ! Same as synop type
1024 type (residual_airep_type), pointer :: airep(:)
1025 type (residual_pilot_type), pointer :: pilot(:)
1026 type (residual_satem_type), pointer :: satem(:)
1027 type (residual_ssmi_tb_type), pointer :: ssmi_tb(:)
1028 type (residual_ssmi_rv_type), pointer :: ssmi_rv(:)
1029 type (residual_ssmt1_type), pointer :: ssmt1(:)
1030 type (residual_ssmt2_type), pointer :: ssmt2(:)
1031 type (residual_pseudo_type), pointer :: pseudo(:)
1032 type (residual_qscat_type), pointer :: qscat(:)
1033 type (residual_synop_type), pointer :: buoy(:) ! Same as synop type
1034 type (residual_pilot_type), pointer :: profiler(:) ! Same as pilot type
1035 type (residual_radar_type), pointer :: radar(:)
1036 type (residual_instid_type), pointer :: instid(:)
1037 type (residual_rain_type), pointer :: rain(:)
1038 type (residual_lightning_type),pointer :: lightning(:)
1039 #if (WRF_CHEM == 1)
1040 type (residual_chem_surf_type),pointer :: chemic_surf(:)
1041 #endif
1042 end type y_type
1044 !--------------------------------------------------------------------------
1045 ! [4.0] Control variable structure:
1046 !--------------------------------------------------------------------------
1048 ! Max/Min type:
1050 type maxmin_type
1051 real :: value
1052 integer :: n, l
1053 end type maxmin_type
1055 !--------------------------------------------------------------------------
1056 ! [5.0] Control variable structure:
1057 !--------------------------------------------------------------------------
1059 type jo_type_rad
1060 integer, pointer :: num_ichan(:)
1061 real, pointer :: jo_ichan(:)
1062 end type jo_type_rad
1064 type jo_type
1065 real :: total
1066 real :: synop_u, synop_v, synop_t, synop_p, synop_q
1067 real :: metar_u, metar_v, metar_t, metar_p, metar_q
1068 real :: ships_u, ships_v, ships_t, ships_p, ships_q
1069 real :: geoamv_u, geoamv_v
1070 real :: polaramv_u, polaramv_v
1071 real :: gpspw_tpw, satem_thickness, gpsref_ref, gpseph_eph
1072 real :: sound_u, sound_v, sound_t, sound_q
1073 real :: sonde_sfc_u, sonde_sfc_v, sonde_sfc_t, &
1074 sonde_sfc_p, sonde_sfc_q
1075 real :: mtgirs_u, mtgirs_v, mtgirs_t, mtgirs_q
1076 real :: tamdar_u, tamdar_v, tamdar_t, tamdar_q
1077 real :: tamdar_sfc_u, tamdar_sfc_v, tamdar_sfc_t, &
1078 tamdar_sfc_p, tamdar_sfc_q
1079 real :: airep_u, airep_v, airep_t, airep_q
1080 real :: pilot_u, pilot_v
1081 real :: ssmir_speed, ssmir_tpw
1082 real :: ssmi_tb19v, ssmi_tb19h, ssmi_tb22v, ssmi_tb37v, &
1083 ssmi_tb37h, ssmi_tb85v, ssmi_tb85h
1084 real :: ssmt1_t, ssmt2_rh
1085 real :: pseudo_u, pseudo_v, pseudo_t, pseudo_p, pseudo_q
1086 real :: qscat_u, qscat_v
1087 real :: profiler_u, profiler_v
1088 real :: buoy_u, buoy_v, buoy_t, buoy_p, buoy_q
1089 real :: radar_rv, radar_rf, radar_rrn,radar_rsn,radar_rgr,radar_rcl,radar_rci,radar_rqv
1090 real :: bogus_u, bogus_v, bogus_t, bogus_q, bogus_slp
1091 real :: airsr_t, airsr_q
1092 real :: rain_r
1093 real :: lightning_w, lightning_div, lightning_qv
1094 #if (WRF_CHEM == 1)
1095 real :: chemic_surf
1096 #endif
1097 type(jo_type_rad), pointer :: rad(:)
1098 end type jo_type
1100 type j_type
1101 real :: total
1102 real :: jb
1103 real :: jc
1104 real :: je
1105 real :: jp
1106 real :: js
1107 real :: jl
1108 real :: jd
1109 real :: jm
1110 real :: jt
1111 type (jo_type) :: jo
1112 end type j_type
1114 type cv_type
1115 integer :: size ! Total size of control variable.
1116 integer :: size_jb ! Size of CV array for Jb term.
1117 integer :: size_je ! Size of CV array for Je term.
1118 integer :: size_jp ! Size of CV array for Jp term.
1119 integer :: size_js ! Size of CV array for Js term.
1120 integer :: size_jl ! Size of CV array for Jl term.
1121 integer :: size_jt ! Size of CV array for Jt term.
1122 integer :: size1c ! Complex size of CV array of 1st variable error.
1123 integer :: size2c ! Complex size of CV array of 2nd variable error.
1124 integer :: size3c ! Complex size of CV array of 3rd variable error.
1125 integer :: size4c ! Complex size of CV array of 4th variable error.
1126 integer :: size5c ! Complex size of CV array of 5th variable error.
1128 integer :: size6c ! Complex size of CV array of 6th variable error.
1129 integer :: size7c ! Complex size of CV array of 7th variable error.
1130 integer :: size8c ! Complex size of CV array of 8th variable error.
1131 integer :: size9c ! Complex size of CV array of 9th variable error.
1132 integer :: size10c ! Complex size of CV array of 10th variable error.
1133 integer :: size11c ! Complex size of CV array of 11th variable error.
1135 integer :: size_alphac ! Size of alpha control variable (complex).
1136 integer :: size1 ! Size of CV array of 1st variable error.
1137 integer :: size2 ! Size of CV array of 2nd variable error.
1138 integer :: size3 ! Size of CV array of 3rd variable error.
1139 integer :: size4 ! Size of CV array of 4th variable error.
1140 integer :: size5 ! Size of CV array of 5th variable error.
1142 integer :: size6 ! Size of CV array of 6th variable error.
1143 integer :: size7 ! Size of CV array of 7th variable error.
1144 integer :: size8 ! Size of CV array of 8th variable error.
1145 integer :: size9 ! Size of CV array of 9th variable error.
1146 integer :: size10 ! Size of CV array of 10th variable error.
1147 integer :: size11i ! Size of CV array of 11th variable error.
1149 integer :: size1l ! Size of CV array of 1st variable lbc error.
1150 integer :: size2l ! Size of CV array of 2nd variable lbc error.
1151 integer :: size3l ! Size of CV array of 3rd variable lbc error.
1152 integer :: size4l ! Size of CV array of 4th variable lbc error.
1153 integer :: size5l ! Size of CV array of 5th variable lbc error.
1154 #if (WRF_CHEM == 1)
1155 integer,allocatable :: sizechemic (:) ! Size of CV array of chem variable error.
1156 #endif
1157 end type cv_type
1159 type qhat_type
1160 integer :: i
1161 real, allocatable:: values(:) ! qhat_type used in da_minimise_cg
1162 end type qhat_type
1164 type be_subtype
1165 integer :: mz ! Vertical truncation of errors.
1166 integer :: max_wave ! Global only - horizontal spectral truncation.
1167 character*10 :: name ! Variable name.
1168 real*8, pointer :: rf_alpha(:) ! RF scale length.
1169 real*8, pointer :: val(:,:) ! Local Standard dev./sqrt(eigenvalue).
1170 real*8, pointer :: evec(:,:,:) ! Local Vertical eigenvectors.
1171 real*8, pointer :: val_g(:) ! Global Standard dev./sqrt(eigenvalue).
1172 real*8, pointer :: evec_g(:,:) ! Global Vertical eigenvectors.
1173 real*8, pointer :: power(:,:) ! Power spectrum
1174 !_____For wavelet option:
1175 REAL, POINTER ::sd(:,:,:) ! 3D field std. dev.
1176 REAL, POINTER ::wsd(:,:,:) ! 3D wavelet std. dev.
1177 end type be_subtype
1179 type be_type
1180 integer :: ncv_mz ! number of variables for cv_mz
1181 integer, pointer :: cv_mz(:) ! array to hold mz of each cv
1182 integer :: ne
1183 integer :: max_wave ! Smallest spectral mode (global).
1184 integer :: mix
1185 integer :: mjy
1186 type (be_subtype) :: v1
1187 type (be_subtype) :: v2
1188 type (be_subtype) :: v3
1189 type (be_subtype) :: v4
1190 type (be_subtype) :: v5
1192 type (be_subtype) :: v6
1193 type (be_subtype) :: v7
1194 type (be_subtype) :: v8
1195 type (be_subtype) :: v9
1196 type (be_subtype) :: v10
1197 type (be_subtype) :: v11
1199 type (be_subtype) :: alpha
1200 real*8, pointer :: pb_vert_reg(:,:,:)
1201 #if (WRF_CHEM == 1)
1202 !integer :: ncv_mz_chem ! number of variables for cv_mz
1203 !integer, pointer :: cv_mz_chem(:) ! array to hold mz of each cv
1205 type (be_subtype),allocatable :: v12(:) ! Chem initial condition scaling factor CVs
1206 integer :: ncv_mz_chemic ! number of variables for cv_mz
1207 integer, pointer :: cv_mz_chemic(:) ! array to hold mz of each cv
1209 #endif
1211 ! Control variable space errors:
1212 type (cv_type) :: cv
1214 real, pointer :: reg_psi_chi (:,:)
1215 real, pointer :: reg_psi_t (:,:,:)
1216 real, pointer :: reg_psi_ps (:,:)
1217 real, pointer :: reg_psi_rh (:,:,:)
1218 real, pointer :: reg_chi_u_t (:,:,:)
1219 real, pointer :: reg_chi_u_ps (:,:)
1220 real, pointer :: reg_chi_u_rh (:,:,:)
1221 real, pointer :: reg_t_u_rh (:,:,:)
1222 real, pointer :: reg_ps_u_rh (:,:)
1224 !-----For cv option 3:
1225 INTEGER :: ndeg,nta
1226 REAL :: swidth
1227 REAL, POINTER :: be(:)
1228 REAL, POINTER :: rate(:)
1229 REAL, POINTER :: table(:,:)
1230 REAL, POINTER :: agvz(:,:,:,:)
1231 REAL, POINTER :: bvz(:,:,:)
1232 REAL, POINTER :: wgvz(:,:,:)
1233 REAL, POINTER :: slix(:,:,:,:)
1234 REAL, POINTER :: slipx(:,:)
1235 REAL, POINTER :: sljy(:,:,:,:)
1236 REAL, POINTER :: sljpy(:,:)
1237 REAL, POINTER :: vz(:,:,:,:)
1238 REAL, POINTER :: corz(:,:,:,:)
1239 REAL, POINTER :: corp(:,:)
1241 !_____For wavelet option:
1242 REAL, POINTER ::sd( :,:,:)! 4 3D & 1 2D field std. dev. sets.
1243 REAL, POINTER ::wsd(:,:,:)! 4 3D & 1 2D wavelet std. dev. sets.
1244 end type be_type
1246 ! Analysis_Stats maximum-minumum structure.
1248 type maxmin_field_type
1249 real :: value
1250 integer :: i, j
1251 end type maxmin_field_type
1253 ! vp_type is defined in the Registry
1254 ! x_type is defined in the Registry
1255 ! The framework allocates the (local-grid) xa structure.
1256 ! The framework allocates the (local-grid) xb structure.
1257 ! The framework (de)allocates the vv structure.
1258 ! The framework (de)allocates the vp structure.
1260 contains
1262 #include "da_allocate_background_errors.inc"
1263 #include "da_allocate_obs_info.inc"
1264 #include "da_allocate_observations.inc"
1265 #include "da_allocate_observations_rain.inc"
1266 #if (WRF_CHEM == 1)
1267 #include "da_allocate_observations_chem_sfc.inc"
1268 #endif
1269 #include "da_allocate_y.inc"
1270 #include "da_allocate_y_radar.inc"
1271 #include "da_allocate_y_lightning.inc"
1272 #include "da_allocate_y_rain.inc"
1273 #if (WRF_CHEM == 1)
1274 #include "da_allocate_y_chem_sfc.inc"
1275 #include "da_deallocate_y_chem_sfc.inc"
1276 #endif
1277 #include "da_deallocate_background_errors.inc"
1278 #include "da_deallocate_observations.inc"
1279 #include "da_deallocate_y.inc"
1280 #include "da_zero_x.inc"
1281 #include "da_zero_y.inc"
1282 #include "da_zero_vp_type.inc"
1283 #if (WRF_CHEM == 1)
1284 #include "da_zero_xchem_type.inc"
1285 #endif
1286 #include "da_initialize_cv.inc"
1287 #include "da_random_seed.inc"
1288 #include "da_gauss_noise.inc"
1290 end module da_define_structures