wrf svn trunk commit r4103
[wrffire.git] / wrfv2_fire / var / da / da_obs_io / da_read_obs_ascii.inc
blob05f75b45d345b4f4ed2bf204ed16edff3a8cd4c0
1 subroutine da_read_obs_ascii (iv, filename, uvq_direct)
3    !---------------------------------------------------------------------------
4    ! Purpose: Read a GTS observation file
5    !
6    ! Modifications:      10/26/2004            Syed RH Rizvi
7    !
8    !              Fix Obs-Long as -180 if it is +180
9    !
10    !      Date:  03/04/2005 -       Syed  RH  Rizvi
11    !
12    !      (a)  AMVs from Geostationary and Polar orbiting satellite are
13    !           seperated & used as profile. Currently there is a provision
14    !           to use MODIS winds only.
15    !      (b)  MODIS obs error are currently assigned through namelist
16    !           parameter (modis_cmv_error)
17    !
18    !                     03/30/2005           Syed RH Rizvi
19    !              For global option duplicate obs at East/West boundary
20    !                        
21    !                     08/30/2005           Syed RH Rizvi
22    !           Writing original errors & thicknesses
23    !           desired for outputting QC obs with NTMAX = 0
24    !
25    !       Date: 02/28/2008 -        Y.-R. Guo
26    !
27    !           Satem thickness error should not be divided by gravity because
28    !           the unit from obsproc is already meter, not geopotential meter.
29    !
30    !       Date: 03/19/2009 -        Y.-R. Guo
31    !
32    !           Added the time range check when reading in observations.
33    !---------------------------------------------------------------------------
35    implicit none
37    type (iv_type),    intent(inout) :: iv
38    character(len=*),  intent(in)    :: filename
40    character (len =  10)        :: fmt_name
42    character (len = 160)        :: info_string
44 !   character (len = 160)        :: fmt_info, fmt_srfc, fmt_each
46    integer                      :: i, j, iost, nlevels, old_nlevels, fm,iunit
48    type (multi_level_type)      :: platform
50    logical                      :: outside
51    logical                      :: outside_all
52    logical                      :: uvq_direct               ![cys_add]
53    integer                      :: surface_level
54    real                         :: height_error, u_comp, v_comp
55    integer                      :: nlocal(num_ob_indexes)
56    integer                      :: ntotal(num_ob_indexes)
58    integer                      :: ndup, n, report, obs_index
60    real                  :: obs_time
61    integer               :: iyear, imonth, iday, ihour, imin
63    if (trace_use) call da_trace_entry("da_read_obs_ascii")
65    ! Local counts of obs, initialise from end of last file
67    nlocal(:) = iv%info(:)%plocal(iv%time-1)
68    ntotal(:) = iv%info(:)%ptotal(iv%time-1)
70    ! open file
71    ! =========
73    call da_get_unit(iunit)
74    open(unit   = iunit,     &
75       FILE   = trim(filename), &
76       FORM   = 'FORMATTED',  &
77       ACCESS = 'SEQUENTIAL', &
78       iostat =  iost,     &
79       STATUS = 'OLD')
81    if (iost /= 0) then
82       write(unit=message(1),fmt='(A,I5,A)') &
83          "Error",iost," opening gts obs file "//trim(filename)
84       call da_warning(__FILE__,__LINE__,message(1:1))
85       call da_free_unit(iunit)
86       if (trace_use) call da_trace_exit("da_read_obs_ascii")
87       return
88    end if
90    ! read header
91    ! ===========
93    do
94       read (unit = iunit, fmt = '(A)', iostat = iost) info_string
95       if (iost /= 0) then
96          call da_warning(__FILE__,__LINE__, &
97             (/"Problem reading gts obs header, skipping file"/))
98          if (trace_use) call da_trace_exit("da_read_obs_ascii")
99          return
100       end if
102       if (info_string(1:6) == 'EACH  ') exit
103    end do
105    !  read formats
106    !  ------------
108    read (iunit, fmt = '(A,1X,A)', iostat = iost) &
109       fmt_name, fmt_info, &
110       fmt_name, fmt_srfc,  &
111       fmt_name, fmt_each
113    if (iost /= 0) then
114       call da_warning(__FILE__,__LINE__, &
115          (/"Problem reading gts obs file, skipping"/))
116          if (trace_use) call da_trace_exit("da_read_obs_ascii")
117       return
118    end if
120    if (print_detail_obs) then
121       write(unit=stdout, fmt='(2a)') &
122          'fmt_info=', fmt_info, &
123          'fmt_srfc =', fmt_srfc,  &
124          'fmt_each=', fmt_each
125    end if
127    ! skip line
128    ! ----------
130    ![cys_change]
131    ! read (iunit, fmt = '(a)') fmt_name
132    read (iunit, fmt = '(a)') info_string
133    if (info_string(1:21) == 'MODIFIED FILTERED OBS') then
134       uvq_direct=.true.
135    else
136       uvq_direct=.false.
137    endif
139    ! loop over records
140    ! -----------------
142    report = 0 ! report number in file
144    reports: &
145    do
147       report = report+1
149       ! read station general info
150       ! =============================
152       read (iunit, fmt = fmt_info, iostat = iost) &
153          platform%info%platform,    &
154          platform%info%date_char,   &
155          platform%info%name,        &
156          platform%info%levels,      &
157          platform%info%lat,         &
158          platform%info%lon,         &
159          platform%info%elv,         &
160          platform%info%id
162       if (iost /= 0) then
163          ! FIX? This is expected, but its unclear how we handle failure
164          ! here without assuming the fortran2003 convention on
165          ! error statuses
166          exit reports
167       end if
169       if (print_detail_obs) then
170          write(unit=stdout, fmt=fmt_info) &
171             platform%info%platform,    &
172             platform%info%date_char,   &
173             platform%info%name,        &
174             platform%info%levels,      &
175             platform%info%lat,         &
176             platform%info%lon,         &
177             platform%info%elv,         &
178             platform%info%id
179       end if
181       if (platform%info%lon == 180.0  ) platform%info%lon =-180.000 
182       ! Fix funny wind direction at Poles
183       if (platform%info%lat < -89.9999 .or. platform%info%lat > 89.9999) then
184          platform%info%lon = 0.0
185       end if
187       if (platform%info%platform(6:6) == ' ') then
188          read(platform%info%platform(4:5), '(I2)') fm
189       else
190          read(platform%info%platform(4:6), '(I3)') fm
191       end if
193       ! read model location
194       ! =========================
196       read (iunit, fmt = fmt_srfc)  &
197          platform%loc%slp%inv, platform%loc%slp%qc, platform%loc%slp%error, &
198          platform%loc%pw%inv, platform%loc%pw%qc, platform%loc%pw%error
200       ! levels < 1 and .not.GPSPW and .not.GPSZD, go back to reports
202       if ((platform%info%levels < 1) .AND.   &
203          ( (index(platform%info%platform, 'GPSPW') <= 0) .and. &
204            (index(platform%info%platform, 'GPSZD') <= 0) )) then
205          cycle reports
206       end if
208       ! read each level
209       ! ---------------
211       do i = 1, platform%info%levels
212          platform%each (i) = each_level_type(missing_r, missing, -1.0, & ! height
213             field_type(missing_r, missing, missing_r, missing, missing_r), & ! u
214             field_type(missing_r, missing, missing_r, missing, missing_r), & ! v
215             field_type(missing_r, missing, missing_r, missing, missing_r), & ! p
216             field_type(missing_r, missing, missing_r, missing, missing_r), & ! t
217             field_type(missing_r, missing, missing_r, missing, missing_r), & ! q
218             field_type(missing_r, missing, missing_r, missing, missing_r), & ! rh
219             field_type(missing_r, missing, missing_r, missing, missing_r), & ! td
220             field_type(missing_r, missing, missing_r, missing, missing_r))  ! speed
222          read (unit = iunit, fmt = trim (fmt_each)) &
223             platform%each(i)%p%inv, platform%each(i)%p%qc, platform%each(i)%p%error, &
224             platform%each(i)%speed%inv, platform%each(i)%speed%qc, &
225             platform%each(i)%speed%error, &
226             ! Here the 'direction' is stored in platform%each (i)%v:
227             platform%each(i)%v%inv, platform%each(i)%v%qc, platform%each(i)%v%error, &
228             platform%each(i)%height,       &
229             platform%each(i)%height_qc,    &
230             height_error,                  &
231             platform%each(i)%t%inv, platform%each(i)%t%qc, platform%each(i)%t%error, &
232             platform%each(i)%td%inv, platform%each(i)%td%qc, platform%each(i)%td%error, &
233             platform%each(i)%rh%inv, platform%each(i)%rh%qc, platform%each(i)%rh%error
235 ! cys_add
236          if (uvq_direct) then
237             platform%each (i)%u = platform%each (i)%speed
238             if (platform%each(i)%rh%inv .gt. missing_r)  &
239                platform%each(i)%rh%inv=platform%each(i)%rh%inv / 1e3    !convert back to kg/kg
240             if (platform%each(i)%rh%error .gt. 0.0)  &
241                platform%each(i)%rh%error=platform%each(i)%rh%error / 1e3  !convert back to kg/kg
242          end if
243 ! cys_add
245          if (print_detail_obs) then
246             write(unit=stdout, fmt = '(a, i6)') 'i=', i
247 ! because now the field_type included: inv, qc, error, sens, and imp (YRG, 02/23/2009):              
248             write(unit=stdout, fmt = trim (fmt_each)) &
249                platform%each(i)%p%inv, platform%each(i)%p%qc, platform%each(i)%p%error, &
250                platform%each(i)%speed%inv, platform%each(i)%speed%qc, &
251                platform%each(i)%speed%error,  &
252                platform%each(i)%v%inv, platform%each(i)%v%qc, platform%each(i)%v%error, &
253                platform%each(i)%height,       &
254                platform%each(i)%height_qc,    &
255                height_error,                  &
256                platform%each(i)%t%inv, platform%each(i)%t%qc, platform%each(i)%t%error, &
257                platform%each(i)%td%inv, platform%each(i)%td%qc, platform%each(i)%td%error, &
258                platform%each(i)%rh%inv, platform%each(i)%rh%qc, platform%each(i)%rh%error
259          end if
261          ! Uncomment the following if errors in reported heights (test later):             
262          ! if (fm == 97 .or. fm == 96 .or. fm == 42) then
263          !    platform%each (i)%height_qc = -5 ! Aircraft heights are not above surface.
264          ! end if
266          ! To convert the wind speed and direction to 
267          !      the model wind components: u, v
269          if (.not. uvq_direct) then   !cys_add
270          if (platform%each (i)%speed%qc /= missing_data .and. &
271              platform%each (i)%v%qc /= missing_data) then
272             call da_ffdduv (platform%each (i)%speed%inv, platform%each (i)%v%inv,     &
273                U_comp, V_comp, platform%info%lon, convert_fd2uv)
274                platform%each (i)%u = platform%each (i)%speed
275                platform%each (i)%v = platform%each (i)%speed
276             platform%each (i)%u%inv = U_comp
277             platform%each (i)%v%inv = V_comp
278          else
279             platform%each (i)%u%inv   = missing_r
280             platform%each (i)%v%inv   = missing_r
281             platform%each (i)%u%error = missing_r
282             platform%each (i)%v%error = missing_r
283             platform%each (i)%u%qc    = missing_data
284             platform%each (i)%v%qc    = missing_data
285          end if
286          end if   !cys_add
287       end do
289       ! Check if outside of the time range:
291       read (platform%info%date_char,'(i4,4(1x,i2))') &
292                                     iyear, imonth, iday, ihour, imin
293       call da_get_julian_time (iyear,imonth,iday,ihour,imin,obs_time)
294       if ( obs_time < time_slots(0) .or. &
295            obs_time >= time_slots(num_fgat_time) ) then
296          if (print_detail_obs) then
297            write(unit=stdout, fmt='(a)') '*** Outside of the time range:'
298            write(unit=stdout, fmt=fmt_info) &
299             platform%info%platform,    &
300             platform%info%date_char,   &
301             platform%info%name,        &
302             platform%info%levels,      &
303             platform%info%lat,         &
304             platform%info%lon,         &
305             platform%info%elv,         &
306             platform%info%id
307          end if
308          cycle
309       endif
311       ! Restrict to a range of reports, useful for debugging
313       if (report < report_start) then
314          cycle
315       end if
317       if (report > report_end) then
318          exit
319       end if
321       call da_llxy (platform%info, platform%loc, outside, outside_all)
323       if (outside_all) then
324          cycle reports
325       end if
327       if (print_detail_obs) then
328          ! Simplistic approach, could be improved to get it all done on PE 0
329          if (.NOT. outside) then
330             write(unit=stdout,fmt='(A,I5,A,F8.2,A,F8.2,A,I3,A,2F8.2)') &
331                "Report",report," at",platform%info%lon,"E",platform%info%lat, &
332                "N on processor", myproc,", position", platform%loc%x,platform%loc%y
333          end if
334       end if
336       nlevels = platform%info%levels
337       if (nlevels > max_ob_levels) then
338          nlevels = max_ob_levels
339          write(unit=message(1), fmt='(/4(2a,2x),a,2f8.2,2x,2(a,f9.2,2x),2(a,i4,2x)/)') &
340             'Station: ', trim(platform%info%name), &
341             'ID: ', trim(platform%info%id), &
342             'Platform: ', trim(platform%info%platform), &
343             'Date: ', trim(platform%info%date_char), &
344             'At Loc(lat, lon): ', platform%info%lat, platform%info%lon, &
345             'At elv: ', platform%info%elv, &
346             'with pstar: ', platform%info%pstar, &
347             'Has level: ', platform%info%levels, &
348             'which is great than max_ob_levels: ', max_ob_levels
350          write (unit=message(2), fmt = '(A,1X,A,1X,A,1X,I4,2f9.3,f9.1,1X,A)') &
351             platform%info%name,        &
352             platform%info%platform,    &
353             platform%info%date_char,   &
354             platform%info%levels,      &
355             platform%info%lat,         &
356             platform%info%lon,         &
357             platform%info%elv,         &
358             platform%info%id
359          call da_warning(__FILE__,__LINE__,message(1:2))
361          platform%info%levels = nlevels
362       else if (nlevels < 1) then
363          ! Not GPSPW and GPSZD data:
364          if (fm /= 111 .and. fm /= 114) then
365             cycle reports
366          end if
367       end if
369       if (fm /= 86) call da_obs_proc_station(platform,fm,uvq_direct)  !cys_change
371       nlevels = platform%info%levels
372       ! Loop over duplicating obs for global
373       ndup = 1
374       if (global .and. (platform%loc%i < ids .or. platform%loc%i >= ide)) ndup= 2
376       ! It is possible that logic for counting obs is incorrect for the 
377       ! global case with >1 MPI tasks due to obs duplication, halo, etc.  
378       ! TBH:  20050913
380       if (.not.outside) then
381          if (print_detail_obs .and. ndup > 1) then
382             write(unit=stdout, fmt = fmt_info) &
383                platform%info%platform,    &
384                platform%info%date_char,   &
385                platform%info%name,        &
386                platform%info%levels,      &
387                platform%info%lat,         &
388                platform%info%lon,         &
389                platform%info%elv,         &
390                platform%info%id
392             write(unit=stdout, fmt = '(a,2i5,4e20.10)') &
393                ' duplicating obs since loc% i,j,dx,dxm,dy & dym ', &
394                platform%loc%i,  platform%loc%j,   &
395                platform%loc%dx, platform%loc%dxm, &
396               platform%loc%dy, platform%loc%dym
397          end if
398       end if
399       
400       obs_index = fm_index(fm)
402       dup_loop: do n = 1, ndup
403          select case(fm)
405          case (12) ;
406             if (.not. use_synopobs) cycle reports
407             if (n==1) ntotal(synop) = ntotal(synop)+1
408             if (outside) cycle reports
409             nlocal(synop) = nlocal(synop) + 1
410             if (nlocal(synop) > iv%info(synop)%nlocal) cycle reports
412             iv%synop(nlocal(synop))%h = platform%each(1)%height
413             iv%synop(nlocal(synop))%u = platform%each(1)%u
414             iv%synop(nlocal(synop))%v = platform%each(1)%v
415             iv%synop(nlocal(synop))%t = platform%each(1)%t
416             iv%synop(nlocal(synop))%q = platform%each(1)%q
417             iv%synop(nlocal(synop))%p = platform%each(1)%p
419          case (13, 17) ;                  ! ships 
420             if (.not. use_shipsobs) cycle reports
421             if (n==1) ntotal(ships) = ntotal(ships) + 1 
422             if (outside) cycle reports
423             nlocal(ships) = nlocal(ships) + 1
424             if (nlocal(ships) > iv%info(ships)%nlocal) cycle reports
426             iv%ships(nlocal(ships))%h = platform%each(1)%height
427             iv%ships(nlocal(ships))%u = platform%each(1)%u
428             iv%ships(nlocal(ships))%v = platform%each(1)%v
429             iv%ships(nlocal(ships))%t = platform%each(1)%t
430             iv%ships(nlocal(ships))%p = platform%each(1)%p
431             iv%ships(nlocal(ships))%q = platform%each(1)%q
433          case (15:16) ;
434             if (.not. use_metarobs) cycle reports
435             if (n==1) ntotal(metar) = ntotal(metar) + 1 
436             if (outside) cycle reports
437             nlocal(metar) = nlocal(metar) + 1
438             if (nlocal(metar) > iv%info(metar)%nlocal) cycle reports
440             iv%metar(nlocal(metar))%h = platform%each(1)%height
441             iv%metar(nlocal(metar))%u = platform%each(1)%u
442             iv%metar(nlocal(metar))%v = platform%each(1)%v
443             iv%metar(nlocal(metar))%t = platform%each(1)%t
444             iv%metar(nlocal(metar))%p = platform%each(1)%p
445             iv%metar(nlocal(metar))%q = platform%each(1)%q
447          case (32:34) ;
448             if (.not. use_pilotobs) cycle reports
449             if (n==1) ntotal(pilot) = ntotal(pilot) + 1 
450             if (outside) cycle reports
451             nlocal(pilot) = nlocal(pilot) + 1
452             if (nlocal(pilot) > iv%info(pilot)%nlocal) cycle reports
454             allocate (iv%pilot(nlocal(pilot))%h (1:nlevels))
455             allocate (iv%pilot(nlocal(pilot))%p (1:nlevels))
456             allocate (iv%pilot(nlocal(pilot))%u (1:nlevels))
457             allocate (iv%pilot(nlocal(pilot))%v (1:nlevels))
459             do i = 1, nlevels
460               iv%pilot(nlocal(pilot))%h(i) = platform%each(i)%height
461               iv%pilot(nlocal(pilot))%p(i) = platform%each(i)%p%inv
462               iv%pilot(nlocal(pilot))%u(i) = platform%each(i)%u
463               iv%pilot(nlocal(pilot))%v(i) = platform%each(i)%v
464             end do
466          case (35:38) ;
467             if (.not. use_soundobs) cycle reports
468             if (n==1) ntotal(sound) = ntotal(sound) + 1 
469             if (n==1) ntotal(sonde_sfc) = ntotal(sonde_sfc) + 1 
470             if (outside) cycle reports
471             nlocal(sound) = nlocal(sound) + 1
472             nlocal(sonde_sfc) = nlocal(sonde_sfc) + 1
473             if (nlocal(sound) > iv%info(sound)%nlocal) cycle reports
475             ! Search to see if we have surface obs.
477             surface_level = 0
479             do i = 1, nlevels
480                ! if (elevation and height are the same, it is surface.)
481                if (abs(platform%info%elv - platform%each(i)%height) < 0.1) then
482                   surface_level = i
484                   ! Save surface pressure.
485                   iv%sonde_sfc(nlocal(sonde_sfc))%h = platform%each(i)%height
486                   iv%sonde_sfc(nlocal(sonde_sfc))%u = platform%each(i)%u
487                   iv%sonde_sfc(nlocal(sonde_sfc))%v = platform%each(i)%v
488                   iv%sonde_sfc(nlocal(sonde_sfc))%t = platform%each(i)%t
489                   iv%sonde_sfc(nlocal(sonde_sfc))%q = platform%each(i)%q
490                   iv%sonde_sfc(nlocal(sonde_sfc))%p = platform%each(i)%p
492                   exit
493                end if
494             end do
496             ! processing the sonde_sfc data:
498             old_nlevels = nlevels
500             if (surface_level > 0) then
501                nlevels = nlevels - 1
502             else
503                iv%sonde_sfc(nlocal(sonde_sfc))%h = missing_r
504                iv%sonde_sfc(nlocal(sonde_sfc))%u%inv   = missing_r
505                iv%sonde_sfc(nlocal(sonde_sfc))%u%qc    = missing
506                iv%sonde_sfc(nlocal(sonde_sfc))%u%error = abs(missing_r)
507                iv%sonde_sfc(nlocal(sonde_sfc))%v = iv%sonde_sfc(nlocal(sonde_sfc))%u
508                iv%sonde_sfc(nlocal(sonde_sfc))%t = iv%sonde_sfc(nlocal(sonde_sfc))%u
509                iv%sonde_sfc(nlocal(sonde_sfc))%p = iv%sonde_sfc(nlocal(sonde_sfc))%u
510                iv%sonde_sfc(nlocal(sonde_sfc))%q = iv%sonde_sfc(nlocal(sonde_sfc))%u
511             end if
513             if (nlevels > 0) then
515                allocate (iv%sound(nlocal(sound))%h (1:nlevels))
516                allocate (iv%sound(nlocal(sound))%p (1:nlevels))
517                allocate (iv%sound(nlocal(sound))%u (1:nlevels))
518                allocate (iv%sound(nlocal(sound))%v (1:nlevels))
519                allocate (iv%sound(nlocal(sound))%t (1:nlevels))
520                allocate (iv%sound(nlocal(sound))%q (1:nlevels))
522                j = 0
523 !               do i = 1, iv%sound(nlocal(sound))%info%levels
524                do i = 1, old_nlevels
525                   if (i == surface_level) cycle
527                   j=j+1
529                   iv%sound(nlocal(sound))%h(j) = platform%each(i)%height
530                   iv%sound(nlocal(sound))%p(j) = platform%each(i)%p%inv
531                   iv%sound(nlocal(sound))%u(j) = platform%each(i)%u
532                   iv%sound(nlocal(sound))%v(j) = platform%each(i)%v
533                   iv%sound(nlocal(sound))%t(j) = platform%each(i)%t
534                   iv%sound(nlocal(sound))%q(j) = platform%each(i)%q
535                end do
536             end if
538 !            iv%sound(nlocal(sound))%info%levels = nlevels
539          case (101) ;
540             if (.not. use_tamdarobs) cycle reports
541             if (n==1) ntotal(tamdar) = ntotal(tamdar) + 1
542             if (n==1) ntotal(tamdar_sfc) = ntotal(tamdar_sfc) + 1
543             if (outside) cycle reports
544             nlocal(tamdar) = nlocal(tamdar) + 1
545             nlocal(tamdar_sfc) = nlocal(tamdar_sfc) + 1
546             if (nlocal(tamdar) > iv%info(tamdar)%nlocal) cycle reports
547             ! Search to see if we have surface obs.
549             surface_level = 0
551             do i = 1, nlevels
552                ! if (elevation and height are the same, it is surface.)
553                if (abs(platform%info%elv - platform%each(i)%height) < 0.1) then
554                   surface_level = i
556                   ! Save surface pressure.
557                   iv%tamdar_sfc(nlocal(tamdar_sfc))%h = platform%each(i)%height
558                   iv%tamdar_sfc(nlocal(tamdar_sfc))%u = platform%each(i)%u
559                   iv%tamdar_sfc(nlocal(tamdar_sfc))%v = platform%each(i)%v
560                   iv%tamdar_sfc(nlocal(tamdar_sfc))%t = platform%each(i)%t
561                   iv%tamdar_sfc(nlocal(tamdar_sfc))%q = platform%each(i)%q
562                   iv%tamdar_sfc(nlocal(tamdar_sfc))%p = platform%each(i)%p
563                   exit
564                end if
565             end do
566             ! processing the tamdar_sfc data:
568             old_nlevels = nlevels
570            if (surface_level > 0) then
571                nlevels = nlevels - 1
572             else
573                iv%tamdar_sfc(nlocal(tamdar_sfc))%h = missing_r
574                iv%tamdar_sfc(nlocal(tamdar_sfc))%u%inv   = missing_r
575                iv%tamdar_sfc(nlocal(tamdar_sfc))%u%qc    = missing
576                iv%tamdar_sfc(nlocal(tamdar_sfc))%u%error = abs(missing_r)
577                iv%tamdar_sfc(nlocal(tamdar_sfc))%v = iv%tamdar_sfc(nlocal(tamdar_sfc))%u
578                iv%tamdar_sfc(nlocal(tamdar_sfc))%t = iv%tamdar_sfc(nlocal(tamdar_sfc))%u
579                iv%tamdar_sfc(nlocal(tamdar_sfc))%p = iv%tamdar_sfc(nlocal(tamdar_sfc))%u
580                iv%tamdar_sfc(nlocal(tamdar_sfc))%q = iv%tamdar_sfc(nlocal(tamdar_sfc))%u
581             end if
583             if (nlevels > 0) then
585                allocate (iv%tamdar(nlocal(tamdar))%h (1:nlevels))
586                allocate (iv%tamdar(nlocal(tamdar))%p (1:nlevels))
587                allocate (iv%tamdar(nlocal(tamdar))%u (1:nlevels))
588                allocate (iv%tamdar(nlocal(tamdar))%v (1:nlevels))
589                allocate (iv%tamdar(nlocal(tamdar))%t (1:nlevels))
590                allocate (iv%tamdar(nlocal(tamdar))%q (1:nlevels))
592                j = 0
593                do i = 1, nlevels
595                   j=j+1
597                   iv%tamdar(nlocal(tamdar))%h(j) = platform%each(i)%height
598                   iv%tamdar(nlocal(tamdar))%p(j) = platform%each(i)%p%inv
599                   iv%tamdar(nlocal(tamdar))%u(j) = platform%each(i)%u
600                   iv%tamdar(nlocal(tamdar))%v(j) = platform%each(i)%v
601                   iv%tamdar(nlocal(tamdar))%t(j) = platform%each(i)%t
602                   iv%tamdar(nlocal(tamdar))%q(j) = platform%each(i)%q
603                  if(iv%tamdar(nlocal(tamdar))%q(j)%inv.ne.missing_r)then
604                  iv%tamdar(nlocal(tamdar))%q(j)%inv = iv%tamdar(nlocal(tamdar))%q(j)%inv
605                  endif
606                  if(iv%tamdar(nlocal(tamdar))%q(j)%error.ne.missing_r)then
607                  iv%tamdar(nlocal(tamdar))%q(j)%error = iv%tamdar(nlocal(tamdar))%q(j)%error
608                  endif
610                end do
611             else
612                nlevels = 1
613                allocate (iv%tamdar(nlocal(tamdar))%h (1:nlevels))
614                allocate (iv%tamdar(nlocal(tamdar))%p (1:nlevels))
615                allocate (iv%tamdar(nlocal(tamdar))%u (1:nlevels))
616                allocate (iv%tamdar(nlocal(tamdar))%v (1:nlevels))
617                allocate (iv%tamdar(nlocal(tamdar))%t (1:nlevels))
618                allocate (iv%tamdar(nlocal(tamdar))%q (1:nlevels))
619                j=1
620                iv%tamdar(nlocal(tamdar))%h = missing_r
621                iv%tamdar(nlocal(tamdar))%p = missing_r
622                iv%tamdar(nlocal(tamdar))%u%inv   = missing_r
623                iv%tamdar(nlocal(tamdar))%u%qc    = missing
624                iv%tamdar(nlocal(tamdar))%u%error = abs(missing_r)
625                iv%tamdar(nlocal(tamdar))%v = iv%tamdar(nlocal(tamdar))%u
626                iv%tamdar(nlocal(tamdar))%t = iv%tamdar(nlocal(tamdar))%u
627                iv%tamdar(nlocal(tamdar))%q = iv%tamdar(nlocal(tamdar))%u
629             end if
630       
631          case (161) ;
632             if (.not. use_mtgirsobs) cycle reports
633             if (n==1) ntotal(mtgirs) = ntotal(mtgirs) + 1
634             if (outside) cycle reports
635             nlocal(mtgirs) = nlocal(mtgirs) + 1
636             if (nlocal(mtgirs) > iv%info(mtgirs)%nlocal) cycle reports
638             if (nlevels > 0) then
640                allocate (iv%mtgirs(nlocal(mtgirs))%h (1:nlevels))
641                allocate (iv%mtgirs(nlocal(mtgirs))%p (1:nlevels))
642                allocate (iv%mtgirs(nlocal(mtgirs))%u (1:nlevels))
643                allocate (iv%mtgirs(nlocal(mtgirs))%v (1:nlevels))
644                allocate (iv%mtgirs(nlocal(mtgirs))%t (1:nlevels))
645                allocate (iv%mtgirs(nlocal(mtgirs))%q (1:nlevels))
647                j = 0
648                do i = 1, nlevels 
650                   j=j+1
652                   iv%mtgirs(nlocal(mtgirs))%h(j) = platform%each(i)%height
653                   iv%mtgirs(nlocal(mtgirs))%p(j) = platform%each(i)%p%inv
654                   iv%mtgirs(nlocal(mtgirs))%u(j) = platform%each(i)%u
655                   iv%mtgirs(nlocal(mtgirs))%v(j) = platform%each(i)%v
656                   iv%mtgirs(nlocal(mtgirs))%t(j) = platform%each(i)%t
657                   iv%mtgirs(nlocal(mtgirs))%q(j) = platform%each(i)%q
658                  if(iv%mtgirs(nlocal(mtgirs))%q(j)%inv.ne.missing_r)then
659                  iv%mtgirs(nlocal(mtgirs))%q(j)%inv = iv%mtgirs(nlocal(mtgirs))%q(j)%inv/1000.0
660                  endif
661                  if(iv%mtgirs(nlocal(mtgirs))%q(j)%error.ne.missing_r)then
662                  iv%mtgirs(nlocal(mtgirs))%q(j)%error = iv%mtgirs(nlocal(mtgirs))%q(j)%error/1000.0/100.0
663                  endif
665                end do
666             end if
669          case (86)    ;
670             ! Reject cloudy satem obs.
671             if (.not. use_satemobs .or. platform%loc%pw%inv > 10.0) cycle reports
672             if (n==1) ntotal(satem) = ntotal(satem) + 1 
673             if (outside) cycle reports
674             nlocal(satem) = nlocal(satem) + 1
675             if (nlocal(satem) > iv%info(satem)%nlocal) cycle reports
677             ! The satem ref_p is put in the SLP position in OBSPROC data stream.
679             iv%satem(nlocal(satem))%ref_p= platform%loc%slp%inv
681             allocate (iv%satem(nlocal(satem))%p        (1:nlevels))
682             allocate (iv%satem(nlocal(satem))%thickness(1:nlevels))
683             allocate (iv%satem(nlocal(satem))%org_thickness(1:nlevels))
685             iv%satem(nlocal(satem))%p(1) = platform%each(1)%p%inv
686             iv%satem(nlocal(satem))%thickness(1) = platform%each(1)%t
687             !  write original thickness errors for filtered obs
688             if (anal_type_qcobs) then
689                do i = 1, nlevels
690                   iv%satem(nlocal(satem))%org_thickness(i) = platform%each(i)%t
691                end do 
692             end if
694             ! Splitting the reported satem data into smaller layers.
696             do i = 2, nlevels
697                iv%satem(nlocal(satem))%p(i) = platform%each(i)%p%inv
698                iv%satem(nlocal(satem))%thickness(i) = platform%each(i)%t
699                if (platform%each(i)%t%qc /= missing_data   .and. &
700                   platform%each(i-1)%t%qc /= missing_data) then
701                   iv%satem(nlocal(satem))%thickness(i)%inv =            &
702                   platform%each(i)%t%inv - platform%each(i-1)%t%inv
703                else
704                   iv%satem(nlocal(satem))%thickness(i)%inv = missing_r
705                   iv%satem(nlocal(satem))%thickness(i)%qc  = missing_data
706                end if
707             end do
709             ! Thickness error (m):
711             do i = nlevels, 2, -1
712                iv%satem(nlocal(satem))%thickness(i)%error = &
713                sqrt(iv%satem(nlocal(satem))%thickness(i )%error ** 2 + &
714                   iv%satem(nlocal(satem))%thickness(i-1)%error ** 2) 
715 !                  iv%satem(nlocal(satem))%thickness(i-1)%error ** 2) / gravity
716             end do
718             iv%satem(nlocal(satem))%thickness(1)%error = &
719                            sqrt(iv%satem(nlocal(satem))%thickness(1)%error ** 2 + &
720                            platform%loc%pw%error ** 2) 
721 !                           platform%loc%pw%error ** 2) / gravity
723             ! Geostationary ot Polar orbitting Satellite AMVs:
725          case (88)    ;
726             if (index(platform%info%name, 'MODIS') > 0 .or. &
727                index(platform%info%name, 'modis') > 0)  then
728                if (.not. use_polaramvobs) cycle reports
729                if (n==1) ntotal(polaramv) = ntotal(polaramv) + 1 
730                if (outside) cycle reports
731                nlocal(polaramv) = nlocal(polaramv) + 1
732                if (nlocal(polaramv) > iv%info(polaramv)%nlocal) cycle reports
734                allocate (iv%polaramv(nlocal(polaramv))%p (1:nlevels))
735                allocate (iv%polaramv(nlocal(polaramv))%u (1:nlevels))
736                allocate (iv%polaramv(nlocal(polaramv))%v (1:nlevels))
738                do i = 1, nlevels
739                   iv%polaramv(nlocal(polaramv))%p(i) = platform%each(i)%p%inv
740                   iv%polaramv(nlocal(polaramv))%u(i) = platform%each(i)%u
741                   iv%polaramv(nlocal(polaramv))%v(i) = platform%each(i)%v
742                end do
743                obs_index = polaramv ! geoamv is the fm_index value for 88
744             else
745                if (.not. use_geoamvobs) cycle reports
746                if (n==1) ntotal(geoamv) = ntotal(geoamv) + 1 
747                if (outside) cycle reports
748                nlocal(geoamv) = nlocal(geoamv) + 1
749                if (nlocal(geoamv) > iv%info(geoamv)%nlocal) cycle reports
751                allocate (iv%geoamv(nlocal(geoamv))%p (1:nlevels))
752                allocate (iv%geoamv(nlocal(geoamv))%u (1:nlevels))
753                allocate (iv%geoamv(nlocal(geoamv))%v (1:nlevels))
755                do i = 1, nlevels
756                   iv%geoamv(nlocal(geoamv))%p(i) = platform%each(i)%p%inv
757                   iv%geoamv(nlocal(geoamv))%u(i) = platform%each(i)%u
758                   iv%geoamv(nlocal(geoamv))%v(i) = platform%each(i)%v
759                end do
760             end if
762          case (42,96:97) ;
763             if (.not. use_airepobs) cycle reports
764             if (n==1) ntotal(airep) = ntotal(airep) + 1 
765             if (outside) cycle reports
766             nlocal(airep) = nlocal(airep) + 1
767             if (nlocal(airep) > iv%info(airep)%nlocal) cycle reports
769             allocate (iv%airep(nlocal(airep))%h        (1:nlevels))
770             allocate (iv%airep(nlocal(airep))%p        (1:nlevels))
771             allocate (iv%airep(nlocal(airep))%u        (1:nlevels))
772             allocate (iv%airep(nlocal(airep))%v        (1:nlevels))
773             allocate (iv%airep(nlocal(airep))%t        (1:nlevels))
775             do i = 1, nlevels
776                iv%airep(nlocal(airep))%h(i) = platform%each(i)%height
777                iv%airep(nlocal(airep))%p(i) = platform%each(i)%p%inv
778                iv%airep(nlocal(airep))%u(i) = platform%each(i)%u
779                iv%airep(nlocal(airep))%v(i) = platform%each(i)%v
780                iv%airep(nlocal(airep))%t(i) = platform%each(i)%t
781             end do
783          case (111, 114) ;
784             if(.not.use_GpspwObs  .and. fm == 111) cycle reports
785             if(.not.use_GpsztdObs .and. fm == 114) cycle reports
787             if (n==1) ntotal(gpspw) = ntotal(gpspw) + 1 
788             if (outside) cycle reports
789             nlocal(gpspw) = nlocal(gpspw) + 1
790             if (nlocal(gpspw) > iv%info(gpspw)%nlocal) cycle reports
792             iv%gpspw(nlocal(gpspw))%tpw  = platform%loc%pw
794          case (116) ;
795             if (.not. use_gpsrefobs) cycle reports
796             if (n==1) ntotal(gpsref) = ntotal(gpsref) + 1 
797             if (outside) cycle reports
798             nlocal(gpsref) = nlocal(gpsref) + 1
799             if (nlocal(gpsref) > iv%info(gpsref)%nlocal) cycle reports
801             allocate (iv%gpsref(nlocal(gpsref))%h (1:nlevels))
802             allocate (iv%gpsref(nlocal(gpsref))%ref(1:nlevels))
803             allocate (iv%gpsref(nlocal(gpsref))%  p(1:nlevels))
804             allocate (iv%gpsref(nlocal(gpsref))%  t(1:nlevels))
805             allocate (iv%gpsref(nlocal(gpsref))%  q(1:nlevels))
807             do i = 1, nlevels
808                iv%gpsref(nlocal(gpsref))%h(i)   = platform%each(i)%height
810                ! In OBSPROC, use "td" field to store "gpsref"
811                iv%gpsref(nlocal(gpsref))%ref(i) = platform%each(i)%td
812                ! Keep the retrieved p and t (and q) as "field_type":   
813                iv%gpsref(nlocal(gpsref))%p(i)   = platform%each(i)%p
814                iv%gpsref(nlocal(gpsref))%t(i)   = platform%each(i)%t
815                iv%gpsref(nlocal(gpsref))%q(i)   = platform%each(i)%q
816             end do
818          case (121) ;
819             if (.not. use_ssmt1obs) cycle reports
820             if (n==1) ntotal(ssmt1) = ntotal(ssmt1) + 1 
821             if (outside) cycle reports
822             nlocal(ssmt1) = nlocal(ssmt1) + 1
823             if (nlocal(ssmt1) > iv%info(ssmt2)%nlocal) cycle reports
825             allocate (iv%ssmt1(nlocal(ssmt1))%h (1:nlevels))
826             allocate (iv%ssmt1(nlocal(ssmt1))%p (1:nlevels))
827             allocate (iv%ssmt1(nlocal(ssmt1))%t (1:nlevels))
829             do i = 1, nlevels
830               iv%ssmt1(nlocal(ssmt1))%h(i) = platform%each(i)%height
831               iv%ssmt1(nlocal(ssmt1))%p(i) = platform%each(i)%p%inv
832               iv%ssmt1(nlocal(ssmt1))%t(i) = platform%each(i)%t
833             end do
834          
835          case (122) ;
836             if (.not. use_ssmt2obs) cycle reports
837             if (n==1) ntotal(ssmt2) = ntotal(ssmt2) + 1
838             if (outside) cycle reports
839             nlocal(ssmt2) = nlocal(ssmt2) + 1
840             if (nlocal(ssmt2) > iv%info(ssmt2)%nlocal) cycle reports
842             allocate (iv%ssmt2(nlocal(ssmt2))%h (1:nlevels))
843             allocate (iv%ssmt2(nlocal(ssmt2))%p (1:nlevels))
844             allocate (iv%ssmt2(nlocal(ssmt2))%rh(1:nlevels))
846             do i = 1, nlevels
847                iv%ssmt2(nlocal(ssmt2))% h(i) = platform%each(i)%height
848                iv%ssmt2(nlocal(ssmt2))% p(i) = platform%each(i)%p%inv
849                iv%ssmt2(nlocal(ssmt2))%rh(i) = platform%each(i)%rh
850             end do
852          case (281)    ;
853             if (.not. use_qscatobs) cycle reports
854             if (n==1) ntotal(qscat) = ntotal(qscat) + 1
855             if (outside) cycle reports
856             nlocal(qscat) = nlocal(qscat)  + 1
857             if (nlocal(qscat) > iv%info(qscat)%nlocal) cycle reports
859             iv%qscat(nlocal(qscat))%h = platform%each(1)%height
860             iv%qscat(nlocal(qscat))%u = platform%each(1)%u
861             iv%qscat(nlocal(qscat))%v = platform%each(1)%v
863             ! Impose minimum observation error = 1.0m/s for Quikscat data:
864             iv%qscat(nlocal(qscat))%u%error = max(platform%each(1)%u%error,1.0)
865             iv%qscat(nlocal(qscat))%v%error = max(platform%each(1)%v%error,1.0)
867          case (132) ; ! profiler
868             if (.not. use_profilerobs) cycle reports
869             if (n==1) ntotal(profiler) = ntotal(profiler) + 1
870             if (outside) cycle reports
871             nlocal(profiler) = nlocal(profiler) + 1
872             if (nlocal(profiler) > iv%info(profiler)%nlocal) cycle reports
874             allocate (iv%profiler(nlocal(profiler))%h (1:nlevels))
875             allocate (iv%profiler(nlocal(profiler))%p (1:nlevels))
876             allocate (iv%profiler(nlocal(profiler))%u (1:nlevels))
877             allocate (iv%profiler(nlocal(profiler))%v (1:nlevels))
879             do i = 1, nlevels
880                iv%profiler(nlocal(profiler))%h(i) = platform%each(i)%height
881                iv%profiler(nlocal(profiler))%p(i) = platform%each(i)%p%inv
882                iv%profiler(nlocal(profiler))%u(i) = platform%each(i)%u
883                iv%profiler(nlocal(profiler))%v(i) = platform%each(i)%v
884             end do
886          case (135) ; ! Bogus
887             if (.not. use_bogusobs) cycle reports
888             if (n==1) ntotal(bogus) = ntotal(bogus) + 1
889             if (outside) cycle reports
890             nlocal(bogus) = nlocal(bogus) + 1
891             if (nlocal(bogus) > iv%info(bogus)%nlocal) cycle reports
893             if (nlocal(bogus) > max_bogus_input) then
894                write(unit=message(1),fmt='(A,I6,A,I6)') &
895                   'Bogus #=', nlocal(bogus), ' > max_bogus_input=', max_bogus_input
896                call da_error(__FILE__,__LINE__,message(1:1))
897             end if
899             allocate (iv%bogus(nlocal(bogus))%h (1:nlevels))
900             allocate (iv%bogus(nlocal(bogus))%p (1:nlevels))
901             allocate (iv%bogus(nlocal(bogus))%u (1:nlevels))
902             allocate (iv%bogus(nlocal(bogus))%v (1:nlevels))
903             allocate (iv%bogus(nlocal(bogus))%t (1:nlevels))
904             allocate (iv%bogus(nlocal(bogus))%q (1:nlevels))
906             do i = 1, nlevels
907                iv%bogus(nlocal(bogus))%h(i) = platform%each(i)%height
908                iv%bogus(nlocal(bogus))%p(i) = platform%each(i)%p%inv
909                iv%bogus(nlocal(bogus))%u(i) = platform%each(i)%u
910                iv%bogus(nlocal(bogus))%v(i) = platform%each(i)%v
911                iv%bogus(nlocal(bogus))%t(i) = platform%each(i)%t
912                iv%bogus(nlocal(bogus))%q(i) = platform%each(i)%q
913             end do
915             iv%bogus(nlocal(bogus))%slp    = platform%loc%slp
917             if (print_detail_obs) then
918                write(unit=stdout,fmt=*) 'nlevels=', nlevels
919                write(unit=stdout,fmt=*) 'iv%info(bogus)%nlocal,slp', iv%info(bogus)%nlocal,  &
920                   iv % bogus (nlocal(bogus)) % slp
921                do i=1,nlevels
922                   write(unit=stdout,fmt=*) 'nlocal(bogus), i ', nlocal(bogus),i
923                   write(unit=stdout,fmt=*) 'iv%bogus(nlocal(bogus))%u,v=',  &
924                      iv%bogus(nlocal(bogus))%u(i),iv%bogus(nlocal(bogus))%v(i)
925                   write(unit=stdout,fmt=*) 'iv%bogus(nlocal(bogus))%t,q=',  &
926                      iv%bogus(nlocal(bogus))%t(i),iv%bogus(nlocal(bogus))%q(i)
927                end do
928                write(unit=stdout,fmt='(2(a,i4))') 'nlocal(bogus)=',nlocal(bogus), &
929                   'nlevels=',nlevels
930             end if
932          case (18,19) ;             ! buoy
933             if (.not. use_buoyobs) cycle reports
934             if (n==1) ntotal(buoy) = ntotal(buoy) + 1
935             if (outside) cycle reports
936             nlocal(buoy) = nlocal(buoy)  + 1
937             if (nlocal(buoy) > iv%info(buoy)%nlocal) cycle reports
939             iv%buoy(nlocal(buoy))%h = platform%each(1)%height
940             iv%buoy(nlocal(buoy))%u = platform%each(1)%u
941             iv%buoy(nlocal(buoy))%v = platform%each(1)%v
942             iv%buoy(nlocal(buoy))%t = platform%each(1)%t
943             iv%buoy(nlocal(buoy))%p = platform%each(1)%p
944             iv%buoy(nlocal(buoy))%q = platform%each(1)%q
945    
946          case (133)    ;         ! AIRS retrievals  
947             if (.not. use_airsretobs) cycle reports
948             if (n==1) ntotal(airsr) = ntotal(airsr) + 1
949             if (outside) cycle reports
950             nlocal(airsr) = nlocal(airsr) + 1
951             if (nlocal(airsr) > iv%info(airsr)%nlocal) cycle reports
953             allocate (iv%airsr(nlocal(airsr))%h (1:nlevels))
954             allocate (iv%airsr(nlocal(airsr))%p (1:nlevels))
955             allocate (iv%airsr(nlocal(airsr))%t (1:nlevels))
956             allocate (iv%airsr(nlocal(airsr))%q (1:nlevels))
957             do i = 1, nlevels
958                iv%airsr(nlocal(airsr))%h(i) = platform%each(i)%height
959                iv%airsr(nlocal(airsr))%p(i) = platform%each(i)%p%inv
960                iv%airsr(nlocal(airsr))%t(i) = platform%each(i)%t
961                iv%airsr(nlocal(airsr))%q(i) = platform%each(i)%q
962             end do
964          case default;
966             write(unit=message(1), fmt='(a)') 'unsaved obs found:'
967             write(unit=message(2), fmt='(2a)') &
968                'platform%info%platform=', platform%info%platform
969             write(unit=message(3), fmt='(a, i3)') &
970                'platform%info%levels=', platform%info%levels
971             call da_warning(__FILE__,__LINE__,message(1:3))
972             cycle
973          end select
974            
975          iv%info(obs_index)%name(nlocal(obs_index))      = platform%info%name
976          iv%info(obs_index)%platform(nlocal(obs_index))  = platform%info%platform
977          iv%info(obs_index)%id(nlocal(obs_index))        = platform%info%id
978          iv%info(obs_index)%date_char(nlocal(obs_index)) = platform%info%date_char
979          ! nlevels adjusted for some obs types so use that
980          iv%info(obs_index)%levels(nlocal(obs_index))    = nlevels
981          iv%info(obs_index)%lat(:,nlocal(obs_index))     = platform%info%lat
982          iv%info(obs_index)%lon(:,nlocal(obs_index))     = platform%info%lon
983          iv%info(obs_index)%elv(nlocal(obs_index))       = platform%info%elv
984          iv%info(obs_index)%pstar(nlocal(obs_index))     = platform%info%pstar
986          iv%info(obs_index)%slp(nlocal(obs_index))           = platform%loc%slp
987          iv%info(obs_index)%pw(nlocal(obs_index))            = platform%loc%pw
988          iv%info(obs_index)%x(:,nlocal(obs_index))           = platform%loc%x
989          iv%info(obs_index)%y(:,nlocal(obs_index))           = platform%loc%y 
990          iv%info(obs_index)%i(:,nlocal(obs_index))           = platform%loc%i 
991          iv%info(obs_index)%j(:,nlocal(obs_index))           = platform%loc%j 
992          iv%info(obs_index)%dx(:,nlocal(obs_index))          = platform%loc%dx
993          iv%info(obs_index)%dxm(:,nlocal(obs_index))         = platform%loc%dxm
994          iv%info(obs_index)%dy(:,nlocal(obs_index))          = platform%loc%dy
995          iv%info(obs_index)%dym(:,nlocal(obs_index))         = platform%loc%dym
996          iv%info(obs_index)%proc_domain(:,nlocal(obs_index)) = platform%loc%proc_domain
998          iv%info(obs_index)%obs_global_index(nlocal(obs_index)) = ntotal(obs_index)
1000          ! special case for sonde_sfc, duplicate sound info
1001          if (obs_index == sound) then
1002             iv%info(sonde_sfc)%name(nlocal(sonde_sfc))      = platform%info%name
1003             iv%info(sonde_sfc)%platform(nlocal(sonde_sfc))  = platform%info%platform
1004             iv%info(sonde_sfc)%id(nlocal(sonde_sfc))        = platform%info%id
1005             iv%info(sonde_sfc)%date_char(nlocal(sonde_sfc)) = platform%info%date_char
1006             iv%info(sonde_sfc)%levels(nlocal(sonde_sfc))    = 1
1007             iv%info(sonde_sfc)%lat(:,nlocal(sonde_sfc))     = platform%info%lat
1008             iv%info(sonde_sfc)%lon(:,nlocal(sonde_sfc))     = platform%info%lon
1009             iv%info(sonde_sfc)%elv(nlocal(sonde_sfc))       = platform%info%elv
1010             iv%info(sonde_sfc)%pstar(nlocal(sonde_sfc))     = platform%info%pstar
1012             iv%info(sonde_sfc)%slp(nlocal(sonde_sfc))           = platform%loc%slp
1013             iv%info(sonde_sfc)%pw(nlocal(sonde_sfc))            = platform%loc%pw
1014             iv%info(sonde_sfc)%x(:,nlocal(sonde_sfc))           = platform%loc%x
1015             iv%info(sonde_sfc)%y(:,nlocal(sonde_sfc))           = platform%loc%y 
1016             iv%info(sonde_sfc)%i(:,nlocal(sonde_sfc))           = platform%loc%i 
1017             iv%info(sonde_sfc)%j(:,nlocal(sonde_sfc))           = platform%loc%j 
1018             iv%info(sonde_sfc)%dx(:,nlocal(sonde_sfc))          = platform%loc%dx
1019             iv%info(sonde_sfc)%dxm(:,nlocal(sonde_sfc))         = platform%loc%dxm
1020             iv%info(sonde_sfc)%dy(:,nlocal(sonde_sfc))          = platform%loc%dy
1021             iv%info(sonde_sfc)%dym(:,nlocal(sonde_sfc))         = platform%loc%dym
1022             iv%info(sonde_sfc)%proc_domain(:,nlocal(sonde_sfc)) = platform%loc%proc_domain
1024             iv%info(sonde_sfc)%obs_global_index(nlocal(sonde_sfc)) = ntotal(sonde_sfc)
1025          end if
1027          if (obs_index == tamdar) then
1028             iv%info(tamdar_sfc)%name(nlocal(tamdar_sfc))      = platform%info%name
1029             iv%info(tamdar_sfc)%platform(nlocal(tamdar_sfc))  = platform%info%platform
1030             iv%info(tamdar_sfc)%id(nlocal(tamdar_sfc))        = platform%info%id
1031             iv%info(tamdar_sfc)%date_char(nlocal(tamdar_sfc)) = platform%info%date_char
1032             iv%info(tamdar_sfc)%levels(nlocal(tamdar_sfc))    = 1
1033             iv%info(tamdar_sfc)%lat(:,nlocal(tamdar_sfc))     = platform%info%lat
1034             iv%info(tamdar_sfc)%lon(:,nlocal(tamdar_sfc))     = platform%info%lon
1035             iv%info(tamdar_sfc)%elv(nlocal(tamdar_sfc))       = platform%info%elv
1036             iv%info(tamdar_sfc)%pstar(nlocal(tamdar_sfc))     = platform%info%pstar
1038             iv%info(tamdar_sfc)%slp(nlocal(tamdar_sfc))           = platform%loc%slp
1039             iv%info(tamdar_sfc)%pw(nlocal(tamdar_sfc))            = platform%loc%pw
1040             iv%info(tamdar_sfc)%x(:,nlocal(tamdar_sfc))           = platform%loc%x
1041             iv%info(tamdar_sfc)%y(:,nlocal(tamdar_sfc))           = platform%loc%y
1042             iv%info(tamdar_sfc)%i(:,nlocal(tamdar_sfc))           = platform%loc%i
1043             iv%info(tamdar_sfc)%j(:,nlocal(tamdar_sfc))           = platform%loc%j
1044             iv%info(tamdar_sfc)%dx(:,nlocal(tamdar_sfc))          = platform%loc%dx
1045             iv%info(tamdar_sfc)%dxm(:,nlocal(tamdar_sfc))         = platform%loc%dxm
1046             iv%info(tamdar_sfc)%dy(:,nlocal(tamdar_sfc))          = platform%loc%dy
1047             iv%info(tamdar_sfc)%dym(:,nlocal(tamdar_sfc))         = platform%loc%dym
1048             iv%info(tamdar_sfc)%proc_domain(:,nlocal(tamdar_sfc)) = platform%loc%proc_domain
1050             iv%info(tamdar_sfc)%obs_global_index(nlocal(tamdar_sfc)) = ntotal(tamdar_sfc)
1051          end if
1053          if (global .and. n < 2) then
1054             if (test_transforms) exit dup_loop
1055             if (platform%loc % i >= ide) then
1056                platform%loc%i = platform%loc % i - ide
1057             else if (platform%loc % i < ids) then
1058                platform%loc%i = platform%loc % i + ide
1059             end if
1061             platform%loc%proc_domain = .not. platform%loc%proc_domain
1062          end if
1063       end do dup_loop
1064    end do reports
1066    close(iunit)
1067    call da_free_unit(iunit)
1069    if (trace_use) call da_trace_exit("da_read_obs_ascii")
1071 end subroutine da_read_obs_ascii