[Dart-dev] [5950] DART/branches/development: Adding support for a MIDAS observations of Total Electron Count (TEC).

nancy at ucar.edu nancy at ucar.edu
Wed Jan 23 14:32:51 MST 2013


Revision: 5950
Author:   thoar
Date:     2013-01-23 14:32:50 -0700 (Wed, 23 Jan 2013)
Log Message:
-----------
Adding support for a MIDAS observations of Total Electron Count (TEC).
Alex Chartier of the University of Bath is using these (or will use these)
with the TIEGCM model.

obs_def_upper_atm_mod.f90 has a forward observation operator routine
get_expected_vtec() that is yet to be written by Alex.

Modified Paths:
--------------
    DART/branches/development/obs_def/obs_def_upper_atm_mod.f90
    DART/branches/development/obs_kind/DEFAULT_obs_kind_mod.F90

Added Paths:
-----------
    DART/branches/development/observations/MIDAS/
    DART/branches/development/observations/MIDAS/MIDAS_to_obs.f90
    DART/branches/development/observations/MIDAS/MIDAS_to_obs.html
    DART/branches/development/observations/MIDAS/MIDAS_to_obs_nml
    DART/branches/development/observations/MIDAS/data/
    DART/branches/development/observations/MIDAS/data/Test.nc
    DART/branches/development/observations/MIDAS/work/
    DART/branches/development/observations/MIDAS/work/input.nml
    DART/branches/development/observations/MIDAS/work/mkmf_MIDAS_to_obs
    DART/branches/development/observations/MIDAS/work/mkmf_obs_sequence_tool
    DART/branches/development/observations/MIDAS/work/mkmf_preprocess
    DART/branches/development/observations/MIDAS/work/path_names_MIDAS_to_obs
    DART/branches/development/observations/MIDAS/work/path_names_obs_sequence_tool
    DART/branches/development/observations/MIDAS/work/path_names_preprocess
    DART/branches/development/observations/MIDAS/work/quickbuild.csh

-------------- next part --------------
Modified: DART/branches/development/obs_def/obs_def_upper_atm_mod.f90
===================================================================
--- DART/branches/development/obs_def/obs_def_upper_atm_mod.f90	2013-01-18 22:24:11 UTC (rev 5949)
+++ DART/branches/development/obs_def/obs_def_upper_atm_mod.f90	2013-01-23 21:32:50 UTC (rev 5950)
@@ -7,31 +7,41 @@
 
 ! BEGIN DART PREPROCESS KIND LIST
 ! CHAMP_DENSITY,             KIND_DENSITY
-! GPS_PROFILE,               KIND_ELECTRON_DENSITY,  COMMON_CODE
+! MIDAS_TEC,                 KIND_VERTICAL_TEC
+! GPS_PROFILE,               KIND_ELECTRON_DENSITY,       COMMON_CODE
 ! END DART PREPROCESS KIND LIST
 
 ! BEGIN DART PREPROCESS USE OF SPECIAL OBS_DEF MODULE
 !  use obs_def_upper_atm_mod, only : get_expected_upper_atm_density
+!  use obs_def_upper_atm_mod, only : get_expected_vtec
 ! END DART PREPROCESS USE OF SPECIAL OBS_DEF MODULE
 
 ! BEGIN DART PREPROCESS GET_EXPECTED_OBS_FROM_DEF
-! case(CHAMP_DENSITY) 
-!      call get_expected_upper_atm_density(state, location, obs_val, istatus)
+!   case(CHAMP_DENSITY) 
+!        call get_expected_upper_atm_density(state, location, obs_val, istatus)
+!   case(MIDAS_TEC) 
+!        call get_expected_vtec(state, location, obs_val, istatus)
 ! END DART PREPROCESS GET_EXPECTED_OBS_FROM_DEF
 
 ! BEGIN DART PREPROCESS READ_OBS_DEF
-! case(CHAMP_DENSITY) 
-!      continue
+!   case(CHAMP_DENSITY) 
+!        continue
+!   case(MIDAS_TEC) 
+!        continue
 ! END DART PREPROCESS READ_OBS_DEF
 
 ! BEGIN DART PREPROCESS WRITE_OBS_DEF
-! case(CHAMP_DENSITY) 
-!      continue
+!   case(CHAMP_DENSITY) 
+!        continue
+!   case(MIDAS_TEC) 
+!        continue
 ! END DART PREPROCESS WRITE_OBS_DEF
 
 ! BEGIN DART PREPROCESS INTERACTIVE_OBS_DEF
-! case(CHAMP_DENSITY) 
-!      continue
+!   case(CHAMP_DENSITY) 
+!        continue
+!   case(MIDAS_TEC) 
+!        continue
 ! END DART PREPROCESS INTERACTIVE_OBS_DEF
 
 ! BEGIN DART PREPROCESS MODULE CODE
@@ -53,7 +63,8 @@
                              KIND_PRESSURE
 implicit none
 private
-public                    :: get_expected_upper_atm_density
+public :: get_expected_upper_atm_density, &
+          get_expected_vtec
 
 ! version controlled file description for error handling, do not edit
 character(len=128) :: &
@@ -119,5 +130,26 @@
 end subroutine get_expected_upper_atm_density
 
 
+subroutine get_expected_vtec(x, location, obs_val, istatus)
+!-----------------------------------------------------------------------------
+!Given DART state vector and a location, 
+!it computes thermospheric neutral density [Kg/m3] 
+!The istatus variable should be returned as 0 unless there is a problem
+!
+real(r8),            intent(in) :: x(:)
+type(location_type), intent(in) :: location
+real(r8),           intent(out) :: obs_val
+integer,            intent(out) :: istatus
+real(r8)                        :: mmro1, mmro2 ! mass mixing ratio 
+real(r8)                        :: pressure, temperature 
+
+if ( .not. module_initialized ) call initialize_module
+
+call error_handler(E_ERR, 'get_expected_vtec', 'routine needs to be written', &
+           source, revision, revdate)
+
+end subroutine get_expected_vtec
+
+
 end module obs_def_upper_atm_mod
 ! END DART PREPROCESS MODULE CODE      

Modified: DART/branches/development/obs_kind/DEFAULT_obs_kind_mod.F90
===================================================================
--- DART/branches/development/obs_kind/DEFAULT_obs_kind_mod.F90	2013-01-18 22:24:11 UTC (rev 5949)
+++ DART/branches/development/obs_kind/DEFAULT_obs_kind_mod.F90	2013-01-23 21:32:50 UTC (rev 5950)
@@ -262,9 +262,13 @@
     KIND_CANOPY_WATER                = 130, &
     KIND_GROUND_HEAT_FLUX            = 131
 
+! more kinds for TIEGCM Alex Chartier 
+integer, parameter, public :: &
+    KIND_VERTICAL_TEC                = 132  ! total electron content
+
 !! PRIVATE ONLY TO THIS MODULE. see comment below near the max_obs_specific
 !! declaration.
-integer, parameter :: max_obs_generic = 131
+integer, parameter :: max_obs_generic = 132
 
 !----------------------------------------------------------------------------
 ! This list is autogenerated by the 'preprocess' program.  To add new
@@ -515,6 +519,7 @@
 obs_kind_names(129) = obs_kind_type(KIND_NEUTRON_INTENSITY     ,'KIND_NEUTRON_INTENSITY')
 obs_kind_names(130) = obs_kind_type(KIND_CANOPY_WATER          ,'KIND_CANOPY_WATER')
 obs_kind_names(131) = obs_kind_type(KIND_GROUND_HEAT_FLUX      ,'KIND_GROUND_HEAT_FLUX')
+obs_kind_names(132) = obs_kind_type(KIND_VERTICAL_TEC          ,'KIND_VERTICAL_TEC')
 
 ! count here, then output below
 

Added: DART/branches/development/observations/MIDAS/MIDAS_to_obs.f90
===================================================================
--- DART/branches/development/observations/MIDAS/MIDAS_to_obs.f90	                        (rev 0)
+++ DART/branches/development/observations/MIDAS/MIDAS_to_obs.f90	2013-01-23 21:32:50 UTC (rev 5950)
@@ -0,0 +1,325 @@
+! DART software - Copyright 2004 - 2011 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
+
+program MIDAS_to_obs
+
+! <next few lines under version control, do not edit>
+! $URL$
+! $Id$
+! $Revision$
+! $Date$
+
+!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
+!
+! MIDAS_to_obs - reads the MIDAS data as created by Alex in a netCDF file
+!
+!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
+
+use          types_mod, only : r8, MISSING_R8, metadatalength
+
+use      utilities_mod, only : initialize_utilities, finalize_utilities, &
+                               register_module, error_handler, E_ERR, &
+                               do_nml_file, do_nml_term, &
+                               check_namelist_read, find_namelist_in_file, &
+                               nmlfileunit, file_exist, nc_check
+
+use   time_manager_mod, only : time_type, set_calendar_type, GREGORIAN, &
+                               set_time, get_time, print_time, print_date
+
+use       location_mod, only : location_type, VERTISUNDEF
+
+use   obs_sequence_mod, only : obs_sequence_type, obs_type, &
+                               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  obs_utilities_mod, only : add_obs_to_seq, create_3d_obs
+
+use       obs_kind_mod, only : MIDAS_TEC
+
+use typesizes
+use netcdf
+
+implicit none
+
+!-----------------------------------------------------------------------
+! version controlled file description for error handling, do not edit
+!-----------------------------------------------------------------------
+
+character(len=128), parameter :: &
+   source   = "$URL$", &
+   revision = "$Revision$", &
+   revdate  = "$Date$"
+
+!-----------------------------------------------------------------------
+! Namelist with default values
+!-----------------------------------------------------------------------
+
+character(len=256) :: input_file    = '../data/Test.nc'
+character(len=256) :: obs_out_file  = 'obs_seq.out'
+logical            :: verbose       = .false.
+
+namelist /MIDAS_to_obs_nml/ input_file, obs_out_file, verbose
+
+!-----------------------------------------------------------------------
+! globally-scoped variables
+!-----------------------------------------------------------------------
+
+character(len=256)      :: string1
+integer                 :: itime
+logical                 :: first_obs
+integer                 :: oday, osec, rcio, iunit
+integer                 :: num_copies, num_qc, max_obs
+real(r8)                :: qc
+type(obs_sequence_type) :: obs_seq
+type(obs_type)          :: obs, prev_obs
+type(time_type)         :: prev_time, time_obs
+
+integer :: nlon, nlat, ntimes
+real(r8), allocatable, dimension(:)   :: latitude
+real(r8), allocatable, dimension(:)   :: longitude
+real(r8), allocatable, dimension(:)   :: time
+real(r8), allocatable, dimension(:,:) :: TEC
+real(r8), allocatable, dimension(:,:) :: ObsErrVar
+
+integer  :: ncid, ilon, ilat
+
+!-----------------------------------------------------------------------
+! start of executable code
+!-----------------------------------------------------------------------
+
+call initialize_utilities('MIDAS_to_obs')
+
+! Print module information to log file and stdout.
+call register_module(source, revision, revdate)
+
+! Read the namelist entry
+call find_namelist_in_file("input.nml", "MIDAS_to_obs_nml", iunit)
+read(iunit, nml = MIDAS_to_obs_nml, iostat = rcio)
+call check_namelist_read(iunit, rcio, "MIDAS_to_obs_nml")
+
+! Record the namelist values used for the run ...
+if (do_nml_file()) write(nmlfileunit, nml=MIDAS_to_obs_nml)
+if (do_nml_term()) write(     *     , nml=MIDAS_to_obs_nml)
+
+! time setup
+call set_calendar_type(GREGORIAN)
+prev_time = set_time(0, 0)
+
+! Read the basic MIDAS netCDF information
+ntimes   = read_midas_metadata(input_file)
+
+num_copies = 1
+num_qc     = 1
+first_obs  = .true.
+
+max_obs = ntimes * nlon * nlat
+allocate(TEC(nlon,nlat),ObsErrVar(nlon,nlat))
+
+call static_init_obs_sequence()
+call init_obs(        obs,      num_copies, num_qc)
+call init_obs(        prev_obs, num_copies, num_qc)
+call init_obs_sequence(obs_seq, num_copies, num_qc, max_obs)
+
+! the first one needs to contain the string 'observation' and the
+! second needs the string 'QC'.
+call set_copy_meta_data(obs_seq, 1, 'observation')
+call set_qc_meta_data(  obs_seq, 1, 'MIDAS QC')
+
+call nc_check(nf90_open(input_file, NF90_NOWRITE, ncid), &
+                   'main', 'open '//trim(input_file))
+
+! Actually get the observations for each timestep
+obsloop: do itime = 1,ntimes
+
+   TEC       = MISSING_R8 ! just in case the get_slab fails
+   ObsErrVar = MISSING_R8 ! just in case the get_slab fails
+
+   call get_slab(ncid, itime,      'TEC', TEC, time_obs)
+   call get_slab(ncid, itime, 'Variance', ObsErrVar)
+
+   if (verbose) call print_date(time_obs, 'obs time is')
+
+   call get_time(time_obs, osec, oday)
+
+   ! make an obs derived type, and then add it to the sequence
+   ! If the QC value is good, use the observation.
+   ! Increasingly larger QC values are more questionable quality data.
+
+   qc   = 0.0_r8   ! all observations are assumed to be GREAT, i.e. 0.0
+
+   do ilon = 1,nlon
+   do ilat = 1,nlat
+
+      if (verbose) then
+         write(*,*)ilon, ilat, latitude(ilat), longitude(ilon), &
+                   TEC(ilon,ilat), ObsErrVar(ilon,ilat)
+      endif
+
+      call create_3d_obs(latitude(ilat), longitude(ilon), 0.0_r8, VERTISUNDEF, &
+           TEC(ilon,ilat), MIDAS_TEC, ObsErrVar(ilon,ilat), oday, osec, qc, obs)
+
+      call add_obs_to_seq(obs_seq, obs, time_obs, prev_obs, prev_time, first_obs)
+   enddo
+   enddo
+
+enddo obsloop
+
+! if we added any obs to the sequence, write it out to a file now.
+if ( get_num_obs(obs_seq) > 0 ) then
+   if (verbose) print *, 'writing obs_seq, obs_count = ', get_num_obs(obs_seq)
+   call write_obs_seq(obs_seq, obs_out_file)
+else
+   call error_handler(E_MSG,'lkljlkjkj'
+endif
+
+! end of main program
+call finalize_utilities()
+
+contains
+
+
+
+function read_midas_metadata(input_file)
+!----------------------------------------------------------------------------
+! Read the list of parameters for every site we know about and
+! return the number of sites we know about.
+
+integer                      :: read_midas_metadata
+character(len=*), intent(in) :: input_file
+
+integer :: ncid, VarID
+integer :: time_dimid
+integer :: lon_dimid
+integer :: lat_dimid
+
+! Check to make sure the required parameter file exists
+
+if ( .not. file_exist(input_file) ) then
+   write(string1,*) 'MIDAS data file [', trim(input_file),'] does not exist.'
+   call error_handler(E_ERR,'read_midas_metadata',string1,source,revision,revdate)
+endif
+
+call nc_check(nf90_open(input_file, NF90_NOWRITE, ncid), &
+                   'read_midas_metadata', 'open '//trim(input_file))
+
+! Read the dimensions for everything of interest
+
+call nc_check(nf90_inq_dimid(ncid, 'time', time_dimid), &
+                  'read_midas_metadata','inq_dimid time '//trim(input_file))
+call nc_check(nf90_inquire_dimension(ncid, time_dimid, len=read_midas_metadata), &
+                  'read_midas_metadata','inquire_dimension time '//trim(input_file))
+
+call nc_check(nf90_inq_dimid(ncid, 'latitude', lat_dimid), &
+                  'read_midas_metadata','inq_dimid latitude '//trim(input_file))
+call nc_check(nf90_inquire_dimension(ncid, lat_dimid, len=nlat), &
+                  'read_midas_metadata','inquire_dimension latitude '//trim(input_file))
+
+call nc_check(nf90_inq_dimid(ncid, 'longitude', lon_dimid), &
+                  'read_midas_metadata','inq_dimid longitude '//trim(input_file))
+call nc_check(nf90_inquire_dimension(ncid, lon_dimid, len=nlon), &
+                  'read_midas_metadata','inquire_dimension longitude '//trim(input_file))
+
+allocate(longitude(nlon), latitude(nlat), time(read_midas_metadata))
+
+! Read the coordinate variables
+
+call nc_check(nf90_inq_varid(ncid, 'longitude', VarID), 'read_midas_metadata', 'inq_varid longitude')
+call nc_check(nf90_get_var(ncid, VarID, longitude), 'get_var longitude')
+
+where(longitude  <   0.0_r8) longitude = longitude + 360.0_r8
+where(longitude == 360.0_r8) longitude = 0.0_r8
+
+call nc_check(nf90_inq_varid(ncid, 'latitude', VarID), 'read_midas_metadata', 'inq_varid latitude')
+call nc_check(nf90_get_var(ncid, VarID, latitude), 'get_var latitude')
+
+call nc_check(nf90_inq_varid(ncid, 'time', VarID), 'read_midas_metadata', 'inq_varid time')
+call nc_check(nf90_get_var(ncid, VarID, time), 'get_var time')
+
+call nc_check(nf90_close(ncid), 'read_midas_metadata', 'close '//trim(input_file))
+
+if (verbose) then
+   write(*,*)
+   write(*,*)'There are ',read_midas_metadata,' timesteps in file '//trim(input_file)
+   write(*,*)'longitude ',longitude 
+   write(*,*)'latitude  ',latitude
+endif
+
+end function read_midas_metadata
+
+
+
+subroutine get_slab(ncid, itime, varname, datmat, time_obs)
+!----------------------------------------------------------------------------
+! Read an entire 2D slab for a single timestep from an open netCDF file.
+! We know the variables in the netCDF file do not have a scale/offset.
+
+integer,                   intent(in)  :: ncid
+integer,                   intent(in)  :: itime
+character(len=*),          intent(in)  :: varname
+real(r8), dimension(:,:),  intent(out) :: datmat
+type(time_type), optional, intent(out) :: time_obs
+
+integer :: VarID, numdims
+integer :: i, days, seconds
+
+integer, dimension(NF90_MAX_VAR_DIMS) :: dimIDs
+integer, dimension(NF90_MAX_VAR_DIMS) :: mystart, mycount
+character(len   =  NF90_MAX_NAME)     :: dimname
+
+mystart(:) = 1
+mycount(:) = 1
+
+! Check to make sure the required variable exists
+call nc_check(nf90_inq_varid(ncid, trim(varname), VarID), &
+         'get_slab', 'inq_varid '//trim(varname))
+
+! Construct the hyperslabbing indices independent of the storage order
+
+call nc_check(nf90_inquire_variable(ncid, VarID, dimids=dimIDs, ndims=numdims), &
+         'get_slab', 'inquire '//trim(varname))
+
+DimensionLoop : do i = 1,numdims
+
+   write(string1,'(''inquire dimension'',i2,1x,A)') i,trim(varname)
+   call nc_check(nf90_inquire_dimension(ncid, dimIDs(i), name=dimname), &
+          'get_slab', string1)
+
+   if (trim(dimname) == 'Time')      mystart(i) = itime
+   if (trim(dimname) == 'time')      mystart(i) = itime
+   if (trim(dimname) == 'latitude')  mycount(i) = nlat
+   if (trim(dimname) == 'longitude') mycount(i) = nlon
+
+enddo DimensionLoop
+
+! Get hyperslab from file
+
+call nc_check(nf90_get_var(ncid, VarID, datmat, start=mystart(1:numdims), &
+         count=mycount(1:numdims)), 'get_slab', 'get_var '//trim(varname))
+
+! Get the time relating to this timestep if needed
+
+if (present(time_obs)) then
+
+   days     = time(itime) ! check for integer truncation
+   seconds  = nint((time(itime) - real(days,r8)) * 86400.0_r8)
+   time_obs = set_time(seconds,days)
+
+   if (verbose) then
+      call print_date(time_obs, 'observation date is')
+      call print_time(time_obs, 'observation time is')
+   endif
+
+endif
+
+if (verbose) write(*,'(''Read slab index '',i4,'' for variable '',A)')itime,trim(varname)
+
+end subroutine get_slab
+
+!----------------------------------------------------------------------------
+
+end program MIDAS_to_obs
+


Property changes on: DART/branches/development/observations/MIDAS/MIDAS_to_obs.f90
___________________________________________________________________
Added: svn:mime-type
   + text/plain
Added: svn:keywords
   + Date Rev Author HeadURL Id
Added: svn:eol-style
   + native

Added: DART/branches/development/observations/MIDAS/MIDAS_to_obs.html
===================================================================
--- DART/branches/development/observations/MIDAS/MIDAS_to_obs.html	                        (rev 0)
+++ DART/branches/development/observations/MIDAS/MIDAS_to_obs.html	2013-01-23 21:32:50 UTC (rev 5950)
@@ -0,0 +1,261 @@
+<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01//EN"
+          "http://www.w3.org/TR/html4/strict.dtd">
+<HTML>
+<HEAD>
+<TITLE>program MIDAS_to_obs</TITLE>
+<link rel="stylesheet" type="text/css" href="../../doc/html/doc.css">
+<link href="../../doc/html/dart.ico" rel="shortcut icon" />
+</HEAD>
+<BODY>
+<A NAME="TOP"></A>
+
+<H1>PROGRAM <em class=program>MIDAS_to_obs</em></H1>
+
+<table border=0 summary="" cellpadding=5>
+<tr>
+    <td valign=middle>
+    <img src="../../doc/html/Dartboard7.png" alt="DART project logo" height=70 />
+    </td>
+    <td>
+       <P>Jump to <a href="../../index.html">DART Documentation Main Index</a><br />
+          <small><small>version information for this file: <br />
+          <!-- version tag follows, do not edit -->
+          $Id: MIDAS_to_obs.html $</small></small>
+       </P></td>
+</tr>
+</table>
+
+<A HREF="#DataSources">DATA SOURCES</A> /
+<A HREF="#Programs">PROGRAMS</A> /
+<A HREF="#Namelist">NAMELIST</A> /
+<A HREF="#References">REFERENCES</A> /
+<A HREF="#Errors">ERRORS</A> /
+<A HREF="#FuturePlans">PLANS</A> / 
+<A HREF="#Legalese">TERMS OF USE</A>
+
+<H1>Overview</H1>
+
+<H4>MIDAS netCDF File to DART observation converter</H4>
+
+<P>Alex Chartier (University of Bath, UK) is the point-of-contact for this effort.
+<blockquote>
+"MIDAS runs in Matlab.
+The raw observations come from GPS receivers as RINEX files,
+but we can't use them directly just yet ... 
+Currently, the 'slant' (satellite-to-receiver path) observations are inverted 
+by MIDAS to make vertical, column-integrated 'observations' of plasma density."
+</blockquote>
+</P>
+
+<!--==================================================================-->
+
+<A NAME="DataSources"></A>
+<div class="top">[<a href="#">top</a>]</div><hr />
+<H2>DATA SOURCES</H2>
+
+<P>
+Contact Alex for MIDAS observations. 
+<br />
+<br />
+Alex writes out netCDF files that may be converted to DART observation sequence files.
+The netCDF files have a pretty simple format.
+</P>
+<pre>
+netcdf Test {
+dimensions:
+        latitude = 5 ;
+        longitude = 6 ;
+        height = 30 ;
+        time = UNLIMITED ; // (1 currently)
+variables:
+        double latitude(latitude) ;
+                latitude:units = "degrees_north" ;
+                latitude:long_name = "latitude" ;
+                latitude:standard_name = "latitude" ;
+        double longitude(longitude) ;
+                longitude:units = "degrees_east" ;
+                longitude:long_name = "longitude" ;
+                longitude:standard_name = "longitude" ;
+        double height(height) ;
+                height:units = "metres" ;
+                height:long_name = "height" ;
+                height:standard_name = "height" ;
+        double time(time) ;
+                time:units = "Days since 1601-01-01" ;
+                time:long_name = "Time (UT)" ;
+                time:standard_name = "Time" ;
+        double Ne(height, latitude, longitude) ;
+                Ne:grid_mapping = "standard" ;
+                Ne:units = "1E11 e/m^3" ;
+                Ne:long_name = "electron density" ;
+                Ne:coordinates = "latitude longitude" ;
+        double TEC(time, latitude, longitude) ;
+                TEC:grid_mapping = "standard" ;
+                TEC:units = "1E16 e/m^2" ;
+                TEC:long_name = "total electron content" ;
+                TEC:coordinates = "latitude longitude" ;
+        double Variance(time, latitude, longitude) ;
+                Variance:grid_mapping = "standard" ;
+                Variance:units = "1E16 e/m^2" ;
+                Variance:long_name = "Variance of total electron content" ;
+                Variance:coordinates = "latitude longitude" ;
+                Variance:standard_name = "TEC variance" ;
+// global attributes:
+                :Conventions = "CF-1.5" ;
+}</pre>
+
+<!--==================================================================-->
+
+<A NAME="Programs"></A>
+<div class="top">[<a href="#">top</a>]</div><hr />
+<H2>PROGRAMS</H2>
+<P>
+The <em class=file>MIDAS_to_obs.f90</em> file is the source code
+for the main converter program.
+<br />
+<br />
+To compile and test, go into the <em class=file>MIDAS/work</em> subdirectory and 
+run the <em class=program>quickbuild.csh</em>
+script to build the converter and a couple of general purpose utilities.
+The <a href="../../obs_sequence/obs_sequence_tool.html">obs_sequence_tool</a>
+manipulates (i.e. combines, subsets) DART observation files once they have been created.
+The default observations supported are those defined in 
+<a href="../../obs_def/obs_def_upper_atm_mod.f90">DART/obs_def/obs_def_upper_atm_mod.f90</a>.
+If you need additional observation types, you will have to add the 
+appropriate <em class=file>obs_def_XXX_mod.f90</em> file to the
+<em class=file>input.nml</em>&nbsp;<em class=code>&amp;preprocess_nml:input_files</em>
+variable and run <em class=program>quickbuild.csh</em> again.
+It rebuilds the table of supported observation types before 
+compiling the source code.
+</P>
+
+<P></P><!-- needed to make 'top' align correctly -->
+
+<!--==================================================================-->
+<!--=================== DESCRIPTION OF A NAMELIST  ===================-->
+<!--==================================================================-->
+
+<A NAME="Namelist"></A>
+<div class="top">[<a href="#">top</a>]</div><hr />
+<H2>NAMELIST</H2>
+<P>We adhere to the F90 standard of starting a namelist with an ampersand
+'&amp;' and terminating with a slash '/' for all our namelist input.
+Consider yourself forewarned that character strings that contain a '/' must be
+enclosed in quotes to prevent them from prematurely terminating the namelist.
+</P>
+<div class=namelist><pre>
+<em class=call>namelist /MIDAS_to_obs_nml/ </em> input_file, &amp;
+          obs_out_file, verbose
+</pre>
+</div>
+
+<div class=indent1>
+<!-- Description -->
+
+<P>This namelist is read in a file called <em class=file>input.nml</em>.
+</P>
+
+<TABLE border=0 cellpadding=3 width=100%>
+<TR><TH align=left>Contents    </TH>
+    <TH align=left>Type        </TH>
+    <TH align=left>Description </TH></TR>
+
+<TR><!--contents--><TD valign=top>input_file</TD>
+    <!--  type  --><TD valign=top>character(len=256)</TD>
+    <!--descript--><TD valign=top>The netCDF file containing the 
+                       MIDAS values.<br \>
+                       <em class=units>[default:&nbsp;'../data/Test.nc']</em>
+                       </TD></TR>
+
+<TR><!--contents--><TD valign=top>obs_out_file</TD>
+    <!--  type  --><TD valign=top>character(len=256)</TD>
+    <!--descript--><TD valign=top>The observation sequence file 
+                       for DART.<br \>
+                       <em class=units>[default:&nbsp;'obs_seq.out']</em>
+                       </TD></TR>
+
+<TR><!--contents--><TD valign=top>verbose</TD>
+    <!--  type  --><TD valign=top>logical</TD>
+    <!--descript--><TD valign=top>The switch to specify the run-time output.
+                       <em class=code>.true.</em> the most amount of output.
+                       <em class=code>.false.</em> the least amount of output.
+                       <em class=units>[default:&nbsp;.false.]</em>
+                       </TD></TR>
+
+</TABLE>
+
+<H3 class=indent1>Example</H3>
+
+<pre>
+&amp;MIDAS_to_obs_nml
+   input_file    = '../data/Test.nc',
+   obs_out_file  = 'obs_seq.out',
+   verbose       = .TRUE.,
+</pre>
+
+</div><!-- end of indent1 -->
+
+<!--==================================================================-->
+<!-- References.                                                      -->
+<!--==================================================================-->
+
+<A NAME="References"></A>
+<div class="top">[<a href="#">top</a>]</div><hr />
+<H2>References</H2>
+<!-- ul>
+<li><a href="http://MIDAS.hwr.arizona.edu">The MIDAS web page.</a></li>
+
+</ul -->
+
+<!--==================================================================-->
+<!-- Describe the bugs.                                               -->
+<!--==================================================================-->
+
+<A NAME="KnownBugs"></A>
+<div class="top">[<a href="#">top</a>]</div><hr />
+<H2>KNOWN BUGS</H2>
+<P>
+none
+</P>
+
+<!--==================================================================-->
+<!-- Describe Future Plans.                                           -->
+<!--==================================================================-->
+
+<A NAME="FuturePlans"></A>
+<div class="top">[<a href="#">top</a>]</div><hr />
+<H2>FUTURE PLANS</H2>
+<ul>
+<li>none</li>
+</ul>
+<P>
+</P>
+
+<!--==================================================================-->
+<!-- Legalese & Metadata                                              -->
+<!--==================================================================-->
+
+<A NAME="Legalese"></A>
+<div class="top">[<a href="#">top</a>]</div><hr />
+<H2>Terms of Use</H2>
+
+<P>
+DART software - Copyright 2004 - 2011 UCAR.<br />
+This open source software is provided by UCAR, "as is",<br />
+without charge, subject to all terms of use at<br />
+<a href="http://www.image.ucar.edu/DAReS/DART/DART_download">
+http://www.image.ucar.edu/DAReS/DART/DART_download</a>
+</P>
+
+<TABLE border=0 cellpadding=0 width=100% summary="">
+<TR><TD valign=top>Contact:       </TD><TD> Tim Hoar </TD></TR>
+<TR><TD valign=top>Revision:      </TD><TD> $Revision: $ </TD></TR>
+<TR><TD valign=top>Source:        </TD><TD> $URL: $ </TD></TR>
+<TR><TD valign=top>Change Date:   </TD><TD> $Date: $ </TD></TR>
+<TR><TD valign=top>Change&nbsp;history:&nbsp;</TD><TD> try "svn&nbsp;log" or "svn&nbsp;diff" </TD></TR>
+</TABLE>
+
+<!--==================================================================-->
+
+</BODY>
+</HTML>

Added: DART/branches/development/observations/MIDAS/MIDAS_to_obs_nml
===================================================================
--- DART/branches/development/observations/MIDAS/MIDAS_to_obs_nml	                        (rev 0)
+++ DART/branches/development/observations/MIDAS/MIDAS_to_obs_nml	2013-01-23 21:32:50 UTC (rev 5950)
@@ -0,0 +1,6 @@
+&MIDAS_to_obs_nml
+   input_file    = '../data/Test.nc'
+   obs_out_file  = 'obs_seq.out',
+   verbose       = .false.
+   /
+


Property changes on: DART/branches/development/observations/MIDAS/MIDAS_to_obs_nml
___________________________________________________________________
Added: svn:mime-type
   + text/plain
Added: svn:eol-style
   + native

Added: DART/branches/development/observations/MIDAS/data/Test.nc
===================================================================
(Binary files differ)


Property changes on: DART/branches/development/observations/MIDAS/data/Test.nc
___________________________________________________________________
Added: svn:mime-type
   + application/x-netcdf

Added: DART/branches/development/observations/MIDAS/work/input.nml
===================================================================
--- DART/branches/development/observations/MIDAS/work/input.nml	                        (rev 0)
+++ DART/branches/development/observations/MIDAS/work/input.nml	2013-01-23 21:32:50 UTC (rev 5950)
@@ -0,0 +1,40 @@
+&preprocess_nml
+    input_obs_kind_mod_file = '../../../obs_kind/DEFAULT_obs_kind_mod.F90',
+   output_obs_kind_mod_file = '../../../obs_kind/obs_kind_mod.f90',
+     input_obs_def_mod_file = '../../../obs_def/DEFAULT_obs_def_mod.F90',
+    output_obs_def_mod_file = '../../../obs_def/obs_def_mod.f90',
+   input_files              = '../../../obs_def/obs_def_upper_atm_mod.f90'
+   /
+
+&obs_kind_nml
+   /
+
+&location_nml
+   /
+
+&utilities_nml
+   module_details = .false.,
+   termlevel      = 2
+   /
+
+&obs_sequence_nml
+   write_binary_obs_sequence = .false.  
+   /
+
+&MIDAS_to_obs_nml
+   input_file    = '../data/Test.nc',
+   obs_out_file  = 'obs_seq.out',
+   verbose       = .TRUE.
+   /
+
+&obs_sequence_tool_nml
+   filename_seq         = 'obs_seq_1.out', 'obs_seq_2.out',
+   filename_out         = 'obs_seq.combined',
+   filename_seq_list    = '',
+   num_input_files      = 2,
+   first_obs_days       = -1,
+   first_obs_seconds    = -1,
+   last_obs_days        = -1,
+   last_obs_seconds     = -1 
+   /
+


Property changes on: DART/branches/development/observations/MIDAS/work/input.nml
___________________________________________________________________
Added: svn:mime-type
   + text/plain
Added: svn:eol-style
   + native

Added: DART/branches/development/observations/MIDAS/work/mkmf_MIDAS_to_obs
===================================================================
--- DART/branches/development/observations/MIDAS/work/mkmf_MIDAS_to_obs	                        (rev 0)
+++ DART/branches/development/observations/MIDAS/work/mkmf_MIDAS_to_obs	2013-01-23 21:32:50 UTC (rev 5950)
@@ -0,0 +1,18 @@
+#!/bin/csh
+#
+# DART software - Copyright 2004 - 2011 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$
+
+../../../mkmf/mkmf -p MIDAS_to_obs -t ../../../mkmf/mkmf.template -c"-Duse_netCDF" \
+ -a "../../.." path_names_MIDAS_to_obs
+
+exit $status
+
+# <next few lines under version control, do not edit>
+# $URL$
+# $Revision$
+# $Date$
+


Property changes on: DART/branches/development/observations/MIDAS/work/mkmf_MIDAS_to_obs
___________________________________________________________________
Added: svn:executable
   + *
Added: svn:mime-type
   + text/plain
Added: svn:keywords
   + Date Rev Author HeadURL Id
Added: svn:eol-style
   + native

Added: DART/branches/development/observations/MIDAS/work/mkmf_obs_sequence_tool
===================================================================
--- DART/branches/development/observations/MIDAS/work/mkmf_obs_sequence_tool	                        (rev 0)
+++ DART/branches/development/observations/MIDAS/work/mkmf_obs_sequence_tool	2013-01-23 21:32:50 UTC (rev 5950)
@@ -0,0 +1,18 @@
+#!/bin/csh
+#
+# DART software - Copyright 2004 - 2011 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$
+
+../../../mkmf/mkmf -p obs_sequence_tool -t ../../../mkmf/mkmf.template -c"-Duse_netCDF" \
+ -a "../../.." path_names_obs_sequence_tool
+
+exit $status
+
+# <next few lines under version control, do not edit>
+# $URL$
+# $Revision$
+# $Date$
+


Property changes on: DART/branches/development/observations/MIDAS/work/mkmf_obs_sequence_tool
___________________________________________________________________
Added: svn:executable
   + *
Added: svn:mime-type
   + text/plain
Added: svn:keywords
   + Date Rev Author HeadURL Id
Added: svn:eol-style
   + native

Added: DART/branches/development/observations/MIDAS/work/mkmf_preprocess
===================================================================
--- DART/branches/development/observations/MIDAS/work/mkmf_preprocess	                        (rev 0)
+++ DART/branches/development/observations/MIDAS/work/mkmf_preprocess	2013-01-23 21:32:50 UTC (rev 5950)
@@ -0,0 +1,18 @@
+#!/bin/csh
+#
+# DART software - Copyright 2004 - 2011 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$
+
+../../../mkmf/mkmf -p preprocess -t ../../../mkmf/mkmf.template -c"-Duse_netCDF" \
+ -a "../../.." path_names_preprocess
+
+exit $status
+
+# <next few lines under version control, do not edit>
+# $URL$
+# $Revision$
+# $Date$
+


Property changes on: DART/branches/development/observations/MIDAS/work/mkmf_preprocess
___________________________________________________________________
Added: svn:executable
   + *
Added: svn:mime-type
   + text/plain
Added: svn:keywords
   + Date Rev Author HeadURL Id
Added: svn:eol-style
   + native

Added: DART/branches/development/observations/MIDAS/work/path_names_MIDAS_to_obs
===================================================================
--- DART/branches/development/observations/MIDAS/work/path_names_MIDAS_to_obs	                        (rev 0)
+++ DART/branches/development/observations/MIDAS/work/path_names_MIDAS_to_obs	2013-01-23 21:32:50 UTC (rev 5950)
@@ -0,0 +1,13 @@
+assim_model/assim_model_mod.f90
+common/types_mod.f90
+location/threed_sphere/location_mod.f90
+models/template/model_mod.f90
+mpi_utilities/null_mpi_utilities_mod.f90
+obs_def/obs_def_mod.f90
+observations/MIDAS/MIDAS_to_obs.f90
+observations/utilities/obs_utilities_mod.f90
+obs_kind/obs_kind_mod.f90
+obs_sequence/obs_sequence_mod.f90
+random_seq/random_seq_mod.f90
+time_manager/time_manager_mod.f90
+utilities/utilities_mod.f90

Added: DART/branches/development/observations/MIDAS/work/path_names_obs_sequence_tool
===================================================================
--- DART/branches/development/observations/MIDAS/work/path_names_obs_sequence_tool	                        (rev 0)
+++ DART/branches/development/observations/MIDAS/work/path_names_obs_sequence_tool	2013-01-23 21:32:50 UTC (rev 5950)
@@ -0,0 +1,13 @@
+assim_model/assim_model_mod.f90
+common/types_mod.f90
+cov_cutoff/cov_cutoff_mod.f90
+location/threed_sphere/location_mod.f90
+models/template/model_mod.f90
+mpi_utilities/null_mpi_utilities_mod.f90
+obs_def/obs_def_mod.f90
+obs_kind/obs_kind_mod.f90
+obs_sequence/obs_sequence_mod.f90
+obs_sequence/obs_sequence_tool.f90
+random_seq/random_seq_mod.f90
+time_manager/time_manager_mod.f90
+utilities/utilities_mod.f90

Added: DART/branches/development/observations/MIDAS/work/path_names_preprocess
===================================================================
--- DART/branches/development/observations/MIDAS/work/path_names_preprocess	                        (rev 0)
+++ DART/branches/development/observations/MIDAS/work/path_names_preprocess	2013-01-23 21:32:50 UTC (rev 5950)
@@ -0,0 +1,5 @@
+common/types_mod.f90
+mpi_utilities/null_mpi_utilities_mod.f90
+preprocess/preprocess.f90
+time_manager/time_manager_mod.f90
+utilities/utilities_mod.f90

Added: DART/branches/development/observations/MIDAS/work/quickbuild.csh
===================================================================
--- DART/branches/development/observations/MIDAS/work/quickbuild.csh	                        (rev 0)
+++ DART/branches/development/observations/MIDAS/work/quickbuild.csh	2013-01-23 21:32:50 UTC (rev 5950)
@@ -0,0 +1,69 @@
+#!/bin/csh
+#
+# DART software - Copyright 2004 - 2011 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$
+#
+# compile all converter programs
+
+#----------------------------------------------------------------------
+# 'preprocess' is a program that culls the appropriate sections of the
+# observation module for the observations types in 'input.nml'; the 
+# resulting source file is used by all the remaining programs, 
+# so this MUST be run first.
+#----------------------------------------------------------------------
+
+\rm -f preprocess *.o *.mod 
+\rm -f ../../../obs_def/obs_def_mod.f90
+\rm -f ../../../obs_kind/obs_kind_mod.f90
+
+set MODEL = "MIDAS converter"
+
+@ n = 1
+
+echo
+echo
+echo "---------------------------------------------------------------"
+echo "${MODEL} build number ${n} is preprocess"
+
+csh  mkmf_preprocess
+make || exit $n
+
+./preprocess || exit 99
+
+#----------------------------------------------------------------------
+# Build all the single-threaded targets
+#----------------------------------------------------------------------
+
+foreach TARGET ( mkmf_* )
+
+   set PROG = `echo $TARGET | sed -e 's#mkmf_##'`
+
+   switch ( $TARGET )
+   case mkmf_preprocess:
+      breaksw
+   default:
+      @ n = $n + 1
+      echo
+      echo "---------------------------------------------------"
+      echo "${MODEL} build number ${n} is ${PROG}" 
+      \rm -f ${PROG}
+      csh $TARGET || exit $n
+      make        || exit $n
+      breaksw
+   endsw
+end
+
+\rm -f *.o *.mod  input.nml*_default
+
+echo "Success: All ${MODEL} programs compiled."  
+
+exit 0
+
+# <next few lines under version control, do not edit>
+# $URL$
+# $Revision$
+# $Date$
+


Property changes on: DART/branches/development/observations/MIDAS/work/quickbuild.csh
___________________________________________________________________
Added: svn:executable
   + *
Added: svn:mime-type
   + text/plain
Added: svn:keywords
   + Date Rev Author HeadURL Id
Added: svn:eol-style
   + native


More information about the Dart-dev mailing list