[Dart-dev] [6968] DART/trunk/observations: observation converter from glen romine for ascii format

nancy at ucar.edu nancy at ucar.edu
Thu May 1 16:49:42 MDT 2014


Revision: 6968
Author:   nancy
Date:     2014-05-01 16:49:41 -0600 (Thu, 01 May 2014)
Log Message:
-----------
observation converter from glen romine for ascii format
(mdf) data from the oklahoma mesonet.  converter to
create obs_seq files, plus example data, plus shell
script snippet for how to download and convert.
minimal html doc file with links to the data locations.

added code in the ncep obs error module for metar
error values; changed nothing in the existing code,
only added some additional subroutines for metar
land obs types.

Modified Paths:
--------------
    DART/trunk/observations/obs_error/ncep_obs_err_mod.f90

Added Paths:
-----------
    DART/trunk/observations/ok_mesonet/
    DART/trunk/observations/ok_mesonet/convert_ok_mesonet.f90
    DART/trunk/observations/ok_mesonet/data/
    DART/trunk/observations/ok_mesonet/data/201305150000.mdf
    DART/trunk/observations/ok_mesonet/data/geoinfo.csv
    DART/trunk/observations/ok_mesonet/ok_mesonet.html
    DART/trunk/observations/ok_mesonet/read_geo.f90
    DART/trunk/observations/ok_mesonet/shell_scripts/
    DART/trunk/observations/ok_mesonet/shell_scripts/README
    DART/trunk/observations/ok_mesonet/shell_scripts/convert_data
    DART/trunk/observations/ok_mesonet/shell_scripts/run_test_data
    DART/trunk/observations/ok_mesonet/work/
    DART/trunk/observations/ok_mesonet/work/input.nml
    DART/trunk/observations/ok_mesonet/work/mkmf_advance_time
    DART/trunk/observations/ok_mesonet/work/mkmf_convert_okmeso
    DART/trunk/observations/ok_mesonet/work/mkmf_obs_sequence_tool
    DART/trunk/observations/ok_mesonet/work/mkmf_preprocess
    DART/trunk/observations/ok_mesonet/work/path_names_advance_time
    DART/trunk/observations/ok_mesonet/work/path_names_convert_okmeso
    DART/trunk/observations/ok_mesonet/work/path_names_obs_sequence_tool
    DART/trunk/observations/ok_mesonet/work/path_names_preprocess
    DART/trunk/observations/ok_mesonet/work/quickbuild.csh

-------------- next part --------------
Modified: DART/trunk/observations/obs_error/ncep_obs_err_mod.f90
===================================================================
--- DART/trunk/observations/obs_error/ncep_obs_err_mod.f90	2014-05-01 16:03:49 UTC (rev 6967)
+++ DART/trunk/observations/obs_error/ncep_obs_err_mod.f90	2014-05-01 22:49:41 UTC (rev 6968)
@@ -37,6 +37,11 @@
           land_temp_error,              &
           land_wind_error
 
+public :: metar_pres_error,              &
+          metar_rel_hum_error,           &
+          metar_temp_error,              &
+          metar_wind_error
+
 public :: acars_rel_hum_error,          &
           acars_temp_error,             &
           acars_wind_error
@@ -77,6 +82,7 @@
 
 integer  :: k0
 real(r8) :: obs_err(nobs_level), wght, acars_temp_error
+! this array is ordered from top of atm down to surface
 
 data obs_err/1.0_r8, 1.0_r8, 1.0_r8, 1.0_r8, 1.0_r8, 1.0_r8, &
              1.0_r8, 1.0_r8, 1.0_r8, 1.0_r8, 1.0_r8, 1.0_r8, &
@@ -84,7 +90,14 @@
              1.0_r8, 1.0_r8, 1.0_r8, 1.0_r8, 1.0_r8, 1.0_r8, &
              1.0_r8, 1.0_r8, 1.0_r8, 1.11_r8, 1.24_r8, 1.35_r8, &
              1.47_r8, 1.47_r8, 1.47_r8/
+!data obs_prs/   0.0_r8,    1.0_r8,    2.0_r8,   3.0_r8,    4.0_r8,   5.0_r8,
+!               10.0_r8,   20.0_r8,   30.0_r8,  40.0_r8,   50.0_r8,  75.0_r8,
+!              100.0_r8,  150.0_r8,  200.0_r8, 250.0_r8,  300.0_r8, 350.0_r8, 
+!              400.0_r8,  450.0_r8,  500.0_r8, 550.0_r8,  600.0_r8, 650.0_r8,  
+!              700.0_r8,  750.0_r8,  800.0_r8, 850.0_r8,  900.0_r8, 950.0_r8, &
+!             1000.0_r8, 1050.0_r8, 1100.0_r8/
 
+
 call find_pressure_level_weight(pres, k0, wght)
 acars_temp_error = wght * obs_err(k0) + (1.0_r8 - wght) * obs_err(k0+1)
 acars_temp_error = dble(nint(acars_temp_error * 10.0_r8)) * 0.1_r8
@@ -121,6 +134,22 @@
 end function land_pres_error
 
 
+function metar_pres_error(pres)
+
+real(r8), intent(in) :: pres  !  (mb)
+
+real(r8) :: metar_pres_error
+
+if ( pres >= 600.0_r8 ) then
+  metar_pres_error = 1.0_r8
+else
+  metar_pres_error = missing_r8
+end if
+
+return
+end function metar_pres_error
+
+
 function land_rel_hum_error(pres, tmpk, rh)
 
 real(r8), intent(in) :: pres, tmpk, rh
@@ -133,6 +162,18 @@
 end function land_rel_hum_error
 
 
+function metar_rel_hum_error(pres, tmpk, rh)
+
+real(r8), intent(in) :: pres, tmpk, rh
+
+real(r8) :: metar_rel_hum_error
+
+metar_rel_hum_error = 0.2_r8
+
+return
+end function metar_rel_hum_error
+
+
 function land_temp_error(pres)
 
 real(r8), intent(in) :: pres  !  (mb)
@@ -145,6 +186,18 @@
 end function land_temp_error
 
 
+function metar_temp_error(pres)
+
+real(r8), intent(in) :: pres  !  (mb)
+
+real(r8) :: metar_temp_error
+
+metar_temp_error = 2.5_r8
+
+return
+end function metar_temp_error
+
+
 function land_wind_error(pres)
 
 real(r8), intent(in) :: pres  !  (mb)
@@ -157,6 +210,18 @@
 end function land_wind_error
 
 
+function metar_wind_error(pres)
+
+real(r8), intent(in) :: pres  !  (mb)
+
+real(r8) :: metar_wind_error
+
+metar_wind_error = 3.5_r8
+
+return
+end function metar_wind_error
+
+
 function fixed_marine_pres_error(pres)
 
 real(r8), intent(in) :: pres  !  (mb)
@@ -360,6 +425,12 @@
              2.6_r8, 2.3_r8, 2.1_r8, 2.0_r8, 1.9_r8, 1.8_r8, &
              1.6_r8, 1.6_r8, 1.6_r8, 1.5_r8, 1.5_r8, 1.5_r8, &
              1.4_r8, 1.4_r8, 1.4_r8/
+!data obs_prs/   0.0_r8,    1.0_r8,    2.0_r8,   3.0_r8,    4.0_r8,   5.0_r8,
+!               10.0_r8,   20.0_r8,   30.0_r8,  40.0_r8,   50.0_r8,  75.0_r8,
+!              100.0_r8,  150.0_r8,  200.0_r8, 250.0_r8,  300.0_r8, 350.0_r8, 
+!              400.0_r8,  450.0_r8,  500.0_r8, 550.0_r8,  600.0_r8, 650.0_r8,  
+!              700.0_r8,  750.0_r8,  800.0_r8, 850.0_r8,  900.0_r8, 950.0_r8, &
+!             1000.0_r8, 1050.0_r8, 1100.0_r8/
 
 call find_pressure_level_weight(pres, k0, wght)
 rawin_wind_error = wght * obs_err(k0) + (1.0_r8 - wght) * obs_err(k0+1)

Added: DART/trunk/observations/ok_mesonet/convert_ok_mesonet.f90
===================================================================
--- DART/trunk/observations/ok_mesonet/convert_ok_mesonet.f90	                        (rev 0)
+++ DART/trunk/observations/ok_mesonet/convert_ok_mesonet.f90	2014-05-01 22:49:41 UTC (rev 6968)
@@ -0,0 +1,408 @@
+! DART software - Copyright 2004 - 2013 UCAR. This open source software is
+! provided by UCAR, "as is", without charge, subject to all terms of use at
+! http://www.image.ucar.edu/DAReS/DART/DART_download
+!
+! $Id$
+
+program convert_ok_mesonet
+
+!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
+!
+!   convert_ok_mesonet - program to convert Oklahoma Mesonet MDF files
+!                        into DART observation sequence files.
+!
+!   The observation files can  be obtained from the Oklahoma Mesonet
+!   archive using urls of the format:
+!   http://www.mesonet.org/index.php/dataMdfMts/dataController/getFile/YYYYMMDDHHMM/mdf/TEXT/ 
+!   where YYYYMMDDHHMM is the date and time of the desired set of observations.
+!   files are available every 5 minutes.
+!
+!   Static fields are drawn from the station description file provided by
+!   the OK Mesonet. Update the local file from:
+!   http://www.mesonet.org/index.php/api/siteinfo/from_all_active_with_geo_fields/format/csv/ 
+!
+!   NOTE: you may want to consider using METAR surface ob errors
+!   with Oklahoma Mesonet surface obs. See flag below.
+!
+!   Written by G. Romine using the madis converters as a template, Aug. 2013
+! 
+!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
+! may want to add a namelist - so leaving module components active for now
+use         utilities_mod, only : get_unit, find_namelist_in_file, check_namelist_read, &
+                                  do_nml_file, do_nml_term, logfileunit, nmlfileunit
+use             types_mod, only : r8, missing_r8
+use      time_manager_mod, only : time_type, set_calendar_type, set_date, &
+                                  increment_time, get_time, operator(-), GREGORIAN
+use          location_mod, only : location_type, set_location, get_location, &
+                                  get_dist, VERTISSURFACE
+use      obs_sequence_mod, only : obs_sequence_type, obs_type, read_obs_seq, &
+                                  static_init_obs_sequence, init_obs, write_obs_seq, &
+                                  init_obs_sequence, get_num_obs, &
+                                  set_copy_meta_data, set_qc_meta_data
+use           obs_def_mod, only : obs_def_type
+use            meteor_mod, only : sat_vapor_pressure, specific_humidity, &
+                                  wind_dirspd_to_uv, rh_and_temp_to_dewpoint
+use           obs_err_mod, only : land_temp_error, land_wind_error, &
+                                  land_pres_error, land_rel_hum_error, &
+                                  metar_temp_error, metar_wind_error, &
+                                  metar_pres_error, metar_rel_hum_error
+use  dewpoint_obs_err_mod, only : dewpt_error_from_rh_and_temp, &
+                                  rh_error_from_dewpt_and_temp
+use          obs_kind_mod, only : LAND_SFC_U_WIND_COMPONENT, LAND_SFC_V_WIND_COMPONENT, &
+                                  LAND_SFC_TEMPERATURE, LAND_SFC_SPECIFIC_HUMIDITY, &
+                                  LAND_SFC_DEWPOINT, LAND_SFC_RELATIVE_HUMIDITY, &
+                                  LAND_SFC_ALTIMETER
+use     obs_utilities_mod, only : add_obs_to_seq, create_3d_obs
+use obs_def_altimeter_mod, only : compute_altimeter
+
+implicit none
+! Mesonet observations are station lists at a common time with observations in
+! the following order:
+! stid (A4), stnm (I3), time (I4), relh (I4), tair (F6.1), wspd (F6.1), wvec
+! (F6.1), wdir (I3), wdsd (F6.1), wssd (F6.1), wmax (F6.1), rain (F7.2), pres
+! (F7.2), srad (I4), ta9m (F6.1), ws2m (F6.1), ts10 (F6.1), tb10 (F6.1), ts05
+! (F6.1), tb05 (F6.1), ts30 (F6.1), tr05 (F6.1), tr25 (F6.1), tr60 (F6.1)
+! first 3 lines are header, date info drawn from middle line
+
+character(len=15),  parameter :: omeso_in_file  = 'okmeso_mdf.in'
+character(len=129), parameter :: omeso_out_file = 'obs_seq.okmeso'
+
+integer, parameter ::   nmax_out   = 4000, &   ! maximum number of reports for file
+                        num_copies = 1,    &   ! number of copies in sequence
+                        num_qc     = 1         ! number of QC entries
+
+! Allow these as namelist entries? Default is convert it all
+logical :: include_specific_humidity = .true.
+logical :: include_relative_humidity = .true.
+logical :: include_dewpoint          = .true.
+logical :: LH_err                    = .true.
+logical :: use_metar_ob_errors       = .true.
+
+real(r8), parameter :: fmiss         = -999.0_r8 ! -998 is also used for some 
+                                                 ! unused fields
+logical  :: fexist, first_obs
+integer :: iunit, obs_num, i
+real(r8) :: qc
+! fields in the mdf
+real(r8)          :: tair, wspd, wvec, wdsd, wssd, wmax, rain, pres, ta9m, &
+                     ws2m, ts10, tb10, ts05, tb05, ts30, tr05, tr25, tr60
+integer           :: stnm, time, relh, wdir, srad
+character(len=4)  :: stid
+integer           :: y4, m2, d2, h2, n2, s2, tobs, osec, oday
+! fields from the geo file
+real(r8)          :: nlat, nlon, elev 
+! local
+real(r8)          :: uwnd, vwnd, alti, oerr, qerr, qv, dptk, qsat, tmpk
+character(len=129) :: header, meta_data
+! obs sequence vars
+type(location_type)     :: obs_loc
+type(obs_sequence_type) :: obs_seq
+type(obs_def_type)      :: obs_def
+type(obs_type)          :: obs, prev_obs
+type(time_type)         :: time_obs, prev_time
+
+obs_num   = 1
+first_obs = .true.
+qc        = 1.0_r8
+
+inquire(file = omeso_in_file, exist = fexist)
+if ( .NOT. fexist ) stop
+
+iunit = get_unit()
+open(unit=iunit, file = omeso_in_file, status = 'old')
+
+!  either read existing obs_seq or create a new one
+call set_calendar_type(GREGORIAN)
+call static_init_obs_sequence()
+call init_obs(obs,      num_copies, num_qc)
+call init_obs(prev_obs, num_copies, num_qc)
+inquire(file=omeso_out_file, exist=fexist)
+
+if ( fexist ) then
+  call read_obs_seq(omeso_out_file, 0, 0, 4*nmax_out, obs_seq)
+else
+  call init_obs_sequence(obs_seq, num_copies, num_qc, 4*nmax_out)
+  do i = 1, num_copies
+    meta_data = 'OKMESO observation'
+    call set_copy_meta_data(obs_seq, i, meta_data)
+  end do
+  do i = 1, num_qc
+    meta_data = 'Data QC'
+    call set_qc_meta_data(obs_seq, i, meta_data)
+  end do
+end if
+
+ read(iunit,*) ! header
+! get the date info from the file
+ read(iunit,'(A50)',END=200) header
+ read(header,12) y4, m2, d2
+12 format(5X,I4,2(X,I2))
+ write(*,*) 'Date ', y4, m2, d2
+! the time is gathered below - minutes since 00 UTC
+ read(iunit,*) ! header  need date and time from here
+
+! loop through all of the obs until reaching the end of the file
+obsloop: do
+!  do while (1 .eq. 1)
+    read(iunit,22,END=200) stid, stnm, time, relh, tair, wspd, wvec, wdir, &
+                           wdsd, wssd, wmax, rain, pres
+
+22 format(1X,A4,3X,I3,2x,I4,3X,I4,3(1X,F6.1),2X,I4,3(1X,F6.1), &
+             1X,F7.2,2X,F7.2)
+! Given the station id, get the lat, lon, and elevation
+    call get_geo(stid,nlat,nlon,elev)
+! Convert the wind speed and direction to u and v wind components, tair to K
+    call wind_dirspd_to_uv(1.0_r8*wdir, wspd, uwnd, vwnd)
+    tmpk = tair + 273.15_r8
+! convert time to UTC
+    h2 = time/60
+    n2 = time - h2*60
+    tobs = h2*100 + n2
+    s2 = 0
+    time_obs = set_date(y4, m2, d2, h2, n2, s2)
+    call get_time(time_obs, osec, oday)
+! NEEDED put in checks for missing obs before each type is added
+! compute surface altimeter
+    alti = compute_altimeter(pres, elev)   ! pres hPa and elev in m
+    
+!Debug    write(*,*) stid, nlat, nlon, elev, tobs, relh, tair, uwnd, vwnd, pres, alti
+
+!    nlon = -nlon  
+    if ( nlon < 0.0_r8 )  nlon = nlon + 360.0_r8
+
+! Gen obs sequence
+! altimeter
+  if ( pres /= fmiss  ) then
+    if (use_metar_ob_errors) then
+      oerr = metar_pres_error(pres)
+    else
+      oerr = land_pres_error(pres)
+    end if
+
+    if ( alti >=  890.0_r8 .and. &
+         alti <= 1100.0_r8 .and. oerr /= missing_r8 ) then
+   
+      call create_3d_obs(nlat, nlon, elev, VERTISSURFACE, alti, &
+                         LAND_SFC_ALTIMETER, oerr, oday, osec, qc, obs)
+      call add_obs_to_seq(obs_seq, obs, time_obs, prev_obs, prev_time, first_obs)
+      obs_num = obs_num + 1
+    end if
+  end if
+
+! winds
+  if ( wspd /= fmiss .and. wdir /= fmiss ) then
+    if (use_metar_ob_errors) then
+      oerr = metar_wind_error(pres)
+    else
+      oerr = land_wind_error(pres)
+    end if
+
+    if ( abs(uwnd) < 150.0_r8 .and. abs(vwnd) < 150.0_r8 .and. oerr /= missing_r8 ) then
+
+      call create_3d_obs(nlat, nlon, elev, VERTISSURFACE, uwnd, &
+                         LAND_SFC_U_WIND_COMPONENT, oerr, oday, osec, qc, obs)
+      call add_obs_to_seq(obs_seq, obs, time_obs, prev_obs, prev_time, first_obs)
+
+      call create_3d_obs(nlat, nlon, elev, VERTISSURFACE, vwnd, &
+                         LAND_SFC_V_WIND_COMPONENT, oerr, oday, osec, qc, obs)
+      call add_obs_to_seq(obs_seq, obs, time_obs, prev_obs, prev_time, first_obs)
+      obs_num = obs_num + 1
+
+    endif
+  endif
+
+! temperature
+  if ( tair /= fmiss  ) then
+    if (use_metar_ob_errors) then
+      oerr = metar_temp_error(pres)
+    else
+      oerr = land_temp_error(pres)
+    endif
+    if ( tmpk >= 200.0_r8 .and. tmpk <= 335.0_r8 .and. oerr /= missing_r8) then
+
+      call create_3d_obs(nlat, nlon, elev, VERTISSURFACE, tmpk, &
+                         LAND_SFC_TEMPERATURE, oerr, oday, osec, qc, obs)
+      call add_obs_to_seq(obs_seq, obs, time_obs, prev_obs, prev_time, first_obs)
+      obs_num = obs_num + 1
+
+    endif
+  endif
+
+! moisture
+  if ( tair /= fmiss .and. relh /= fmiss .and. pres /= fmiss ) then
+
+    qsat = specific_humidity(sat_vapor_pressure(tmpk), pres * 100.0_r8)
+
+    if ( include_specific_humidity ) then
+
+      qv   = qsat * relh / 100.0_r8
+      if (use_metar_ob_errors) then
+        qerr = metar_rel_hum_error(pres, tmpk, qv / qsat)
+      else
+        qerr = land_rel_hum_error(pres, tmpk, qv / qsat)
+      endif
+      if ( LH_err ) then
+        dptk = rh_and_temp_to_dewpoint(relh/100.0_r8, tmpk)  ! Kelvin temp, rh 0.0-1.0
+        qerr = rh_error_from_dewpt_and_temp(tmpk, dptk)
+      endif
+
+      oerr = max(qerr * qsat, 0.0001_r8)
+
+      if ( qv >= 0.0_r8 .and. oerr /= missing_r8) then
+
+        call create_3d_obs(nlat, nlon, elev, VERTISSURFACE, qv, &
+                           LAND_SFC_SPECIFIC_HUMIDITY, oerr, oday, osec, qc, obs)
+        call add_obs_to_seq(obs_seq, obs, time_obs, prev_obs, prev_time, first_obs)
+        obs_num = obs_num + 1
+
+      end if
+
+    end if
+
+    if ( include_relative_humidity ) then
+
+      if (use_metar_ob_errors) then
+        oerr = metar_rel_hum_error(pres, tmpk, relh/100.0_r8)
+      else
+        oerr = land_rel_hum_error(pres, tmpk, relh/100.0_r8)
+      endif
+      if ( LH_err ) then
+        dptk = rh_and_temp_to_dewpoint(relh/100.0_r8, tmpk)  ! Kelvin temp, rh 0.0-1.0
+        oerr = rh_error_from_dewpt_and_temp(tmpk, dptk)
+      endif
+
+      if ( relh >=  0.0_r8 .and. relh <= 101.0_r8 .and. oerr /= missing_r8) then
+
+        call create_3d_obs(nlat, nlon, elev, VERTISSURFACE, relh * 0.01_r8, &
+                           LAND_SFC_RELATIVE_HUMIDITY, oerr, oday, osec, qc, obs)
+        call add_obs_to_seq(obs_seq, obs, time_obs, prev_obs, prev_time, first_obs)
+        obs_num = obs_num + 1
+
+      end if
+
+    end if
+
+    if ( include_dewpoint ) then
+
+      dptk = rh_and_temp_to_dewpoint(relh/100.0_r8, tmpk)  ! Kelvin temp, rh 0.0-1.0
+      oerr = dewpt_error_from_rh_and_temp(tmpk, relh/100.0_r8)  ! This is the LH_err module
+
+      if ( relh >=  0.0_r8 .and. relh <= 101.0_r8 .and. oerr /= missing_r8) then
+
+        call create_3d_obs(nlat, nlon, elev, VERTISSURFACE, dptk, &
+                           LAND_SFC_DEWPOINT, oerr, oday, osec, qc, obs)
+        call add_obs_to_seq(obs_seq, obs, time_obs, prev_obs, prev_time, first_obs)
+        obs_num = obs_num + 1
+
+      end if
+
+    end if
+
+  end if
+ 
+  end do obsloop
+200 continue
+close(iunit) 
+! if we added any obs to the sequence, write it now.
+if ( get_num_obs(obs_seq) > 0 )  call write_obs_seq(obs_seq, omeso_out_file)
+   write (*,fmt='(A,I5,A)') 'Created ',obs_num, ' obs'
+end program convert_ok_mesonet
+!
+!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
+subroutine get_geo(search_stid,nlat,nlon,elevf)
+
+use         utilities_mod, only : get_unit, find_namelist_in_file, check_namelist_read, &
+                                  do_nml_file, do_nml_term, logfileunit, nmlfileunit
+use             types_mod, only : r8, missing_r8
+
+implicit none
+
+character(len=4), intent(in)  :: search_stid
+real(r8), intent(out) :: nlat, nlon, elevf
+
+! Given a station id, find the lat, lon and elevation from the geo file
+! provided by the Oklahoma Mesonent website
+!
+! the geoinfo.csv file has data in the following order:
+!
+! stnm - station number
+! stid - CHAR len=4
+! name - CHAR of variable size
+! city - CHAR of variable size
+! rang - distance of station from city, float
+! cdir - CHAR of variable size
+! cnty - CHAR of variable size
+! nlat - latitude, float
+! nlon - longitude, float
+! elev - elevation, float
+! + other stuff we don't need
+!
+
+! temp vars
+integer :: stnm, iunit, elev
+character(len=4) :: stid
+character(len=15) :: name, city, cdir, cnty
+real :: rang
+character(len=330) :: line
+integer :: n1, n2, n3, n4, n5, n6, n7, n8, n9, n10, nend
+logical :: stn_found
+
+
+ stn_found = .false.
+ iunit = get_unit()
+ open(unit=iunit, file='geoinfo.csv', status='old')
+
+ read(iunit,*) ! header
+
+  do while (1 .eq. 1)
+! read through each line and look for a match 
+ read(iunit,'(A330)',END=200) line
+
+! Ugh... a csv file with mixed var types is a 
+! pain. Find the locations of delimiters and 
+! assign vars as whatever is found between them. 
+! Getting out to the 10th item gives us all we
+! need. 
+! Determine locations of the first 10 delimiters
+n1  = index(line, ',')
+nend = len_trim(line)
+n2  = n1 + index(line(n1+1:nend), ',')
+n3  = n2 + index(line(n2+1:nend), ',')
+n4  = n3 + index(line(n3+1:nend), ',')
+n5  = n4 + index(line(n4+1:nend), ',')
+n6  = n5 + index(line(n5+1:nend), ',')
+n7  = n6 + index(line(n6+1:nend), ',')
+n8  = n7 + index(line(n7+1:nend), ',')
+n9  = n8 + index(line(n8+1:nend), ',')
+n10 = n9 + index(line(n9+1:nend), ',')
+
+!
+ read (line(1:n1-1),'(I3)') stnm
+ read (line(n1+1:n2-1),'(A4)') stid
+ read (line(n2+1:n3-1),'(A15)') name
+ read (line(n3+1:n4-1),'(A15)') city
+ read (line(n4+1:n5-1),'(f6.3)') rang
+ read (line(n5+1:n6-1),'(A3)') cdir
+ read (line(n6+1:n7-1),'(A15)') cnty
+ read (line(n7+1:n8-1),'(f10.7)') nlat
+ read (line(n8+1:n9-1),'(f10.7)') nlon
+ read (line(n9+1:n10-1),'(I4)') elev
+ elevf = 1.0_r8 * elev
+  if (search_stid .eq. stid) then
+    stn_found = .true.
+    goto 200
+  end if
+
+  end do
+200  continue
+  if (.not. stn_found) then
+    write(*,*) ' station ',stid,' not found. Update the geo file.'
+  end if
+  close(iunit)
+end subroutine get_geo
+
+# <next few lines under version control, do not edit>
+# $URL$
+# $Revision$
+# $Date$
+


Property changes on: DART/trunk/observations/ok_mesonet/convert_ok_mesonet.f90
___________________________________________________________________
Added: svn:mime-type
   + text/plain
Added: svn:keywords
   + Date Rev Author HeadURL Id
Added: svn:eol-style
   + native

Added: DART/trunk/observations/ok_mesonet/data/201305150000.mdf
===================================================================
--- DART/trunk/observations/ok_mesonet/data/201305150000.mdf	                        (rev 0)
+++ DART/trunk/observations/ok_mesonet/data/201305150000.mdf	2014-05-01 22:49:41 UTC (rev 6968)
@@ -0,0 +1,122 @@
+  101 ! (c) 2013 Oklahoma Climatological Survey and the Oklahoma Mesonet - all rights reserved
+  21 2013 05 15 00 00 00
+ STID  STNM  TIME   RELH   TAIR   WSPD   WVEC  WDIR   WDSD   WSSD   WMAX    RAIN     PRES  SRAD   TA9M   WS2M   TS10   TB10   TS05   TB05   TS30    TR05    TR25    TR60
+ ADAX     1     0     32   28.2    5.7    5.5   179   13.4    1.7    9.1    0.00   979.22   210   28.5    4.1   25.9   -999   27.5   32.3   20.6    1.50    1.92    -998
+ ALTU     2     0     27   31.4    7.7    7.6   175    8.9    1.1   10.6    0.00   962.40   254   31.0    5.7   23.4   25.3   25.2   27.8   19.3    2.00    3.60    -998
+ ARNE     6     0     22   30.0    7.0    6.9   192   10.2    1.7   10.9    0.00   928.25   282   29.6    5.5   26.3   28.2   28.2   30.6   20.0    2.14    2.47    2.27
+ BEAV     8     0     14   31.5    9.1    9.0   192    7.1    1.3   11.8    0.00   922.41   311   31.1    6.9   24.5   27.8   26.7   29.2   19.1    3.74    2.26    2.48
+ BESS     9     0     26   29.8    8.5    8.5   182    6.5    1.2   11.4    0.00   951.68   261   29.9    6.8   25.0   27.8   27.3   30.5   19.6    3.81    3.16    -998
+ BIXB    10     0     32   27.9    5.1    5.0   184    8.0    1.1    8.5    0.00   991.11   217   29.0    3.2   19.8   -999   20.9   -999   17.2    1.50    1.59    1.56
+ BLAC    11     0     35   28.6    5.5    5.4   191    7.3    0.9    7.4    0.00   975.46   244   29.1    4.6   20.2   -999   22.3   -999   16.4    2.38    1.59    1.56
+ BOIS    12     0     10   30.0    5.6    5.5   181   11.8    0.8    7.0    0.00   869.05   328   29.5    4.9   18.8   21.6   20.7   24.5   15.2    3.69    3.63    3.06
+ BOWL    13     0     34   28.0    5.3    5.2   166   13.4    1.2    9.0    0.00   980.17   221   -998    4.2   22.6   30.4   -998   -998   -998    1.64    1.44    1.59
+ BREC    14     0     38   28.2    5.6    5.5   191    8.7    0.9    7.3    0.00   969.90   247   28.8    4.3   -999   -999   -999   -999   -999    2.26    3.63    3.73
+ BRIS    15     0     35   28.2    3.8    3.7   169   16.2    1.1    6.6    0.00   984.61   212   28.9    2.9   22.9   27.9   24.1   29.3   19.0    1.72    -999    1.49
+ BUFF    16     0     20   31.6    6.5    6.2   199   17.2    2.1   11.4    0.00   944.55   280   -998    3.2   24.9   26.4   -998   28.4   -998    3.38    2.27    2.41
+ BURB    17     0     34   28.7    5.5    5.4   198    6.2    1.0    8.0    0.00   976.29   232   -998    4.1   20.4   25.8   -998   -998   17.2    -998    -998    -998
+ BURN    18     0     34   28.7    6.4    6.2   165   12.8    1.1    9.6    0.00   987.23   206   28.6    4.6   24.7   32.1   25.9   33.7   21.2    2.69    2.02    1.77
+ BUTL    19     0     24   30.4    7.9    7.7   175   11.4    1.6   11.3    0.00   950.46   251   30.5    6.0   21.6   27.6   23.2   29.9   18.1    3.14    3.07    1.99
+ BYAR    20     0     35   27.9    7.7    7.6   176    7.8    1.5   11.1    0.00   972.97   200   28.1    5.9   26.8   29.8   28.7   31.0   20.8    1.92    1.37    1.58
+ CAMA    22     0     26   29.5    9.1    9.1   197    5.9    1.0   11.4    0.00   942.49   267   29.9    6.7   -999   29.2   -999   31.3   17.5    1.85    1.67    -998
+ CENT    23     0     37   27.8    6.6    6.5   177    9.7    1.2   10.1    0.00   989.73   200   28.1    5.3   23.1   28.5   23.6   29.6   18.7    1.73    1.59    1.77
+ CHAN    24     0     28   29.4    4.7    4.5   183   15.2    0.9    6.5    0.00   978.34   226   29.9    3.6   -999   27.8   -999   29.3   19.2    1.44    1.39    -998
+ CHER    25     0     39   28.0    5.8    5.7   180    6.3    0.6    7.3    0.00   967.54   257   28.5    4.2   22.1   28.3   23.1   30.2   18.7    2.08    2.06    1.98
+ CHEY    26     0     22   29.6    7.8    7.8   191    7.2    1.1   11.9    0.00   931.45   275   29.5    6.5   23.6   26.7   25.3   28.0   19.1    3.43    2.11    1.99
+ CHIC    27     0     29   30.3    6.6    6.5   166    7.1    0.9    8.6    0.00   973.51   227   30.0    4.9   23.0   30.4   23.9   32.0   18.5    -998    -998    -998
+ CLAY    29     0     37   27.8    2.9    2.7   179   18.6    0.9    5.5    0.00   992.98   201   28.0    2.5   24.6   -999   26.2   -999   19.9    -998    -998    -998
+ CLOU    30     0     30   27.3    2.7    2.5   187   21.0    0.8    4.9    0.00   989.88   196   27.6    2.1   25.3   25.1   26.4   25.9   20.0    1.82    1.78    -998
+ COOK    31     0     37   27.3    2.3    2.2   178   18.8    0.7    4.0    0.00   979.11   196   27.8    1.5   21.6   25.1   22.6   25.4   18.1    1.87    -998    -998
+ COPA    32     0     37   28.0    4.7    4.6   198    8.8    0.6    6.3    0.00   982.33   210   28.9    3.1   20.2   22.6   20.6   23.5   16.8    1.60    1.44    1.39
+ DURA    33     0     30   27.4    4.6    4.5   180   11.6    0.8    6.8    0.00   991.84   194   27.7    3.8   22.9   32.6   23.1   33.6   19.9    2.14    1.53    1.37
+ ELRE    34     0     40   27.6    4.9    4.9   175    6.2    0.6    6.9    0.00   963.04   257   28.4    3.4   20.0   27.7   21.2   29.6   16.9    2.08    1.54    1.49
+ ERIC    35     0     24   30.4    7.8    7.8   165    7.5    1.3   10.9    0.00   941.32   275   30.2    5.7   27.3   30.5   29.6   32.9   21.4    2.53    -999    3.22
+ EUFA    36     0     38   27.2    5.5    5.5   186    8.4    1.0    7.9    0.00   990.16   215   28.0    4.2   22.2   24.8   23.3   25.1   18.8    1.98    1.57    1.41
+ FAIR    37     0     28   29.5    5.7    5.6   186   11.9    1.4   10.0    0.00   963.16   253   -998    4.2   24.0   28.2   25.4   30.8   -998    -999    -999    -999
+ FORA    38     0     31   29.0    6.6    6.5   199    6.9    0.9    8.6    0.00   973.10   227   29.2    5.3   19.1   -999   20.5   -998   15.6    1.79    1.52    1.40
+ FREE    39     0     23   30.1    8.0    7.9   194    9.0    1.6   11.4    0.00   948.33   270   30.5    5.2   23.7   -999   26.3   30.9   17.7    3.81    3.47    2.53
+ FTCB    40     0     28   30.1    7.0    6.9   173    6.0    0.9    8.8    0.00   962.72   197   30.1    5.5   -999   29.5   -999   -998   22.4    2.08    3.01    2.78
+ GOOD    41     0     12   30.7    9.9    9.8   183    8.4    1.1   12.1    0.00   896.58   292   30.2    8.1   22.7   24.7   25.1   -999   18.4    3.72    3.65    3.76
+ GUTH    43     0     28   29.2    5.4    5.3   190   10.4    1.1    9.5    0.00   972.98   243   29.6    3.9   22.7   29.4   24.6   -998   18.1    1.58    1.39    -998
+ HASK    44     0     36   28.1    4.9    4.9   186    6.9    0.8    7.5    0.00   991.57   212   28.4    4.0   21.5   23.1   22.8   24.0   -999    1.66    1.38    1.39
+ HINT    45     0     28   29.1    7.4    7.3   172    5.9    0.8    9.1    0.00   954.53   252   29.1    5.1   22.8   28.3   24.0   29.6   19.7    3.14    1.63    1.85
+ HOBA    46     0     29   30.2    7.1    7.0   182    8.4    1.2    9.6    0.00   956.48   246   30.2    5.4   26.3   27.3   28.6   29.5   20.0    3.14    2.66    2.75
+ HOLL    47     0   -999   31.0    6.2    6.1   169    8.9    1.6    8.9    0.00   952.91   266   30.7    4.5   21.7   27.4   24.2   30.0   18.3    3.56    2.55    1.90
+ HOOK    48     0     12   31.8    8.8    8.7   186    9.9    1.2   12.7    0.00   905.61   297   31.2    6.9   22.1   -999   24.0   -999   17.5    3.54    3.58    3.58
+ HUGO    49     0     31   27.7    3.4    3.3   186   13.3    0.9    5.5    0.00   995.03   198   27.9    2.4   22.9   29.2   24.0   30.6   19.5    2.38    1.45    -998
+ IDAB    50     0     36   27.3    3.5    3.4   181   11.0    0.7    4.8    0.00  1003.01   191   28.4    1.9   23.8   28.5   24.5   30.2   19.5    2.32    2.83    -998
+ JAYX    51     0     37   27.4    3.3    3.2   210   18.4    1.0    5.4    0.00   978.08   213   28.0    2.5   19.1   23.2   20.1   24.1   16.3    1.43    1.45    -998
+ KENT    52     0     11   30.1    7.1    7.0   151    7.6    0.7    8.5    0.00   863.06   342   29.3    5.9   22.8   23.4   24.5   25.9   17.1    2.23    2.77    -998
+ KETC    53     0     33   29.4    7.6    7.5   167    9.1    0.9    9.8    0.00   972.69   227   29.5    5.8   22.9   29.5   23.9   30.1   -999    1.78    1.59    1.61
+ LAHO    55     0     33   28.9    6.5    6.5   178    8.0    1.1    9.1    0.00   964.64   253   29.2    4.8   19.2   27.5   19.8   29.1   16.3    1.89    1.43    1.47
+ LANE    56     0     37   27.9    4.4    4.3   167   11.4    1.2    7.3    0.00   993.64   203   28.2    3.6   25.0   23.7   26.1   24.0   20.2    1.95    1.81    1.44
+ MADI    57     0     36   28.3    5.9    5.8   172   10.6    1.0    8.5    0.00   986.88   201   -998    4.8   25.2   32.0   25.9   33.4   -998    -998    -998    -998
+ MANG    58     0     27   31.2    7.3    7.2   172    7.5    0.9    8.9    0.00   957.42   252   30.8    5.7   25.1   29.9   27.7   31.8   18.6    -999    -999    -999
+ MARE    59     0     28   29.6    5.3    5.2   194    8.6    0.9    7.6    0.00   973.36   238   30.0    3.9   22.1   29.4   23.3   31.2   18.3    1.62    1.45    1.53
+ MAYR    61     0     24   30.7   -999   -999   203   10.2   -999   -999    0.00   945.39   270   30.8   -999   24.6   27.0   26.6   30.6   -999    2.31    2.42    2.08
+ MCAL    62     0     36   27.8    3.8    3.6   193   18.1    1.3    7.5    0.00   987.55   214   28.0    2.6   20.9   24.0   21.4   24.0   18.6    1.98    1.46    -998
+ MEDF    63     0     37   28.8    4.8    4.7   179    9.5    1.1    8.0    0.00   971.56   250   -998    3.3   22.8   25.2   -998   27.7   -998    -998    -998    -998
+ MEDI    64     0     31   28.8    9.1    9.0   185    7.1    1.1   11.6    0.00   955.44   226   29.2    6.9   24.8   31.0   26.5   32.7   -999    2.03    1.50    -998
+ MIAM    65     0     44   26.7    5.0    4.9   198    9.7    1.0    7.4    0.00   983.93   201   27.5    3.4   18.5   24.1   19.0   25.3   15.4    1.61    1.46    1.50
+ MINC    66     0     33   28.4    5.0    5.0   180    7.0    0.7    6.8    0.00   962.21   230   28.7    3.8   20.5   27.5   22.0   -998   17.2    2.12    2.05    -998
+ MTHE    67     0     34   26.1    2.5    2.4   184   17.6    0.6    4.5    0.00   983.02   193   -998    2.0   21.4   28.4   -998   -998   -998    -998    -998    -998
+ NEWK    68     0     33   28.9    6.4    6.3   198    9.4    0.8    8.2    0.00   969.05   241   29.2    4.6   19.8   26.8   20.9   -999   16.1    1.74    1.56    1.57
+ NOWA    70     0     43   28.1    4.5    4.4   190    6.4    0.6    5.8    0.00   987.88   205   28.8    3.1   18.8   27.6   19.9   29.6   15.8    1.62    1.52    1.44
+ OILT    71     0     31   29.1    4.1    4.0   188   11.8    0.7    6.1    0.00   982.21   228   30.0    3.1   27.1   29.1   28.6   30.8   20.6    2.06    1.92    1.76
+ OKEM    72     0     32   27.5    6.0    5.9   182   10.1    1.1    8.4    0.00   982.57   218   28.1    4.3   21.2   24.6   21.8   24.8   17.7    1.58    1.42    -998
+ OKMU    73     0     33   28.4    3.8    3.7   185   14.6    1.1    7.5    0.00   989.32   223   29.0    2.8   20.3   28.1   21.0   30.5   -998    2.24    1.58    -998
+ PAUL    74     0     31   29.3    4.2    4.0   165   18.7    1.2    7.2    0.00   978.97   219   29.4    2.8   25.0   30.6   26.1   -998   20.5    1.95    1.94    1.59
+ PAWN    75     0     28   29.5    6.3    6.3   190    8.2    0.8    8.5    0.00   978.68   231   29.8    4.9   23.1   26.0   24.2   -998   17.8    2.17    1.51    1.63
+ PERK    76     0     32   28.9    4.9    4.8   188    8.1    0.7    6.3    0.00   977.51   228   29.7    3.3   23.5   29.5   25.1   31.1   -998    1.76    1.63    1.53
+ PRYO    77     0     39   27.3    5.4    5.3   196    8.4    0.7    7.1    0.00   989.19   208   28.1    3.4   22.0   -999   23.2   24.1   18.5    1.49    1.42    -998
+ PUTN    78     0     26   29.1    9.1    9.0   188    6.8    1.5   11.9    0.00   943.09   259   29.3    6.9   19.3   27.7   20.6   30.2   16.7    1.58    1.53    1.59
+ REDR    79     0     32   29.0    5.4    5.4   195    6.3    0.6    6.9    0.00   976.92   239   29.6    4.1   22.1   28.8   23.6   31.0   17.1    1.51    1.49    1.42
+ RETR    80     0     26   30.2    8.0    7.9   181    9.0    1.1   10.1    0.00   948.91   253   -998    5.7   20.8   25.8   -998   -998   -998    -998    -998    -998
+ RING    81     0     33   29.8    8.7    8.6   165    6.8    1.3   10.9    0.00   979.89   209   29.4    7.0   26.1   32.5   27.5   33.4   20.5    3.53    2.69    -998
+ SALL    82     0     32   28.6    4.9    4.8   200   10.1    0.8    7.3    0.00   995.61   210   -998    3.5   22.7   24.1   24.4   -998   -998    1.33    1.36    1.55
+ SEIL    83     0     26   29.7    6.2    6.1   189    9.3    1.0    8.6    0.00   947.53   264   29.7    4.9   23.0   27.9   24.8   29.3   18.2    1.61    1.62    1.87
+ SHAW    84     0     29   28.7    6.2    6.1   186   10.7    0.9    8.2    0.00   974.39   228   29.5    4.4   22.9   24.6   23.9   25.4   16.9    1.74    1.55    1.44
+ SKIA    85     0     31   28.9    5.0    5.0   211    9.3    0.9    7.0    0.00   979.08   211   29.5    3.0   22.4   24.0   23.4   25.2   17.3    1.84    1.55    1.61
+ SLAP    86     0     16   30.6    8.5    8.4   194    7.5    1.3   11.3    0.00   921.42   294   30.1    6.2   25.7   27.7   28.1   29.5   19.9    2.16    1.98    2.24
+ SPEN    87     0     28   29.4    3.3    3.2   184   14.4    0.8    5.4    0.00   968.71   236   29.6    2.9   25.5   29.1   27.0   31.4   20.1    1.69    1.52    1.45
+ STIG    88     0     43   27.0    5.4    5.3   199    7.7    0.8    7.7    0.00   993.62   194   28.2    3.8   23.0   24.4   24.1   25.1   18.8    -999    -999    -999
+ STIL    89     0     27   30.3    4.5    4.4   188   10.0    1.2    7.4    0.00   979.61   233   30.4    3.7   22.3   28.4   23.6   29.9   17.7    2.80    1.58    1.51
+ STUA    90     0     36   27.1    6.0    6.0   186    8.7    0.9    8.3    0.00   984.33   203   27.7    4.8   23.0   29.4   24.1   30.2   -998    1.96    1.65    1.38
+ SULP    91     0     35   28.1    6.8    6.6   177   14.1    1.3   10.2    0.00   976.46   209   -998    5.3   24.4   29.8   -998   -998   -998    -998    -998    -998
+ TAHL    92     0     37   27.4    5.1    5.0   201   11.0    0.9    7.3    0.00   980.10   209   27.9    4.0   21.4   23.3   22.7   -998   16.3    1.88    -998    -998
+ TALI    93     0     35   27.2    6.2    6.0   178   12.6    1.3    9.0    0.00   991.20   195   27.9    4.1   23.2   29.8   24.4   -999   18.5    2.15    1.61    -998
+ TIPT    94     0     26   31.5    8.1    8.0   176   10.4    1.5   11.2    0.00   965.74   249   31.3    6.6   -999   29.0   -999   31.0   -999    3.82    3.86    3.82
+ TISH    95     0     37   27.8    6.4    6.4   167    6.5    1.0    9.5    0.00   982.77   191   27.8    4.7   24.8   30.1   25.4   32.0   18.9    2.33    2.34    -998
+ VINI    97     0     48   26.5    6.0    6.0   185    5.9    0.6    8.3    0.00   985.11   211   27.4    4.2   21.0   24.1   22.6   24.9   16.4    1.67    1.81    1.57
+ WASH    99     0     32   28.4    5.6    5.5   169    8.1    1.0    8.0    0.00   972.41   228   29.0    4.3   24.5   29.7   25.9   31.3   -999    1.66    1.48    1.47
+ WATO   100     0     27   28.8    7.2    7.1   193    8.7    1.2    9.8    -999   951.70   252   29.0    5.5   21.0   29.2   22.1   31.0   16.2    1.64    1.55    1.46
+ WAUR   101     0     29   30.5    6.7    6.5   184   12.1    1.2    9.3    0.00   979.51   217   30.6    5.2   25.7   30.0   27.1   31.4   21.7    3.26    2.86    1.51
+ WEAT   102     0     27   29.3    8.6    8.6   181    7.3    1.2   10.9    0.00   948.99   253   29.3    6.1   22.8   28.2   24.9   29.8   18.4    1.84    2.10    -998
+ WEST   104     0     36   26.8    5.4    5.3   198   11.5    1.2    8.6    0.00   973.71   210   27.5    4.3   20.1   26.1   21.5   27.6   16.5    1.71    1.52    -998
+ WILB   105     0     39   27.1    5.1    5.0   181   10.6    1.2    8.1    0.00   991.35    66   27.9    3.6   22.6   26.7   23.6   27.7   18.9    2.17    1.40    1.42
+ WIST   106     0     41   27.5    3.7    3.6   196   10.6    0.8    6.0    0.00   997.78   197   28.5    2.3   22.2   31.2   23.1   32.8   18.5    2.33    1.95    1.47
+ WOOD   107     0     23   30.2    7.7    7.6   196    8.0    1.2   10.2    0.00   938.67   276   30.3    6.0   25.1   27.6   26.4   -998   19.4    3.02    1.86    2.00
+ WYNO   108     0     31   29.1    5.8    5.8   202    7.4    0.7    7.5    0.00   980.30   225   29.7    4.4   21.0   26.0   22.6   28.0   15.9    1.68    1.59    -998
+ NINN   109     0     33   29.2    7.1    7.0   172    7.8    1.1   10.3    0.00   970.23   227   -998    5.7   -999   29.0   -999   30.4   -999    -998    -998    -998
+ ACME   110     0     31   29.4    7.8    7.7   180    9.3    1.3   11.6    0.00   966.10   196   29.6    6.0   24.7   30.2   25.7   31.9   19.5    1.75    1.73    1.51
+ APAC   111     0     33   28.6    7.0    6.9   173    8.8    0.8    9.0    0.00   960.73   224   29.0    5.3   -999   26.0   -999   27.9   -999    1.72    1.53    1.85
+ HECT   113     0     30   28.0    5.0    4.8   187   12.2    0.9    7.2    0.00   984.38   224   28.6    3.7   20.4   25.6   21.4   27.9   17.7    1.89    1.56    1.54
+ ALV2   116     0     26   29.7    7.9    7.8   192    7.6    1.0   10.4    0.00   958.45   270   30.5    5.8   20.8   27.2   22.8   30.9   -999    1.54    1.42    -998
+ GRA2   117     0     27   30.9    8.9    8.8   172    8.0    1.5   12.0    0.00   971.64   243   30.8    6.0   26.0   28.7   27.3   30.7   20.8    2.54    2.05    1.80
+ PORT   118     0     34   28.2    4.1    4.0   191    9.9    0.9    7.0    0.00   990.81   212   28.6    3.5   22.0   27.7   -998   -998   -998    1.74    1.46    1.41
+ INOL   120     0     46   27.2    5.2    5.2   185    6.9    0.6    6.5    0.00   990.62   212   -998    3.6   21.4   23.1   22.8   23.7   17.6    1.51    1.41    1.45
+ NRMN   121     0     30   29.0    5.2    5.0   175   11.8    1.6    9.3    0.00   970.85   227   29.6    4.2   22.1   28.2   22.8   29.6   18.2    1.47    1.42    1.41
+ CLRM   122     0     34   29.0    4.3    4.1   187   19.6    1.3    6.7    0.00   987.93   203   -998    3.4   26.6   28.9   29.3   -998   19.4    -998    -998    -998
+ NEWP   123     0     37   28.8    7.3    7.2   173    7.9    1.3   10.1    0.00   980.33   212   -998    5.6   19.8   -999   20.6   -999   18.2    -998    -998    -998
+ BROK   124     0     31   27.8    3.0    2.9   187   15.8    0.8    5.2    -999  1002.46   192   28.6    2.1   25.4   28.9   26.8   30.2   20.6    -998    -998    -998
+ MRSH   125     0     37   28.4    5.0    5.0   189    6.8    0.6    6.5    0.00   974.69   235   -998    3.7   20.9   28.0   22.1   29.7   17.2    1.40    1.37    -998
+ ARD2   126     0     36   28.5    5.7    5.6   174   10.9    0.8    8.2    0.00   982.66   203   28.3    4.9   20.1   29.5   20.7   32.0   18.1    3.43    -999    1.91
+ FITT   127     0     32   27.8    7.5    7.4   190   10.0    1.3   11.0    0.00   973.36   200   -998    5.7   26.4   29.8   26.9   31.0   21.5    2.28    1.89    1.59
+ OKCN   128     0     26   29.7    6.2    6.1   182   13.4    1.3    9.1    0.00   969.74   244   30.0    3.9   21.2   30.0   22.5   31.9   17.5    2.45    1.44    1.41
+ OKCW   129     0     26   30.1    4.4    4.3   184   16.4    1.2    7.5    0.00   969.25   236   30.3    3.9   22.1   29.0   23.3   31.5   18.2    1.58    1.77    1.71
+ OKCE   130     0     28   29.6    3.0    2.8   179   19.4    0.7    5.1    0.00   970.66   237   29.9    2.3   23.2   31.4   24.8   32.1   19.8    2.19    2.87    1.81
+ CARL   131     0     28   30.1    5.3    5.3   189    9.9    1.1    8.0    0.00   976.84   243   30.4    4.3   23.1   28.6   24.7   30.5   -998    1.62    1.47    1.51
+ WEBR   132     0     37   27.9    5.2    5.1   185    9.1    0.9    7.1    0.00   996.70   211   29.1    3.4   21.2   28.6   22.1   -998   18.4    1.65    1.72    -999
+ KIN2   133     0     37   28.8    4.7    4.7   176    6.9    0.7    6.4    0.00   973.52   248   29.1    3.5   22.6   -999   23.8   31.9   -998    3.21    3.06    2.29
+ HOLD   134     0     35   27.6    6.7    6.6   188    8.6    1.0    9.4    0.00   980.78   218   28.1    5.3   22.7   28.3   23.9   30.2   18.4    1.87    1.40    1.41
+ ANT2   135     0   -999   27.6    3.7    3.5   195   17.4    1.1    5.7    0.00   995.08   206   28.0    2.7   23.5   27.2   24.0   28.0   19.8    1.99    1.72    1.42
+ WAL2   136     0     26   30.9   10.5   10.4   178    6.2    1.2   12.9    0.00   974.05   231   30.7    8.6   28.7   31.1   -998   -998   -998    1.98    1.50    2.74

Added: DART/trunk/observations/ok_mesonet/data/geoinfo.csv
===================================================================

@@ Diff output truncated at 40000 characters. @@


More information about the Dart-dev mailing list