[Dart-dev] [4795] DART/trunk/utilities: This is the first crack at a program designed to help test new instances

nancy at ucar.edu nancy at ucar.edu
Fri Mar 11 15:45:03 MST 2011


Revision: 4795
Author:   thoar
Date:     2011-03-11 15:45:03 -0700 (Fri, 11 Mar 2011)
Log Message:
-----------
This is the first crack at a program designed to help test new instances
of model_mod.f90 as people try to add their own models to DART. It lets them
test some of the required interfaces - one at a time.

Added Paths:
-----------
    DART/trunk/utilities/model_mod_check.f90
    DART/trunk/utilities/model_mod_check.html
    DART/trunk/utilities/model_mod_check.nml

-------------- next part --------------
Added: DART/trunk/utilities/model_mod_check.f90
===================================================================
--- DART/trunk/utilities/model_mod_check.f90	                        (rev 0)
+++ DART/trunk/utilities/model_mod_check.f90	2011-03-11 22:45:03 UTC (rev 4795)
@@ -0,0 +1,313 @@
+! DART software - Copyright \xA9 2004 - 2010 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 model_mod_check
+
+! <next few lines under version control, do not edit>
+! $URL$
+! $Id$
+! $Revision$
+! $Date$
+
+!----------------------------------------------------------------------
+! purpose: test routines
+!----------------------------------------------------------------------
+
+use        types_mod, only : r8, digits12, metadatalength
+use    utilities_mod, only : initialize_utilities, timestamp, nc_check, &
+                             open_file, close_file, find_namelist_in_file, &
+                             check_namelist_read
+use     location_mod, only : location_type, set_location, write_location, get_dist, &
+                             query_location, LocationDims, get_location
+use     obs_kind_mod, only : get_raw_obs_kind_name, get_raw_obs_kind_index
+use  assim_model_mod, only : open_restart_read, open_restart_write, close_restart, &
+                             aread_state_restart, awrite_state_restart, &
+                             netcdf_file_type, aoutput_diagnostics, &
+                             init_diag_output, finalize_diag_output
+use time_manager_mod, only : time_type, set_calendar_type, GREGORIAN, &
+                             read_time, get_time, set_time,  &
+                             print_date, get_date, &
+                             print_time, write_time, &
+                             operator(-)
+use        model_mod, only : static_init_model, get_model_size, get_state_meta_data
+               !             test_interpolate, get_gridsize
+
+implicit none
+
+! version controlled file description for error handling, do not edit
+character(len=128), parameter :: &
+   source   = "$URL$", &
+   revision = "$Revision$", &
+   revdate  = "$Date$"
+
+!------------------------------------------------------------------
+! The namelist variables
+!------------------------------------------------------------------
+
+character (len = 129) :: input_file  = 'dart.ics'
+character (len = 129) :: output_file = 'check_me'
+logical               :: advance_time_present = .FALSE.
+logical               :: verbose              = .FALSE.
+integer               :: x_ind = -1
+real(r8), dimension(3) :: loc_of_interest = -1.0_r8
+character(len=metadatalength) :: kind_of_interest = 'ANY'
+
+namelist /model_mod_check_nml/ input_file, output_file, &
+                        advance_time_present, x_ind,    &
+                        loc_of_interest, kind_of_interest, verbose
+
+!----------------------------------------------------------------------
+! integer :: numlons, numlats, numlevs
+
+integer :: in_unit, out_unit, ios_out, iunit, io, offset
+integer :: x_size
+integer :: year, month, day, hour, minute, second
+integer :: secs, days
+
+type(time_type)       :: model_time, adv_to_time
+real(r8), allocatable :: statevector(:)
+
+character(len=metadatalength) :: state_meta(1)
+type(netcdf_file_type) :: ncFileID
+
+!----------------------------------------------------------------------
+! This portion checks the geometry information. 
+!----------------------------------------------------------------------
+
+call initialize_utilities(progname='model_mod_check', output_flag=verbose)
+call set_calendar_type(GREGORIAN)
+
+write(*,*)
+write(*,*)'Reading the namelist to get the input filename.'
+
+call find_namelist_in_file("input.nml", "model_mod_check_nml", iunit)
+read(iunit, nml = model_mod_check_nml, iostat = io)
+call check_namelist_read(iunit, io, "model_mod_check_nml")
+
+write(*,'(''Converting DART file '',A,'' to restart file '',A)') &
+     trim(input_file), trim(output_file)
+
+! This harvests all kinds of initialization information
+call static_init_model()
+
+! model_mod:get_gridsize() is a trivial routine to write and is not
+! required. If your model_mod:static_init_model() does not have this
+! information written to stdout, do it here.
+if (verbose) then
+!  call get_gridsize(numlons, numlats, numlevs)
+!  write(*,'(''nlons, nlats, nlevs'',3(1x,i10))') numlons,numlats,numlevs
+endif
+
+x_size = get_model_size()
+write(*,'(''state vector has length'',i10)') x_size
+allocate(statevector(x_size))
+
+!----------------------------------------------------------------------
+! Write a supremely simple restart file. Most of the time, I just use
+! this as a starting point for a Matlab function that replaces the 
+! values with something more complicated.
+!----------------------------------------------------------------------
+
+write(*,*)
+write(*,*)'Writing a trivial restart file.'
+
+statevector = 1.0_r8;
+model_time  = set_time(21600, 149446)   ! 06Z 4 March 2010
+
+iunit = open_restart_write('allones.ics')
+call awrite_state_restart(model_time, statevector, iunit)
+call close_restart(iunit)
+
+!----------------------------------------------------------------------
+! Open a test DART initial conditions file.
+! Reads the valid time, the state, and (possibly) a target time.
+!----------------------------------------------------------------------
+
+write(*,*)
+write(*,*)'Reading the restart file '//trim(input_file)
+
+iunit = open_restart_read(input_file)
+if ( advance_time_present ) then
+   call aread_state_restart(model_time, statevector, iunit, adv_to_time)
+else
+   call aread_state_restart(model_time, statevector, iunit)
+endif
+
+call close_restart(iunit)
+call print_date( model_time,'model_mod_check:model date')
+call print_time( model_time,'model_mod_check:model time')
+
+!----------------------------------------------------------------------
+! Output the state vector to a netCDF file ...
+! This is the same procedure used by 'perfect_model_obs' & 'filter'
+! init_diag_output()
+! aoutput_diagnostics()
+! finalize_diag_output()
+!----------------------------------------------------------------------
+
+write(*,*)
+write(*,*)'Exercising the netCDF routines.'
+write(*,*)'Creating '//trim(output_file)//'.nc'
+
+state_meta(1) = 'restart test'
+ncFileID = init_diag_output(trim(output_file),'just testing a restart', 1, state_meta)
+
+call aoutput_diagnostics(ncFileID, model_time, statevector, 1)
+
+call nc_check( finalize_diag_output(ncFileID), 'model_mod_check:main', 'finalize')
+
+!----------------------------------------------------------------------
+! Check the interpolation - print initially to STDOUT
+!----------------------------------------------------------------------
+! Use 500 mb ~ level 30 (in the 42-level version)
+
+!write(*,*)
+!write(*,*)'Testing the interpolation ...'
+
+! call test_interpolate(statevector, test_pressure=500.0_r8, &
+!                       start_lon=142.5_r8)
+
+!----------------------------------------------------------------------
+! Checking get_state_meta_data (and get_state_indices, get_state_kind)
+! nx = 144; ny=72; nz=42; produce the expected values :
+!  U(       1 :  435456)
+!  V(  435457 :  870912)
+!  T(  870913 : 1306368)
+!  Q( 1306369 : 1741824)
+! PS( 1741825 : 1752193)    (only 144x72)
+!----------------------------------------------------------------------
+
+if ( x_ind > 0 .and. x_ind <= x_size ) call check_meta_data( x_ind )
+
+!----------------------------------------------------------------------
+! Trying to find the state vector index closest to a particular ...
+! Checking for valid input is tricky ... we don't know much. 
+!----------------------------------------------------------------------
+
+if ( loc_of_interest(1) > 0.0_r8 ) call find_closest_gridpoint( loc_of_interest )
+
+!----------------------------------------------------------------------
+! When called with 'end', timestamp will call finalize_utilities()
+! This must be the last few lines of the main program.
+!----------------------------------------------------------------------
+call timestamp(string1=source, pos='end')
+
+contains
+
+
+subroutine check_meta_data( iloc )
+
+integer, intent(in) :: iloc
+type(location_type) :: loc
+integer             :: var_type
+character(len=129)  :: string1
+
+write(*,*)
+write(*,*)'Checking metadata routines.'
+
+call get_state_meta_data( iloc, loc, var_type)
+
+call write_location(42, loc, fform='formatted', charstring=string1)
+write(*,*)' indx ',iloc,' is type ',var_type,trim(string1)
+
+end subroutine check_meta_data
+
+
+
+subroutine find_closest_gridpoint( loc_of_interest )
+! Simple exhaustive search to find the indices into the 
+! state vector of a particular lon/lat/level. They will 
+! occur multiple times - once for each state variable.
+real(r8), dimension(:), intent(in) :: loc_of_interest
+
+type(location_type) :: loc0, loc1
+integer  :: mykindindex
+integer  :: i, var_type, which_vert
+real(r8) :: closest, rlon, rlat, rlev
+real(r8), allocatable, dimension(:) :: thisdist
+real(r8), dimension(LocationDims) :: rloc
+character(len=32) :: kind_name
+logical :: matched
+
+! Check user input ... if there is no 'vertical' ...  
+if ( (count(loc_of_interest >= 0.0_r8) < 3) .or. &
+     (LocationDims < 3 ) ) then
+   write(*,*)
+   write(*,*)'Interface not fully implemented.' 
+   return
+endif
+
+write(*,*)
+write(*,'(''Checking for the indices into the state vector that are at'')')
+write(*,'(''lon/lat/lev'',3(1x,f10.5))')loc_of_interest(1:LocationDims)
+
+allocate( thisdist(get_model_size()) )
+thisdist  = 9999999999.9_r8         ! really far away 
+matched   = .false.
+
+! Trying to support the ability to specify matching a particular KIND.
+! With staggered grids, the closest gridpoint might not be of the kind
+! you are interested in. mykindindex = -1 means anything will do.
+
+mykindindex = get_raw_obs_kind_index(kind_of_interest)
+
+rlon = loc_of_interest(1)
+rlat = loc_of_interest(2)
+rlev = loc_of_interest(3)
+
+! Since there can be/will be multiple variables with
+! identical distances, we will just cruise once through 
+! the array and come back to find all the 'identical' values.
+do i = 1,get_model_size()
+
+   ! Really inefficient, but grab the 'which_vert' from the
+   ! grid and set our target location to have the same.
+   ! Then, compute the distance and compare.
+
+   call get_state_meta_data(i, loc1, var_type)
+
+   if ( (var_type == mykindindex) .or. (mykindindex < 0) ) then
+      which_vert  = nint( query_location(loc1) )
+      loc0        = set_location(rlon, rlat, rlev, which_vert)
+      thisdist(i) = get_dist( loc1, loc0, no_vert= .true. )
+      matched     = .true.
+   endif
+
+enddo
+
+closest = minval(thisdist)
+
+if (.not. matched) then
+   write(*,*)'No state vector elements of type '//trim(kind_of_interest)
+   return
+endif
+
+! Now that we know the distances ... report 
+
+matched = .false.
+do i = 1,get_model_size()
+
+   if ( thisdist(i) == closest ) then
+      call get_state_meta_data(i, loc1, var_type)
+      rloc      = get_location(loc1)
+      if (nint(rloc(3)) == nint(rlev)) then
+         kind_name = get_raw_obs_kind_name(var_type)
+         write(*,'(''lon/lat/lev'',3(1x,f10.5),'' is index '',i10,'' for '',a)') &
+             rloc, i, trim(kind_name)
+         matched = .true.
+      endif
+   endif
+
+enddo
+
+if ( .not. matched ) then
+   write(*,*)'Nothing matched the vertical.'
+endif
+
+deallocate( thisdist )
+
+end subroutine find_closest_gridpoint
+
+
+end program model_mod_check


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

Added: DART/trunk/utilities/model_mod_check.html
===================================================================
--- DART/trunk/utilities/model_mod_check.html	                        (rev 0)
+++ DART/trunk/utilities/model_mod_check.html	2011-03-11 22:45:03 UTC (rev 4795)
@@ -0,0 +1,430 @@
+<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01//EN"
+          "http://www.w3.org/TR/html4/strict.dtd">
+<HTML>
+<HEAD>
+<TITLE>DART program model_mod_check</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>DART PROGRAM <em class=program>model_mod_check</em></H1>
+
+<table border=0 summary="" cellpadding=5>
+<tr>
+    <td valign=middle>
+    <img src="../doc/html/Dartboard9.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$</small></small>
+       </P></td>
+</tr>
+</table>
+
+<A HREF="#Namelist">NAMELIST</A> /
+<A HREF="#Modules">MODULES</A> /
+<A HREF="#FilesUsed">FILES</A> /
+<A HREF="#Usage">USAGE </A> / 
+<A HREF="#References">REFERENCES</A> /
+<A HREF="#Errors">ERRORS</A> /
+<A HREF="#FuturePlans">PLANS</A> /
+<A HREF="#Legalese">TERMS OF USE</A>
+
+<H2>Overview</H2>
+
+<P>
+   <em class="program">model_mod_check</em> tests some of the more
+   fundamental routines in any <em class="program">model_mod</em>.
+   This is intended to be used when adding a new model to DART - 
+   test the pieces as they are written.  As such, this program is
+   meant to be hacked up and customized to your own purpose. Right now,
+   it reads in a DART ics file and writes out restart files, netCDF files,
+   queries the metdata, etc. It also exercises 
+   <em class="program">static_init_model()</em>, which is the first routine
+   to get right ...
+</P>
+
+<!--==================================================================-->
+<!--=================== DESCRIPTION OF A NAMELIST  ===================-->
+<!--==================================================================-->
+
+<A NAME="Namelist"></A>
+<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 filenames that contain a '/' must be
+enclosed in quotes to prevent them from prematurely terminating the namelist.
+The namelist declaration (i.e. what follows) has a different syntax, naturally.
+</P>
+<div class=namelist>
+<pre>
+<em class=call>namelist / model_mod_check_nml / </em> 
+                              input_file, output_file,
+                              advance_time_present, verbose,
+                              x_ind, loc_of_interest, kind_of_interest
+</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=129) </TD>
+    <!--descript--><TD>Name of a file containing DART initial conditions for
+            the model.
+	    <br />
+	    Default 'dart.ics'</TD></TR>  
+
+<TR><!--contents--><TD valign=top> output_file  </TD>
+    <!--  type  --><TD valign=top> character(len=129) </TD>
+    <!--descript--><TD>base portion of the name of the test netCDF file that
+            will exercise the DART routines that create the 
+            <em class="file">True_State.nc</em>,
+            <em class="file">Prior_Diag.nc</em>, and
+            <em class="file">Posterior_Diag.nc</em> files. The proper
+            file extension will be added.
+	    <br />
+	    Default 'check_me'</TD></TR>  
+
+<TR><!--contents--><TD valign=top> advance_time_present </TD>
+    <!--  type  --><TD valign=top> logical </TD>
+    <!--descript--><TD>Flag to indicate if the DART restart file has
+            the <em class="option">advance time</em> present in the file.
+	    <br />
+            Default: .FALSE.</TD></TR>  
+
+<TR><!--contents--><TD valign=top> x_ind </TD>
+    <!--  type  --><TD valign=top> integer </TD>
+    <!--descript--><TD>integer index into the DART state vector.
+	    This will be used to test the metadata routines.
+            Answers questions about location, what variable type is stored there, etc.
+	    <br />
+            Default: -1</TD></TR>  
+
+<TR><!--contents--><TD valign=top> loc_of_interest </TD>
+    <!--  type  --><TD valign=top> real(r8), dimension(3) </TD>
+    <!--descript--><TD>The lat/lon/level for a particular location.
+	    Tests the routine to find the closest gridpoint.
+	    <br />
+            Default: -1.0, -1.0, -1.0</TD></TR>  
+
+<TR><!--contents--><TD valign=top> kind_of_interest </TD>
+    <!--  type  --><TD valign=top> character(len=32) </TD>
+    <!--descript--><TD>Since there are usually many state variables on the same
+            grid, it may be useful to restrict the search for a location of interest
+	    to include a particular kind of state variable.
+	    <br />
+            Default: 'ANY'</TD></TR>  
+
+<TR><!--contents--><TD valign=top>   verbose   </TD>
+    <!--  type  --><TD valign=top>   logical   </TD>
+    <!--descript--><TD>Print extra info about the model_mod_check run.<br />
+            Default: .false. </TD></TR>  
+
+</TABLE>
+
+</div>
+<br />
+
+<!--==================================================================-->
+
+<A NAME="Modules"></A>
+<HR>
+<H2>OTHER MODULES USED</H2>
+<PRE>
+assim_model_mod
+types_mod
+location_mod
+model_mod
+null_mpi_utilities_mod
+obs_def_mod
+obs_kind_mod
+random_nr_mod
+random_seq_mod
+time_manager_mod
+model_mod_check
+utilities_mod
+</PRE>
+
+<!--==================================================================-->
+<!-- Describe the Files Used by this module.                          -->
+<!--==================================================================-->
+
+<A NAME="FilesUsed"></A>
+<HR>
+<H2>FILES</H2>
+<UL><LI><em class="file">input.nml</em> is used for 
+        <em class="code">model_mod_check_nml</em></LI>
+
+    <LI><em class="file">the "input_file" </em> can either be a
+        DART "ics" file - in which case there is a single time associated
+        with the state, or a DART "ud" file - which has an additional
+        "advance_to" time record.</LI>
+    <LI><em class="file">the "output_file"</em> is a netCDF file that
+        exercises the model_mod netcdf routines. Check the attributes, 
+        values, etc.</LI>
+    <LI><em class="file">allones.ics</em> is a DART initial conditions 
+        file that contains all 1's (ones). This gets created by 
+        <em class="program">model_mod_check</em>.
+        </LI>
+</UL>
+
+<!--==================================================================-->
+<!-- Discuss  typical usage of model_mod_check.                              -->
+<!--==================================================================-->
+
+<A NAME="Usage"></A>
+<HR>
+<H2>USAGE</H2>
+
+<P>
+Normal circumstances indicate that you are trying to put a new model into
+DART, so to be able to build and run <em class="program">model_mod_check</em>,
+you will need to create a <em class="file">path_names_model_mod_check</em>
+file with the following contents:
+<pre>
+assim_model/assim_model_mod.f90
+common/types_mod.f90
+location/threed_sphere/location_mod.f90
+models/<em class="input">your_model</em>/model_mod.f90
+mpi_utilities/null_mpi_utilities_mod.f90
+obs_def/obs_def_mod.f90
+obs_kind/obs_kind_mod.f90
+random_nr/random_nr_mod.f90
+random_seq/random_seq_mod.f90
+time_manager/time_manager_mod.f90
+utilities/model_mod_check.f90
+utilities/utilities_mod.f90
+</pre>
+as well as a <em class="file">mkmf_model_mod_check</em> script.
+You should be able to look at any other <em class="file">mkmf_xxxx</em> 
+script and figure out what to change. Once they exist:
+<br />
+<br />
+<div class="unix">
+<pre>
+[~/DART/models/yourmodel/work] % <em class="input">csh mkmf_model_mod_check</em>
+[~/DART/models/yourmodel/work] % <em class="input">make</em>
+[~/DART/models/yourmodel/work] % <em class="input">./model_mod_check</em>
+</pre>
+</div>
+</P>
+
+<P>
+Unlike other DART components, you are expected
+to modify <em class="file">model_mod_check.f90</em> to suit your needs as
+you develop your <em class="program">model_mod</em>. The code is roughly 
+divided into the following categories:
+<ol><li>Check the geometry information,</li>
+    <li>write a trivial restart file,</li>
+    <li>read either a restart file,</li>
+    <li>check the netCDF routines used to create the diagnostic output files,</li>
+    <li>check the metadata, and</li>
+    <li>[optionally] run a test of the model interpolation routine.</li>
+</ol>
+</P>
+
+<H3 class=indent1>Checking the Geometry Information:</H3>
+<P>
+The first block of code in <em class="program">model_mod_check</em>
+is intended to test some of the most basic routines, especially
+<em class="program">static_init_model</em> - which generally sets the
+geometry of the grid, the number of state variables and their shape, etc. 
+Virtually everything requires knowledge of the grid and state vector,
+so this block should never be skipped.
+</P>
+<pre>
+call initialize_utilities(progname='model_mod_check', output_flag=verbose)
+
+call find_namelist_in_file("input.nml", "model_mod_check_nml", iunit)
+read(iunit, nml = model_mod_check_nml, iostat = io)
+call check_namelist_read(iunit, io, "model_mod_check_nml")
+
+call static_init_model() ! Exercise the initialization process
+
+call get_gridsize(numlons, numlats, numlevs)
+write(*,'(''nlons, nlats, nlevs'',3(1x,i10))') numlons,numlats,numlevs
+
+x_size = get_model_size()
+write(*,'(''state vector has length'',i10)') x_size
+allocate(statevector(x_size))
+</pre>
+
+<H3 class=indent1>Writing a trivial restart file:</H3>
+<P>
+It's almost inconceivable that this cannot work, but sometimes it is
+just a nice sanity check to see how big a DART restart file for one
+ensemble member should be.
+</P>
+<pre>
+statevector = 1.0_r8;
+model_time  = set_time(21600, 149446)   ! 06Z 4 March 2010 in the Gregorian calendar
+
+iunit = open_restart_write('allones.ics')
+call awrite_state_restart(model_time, statevector, iunit)
+call close_restart(iunit)
+</pre>
+
+<H3 class=indent1>Reading a restart file:</H3>
+<P>
+I generally take the <em class="file">allones.ics</em> file into Matlab
+and stuff something interesting into the appropriate slots and write it
+out again so I can read it in for a more rigorous test of 
+<em class="program">model_mod:aread_state_restart()</em>. 
+Generally, I'll try to fill up what I *intend* to be the
+locations of the first variable with some constant value or some nice field
+from Matlab. The second variable gets its own field, etc. That way, when
+it's read it in, I know what I'm supposed to find in the output. 
+<em class="program">aread_state_restart()</em> is used to read restart files
+as well as the intermediate files created by DART right before the model advance.
+Those files (created internally by DART) have an additional data record specifying
+the "advance_to_time" of the model state. Common practice has the 
+<em class="program">dart_to_model</em> program reading this intermediate file and 
+communicating the advance_to_time to the model control mechanism and then parsing 
+the DART state vector into a form compatible with the model. <strong>TIP:</strong>
+if you write the restart files in ASCII, you can trivially add another DART time
+record in the first line to test the case in which the "advance_to_time" is present.
+</P>
+<pre>
+iunit = open_restart_read(input_file)
+if ( advance_time_present ) then
+   call aread_state_restart(model_time, statevector, iunit, adv_to_time)
+else
+   call aread_state_restart(model_time, statevector, iunit)
+endif
+
+call close_restart(iunit)
+call print_date( model_time,'model_mod_check:model date')
+call print_time( model_time,'model_mod_check:model time')
+</pre>
+
+<H3 class=indent1>Checking the diagnostic output netCDF routines:</H3>
+<P>This block happens after a call to 
+<em class="program">aread_state_restart()</em>, so, depending on 
+what was in the restart file (presumably, once you get 
+<em class="program">model_to_dart</em> working, you have converted
+a real model state to a DART restart and are using <em>that</em>), 
+you can fine-tune what gets put into the DART 
+<em class="file">True_State.nc</em>, 
+<em class="file">Prior_Diag.nc</em>, and
+<em class="file">Posterior_Diag.nc</em> diagnostic files. Only one
+ensemble member is needed to test the routines (hence the hardcoded 1
+in the test block).
+</P>
+<pre>
+state_meta(1) = 'restart test'
+ncFileID = init_diag_output(trim(output_file),'just testing a restart', 1, state_meta)
+call aoutput_diagnostics(ncFileID, model_time, statevector, 1)
+call nc_check( finalize_diag_output(ncFileID), 'model_mod_check:main', 'finalize')
+</pre>
+
+<H3 class=indent1>Check the metadata, and</H3>
+<P>It is critical to return the correct metadata for any given index into
+the DART state vector. This code block tests the two most common features of
+the metadata. As a bonus, this routine is also quite useful to determine
+EXACTLY where to place your first test observation. If you test precisely at
+a grid location, you should be able to really get a handle on debugging your
+<em class="program">model_interpolate()</em> routine. 
+The <em class="program">find_closest_gridpoint()</em> routine is designed to
+ensure that your variable layout is as you expect. "closest" in this context
+is close in the horizontal only - all vertical levels will be reported.
+</P>
+<pre>
+call check_meta_data( x_ind )
+call find_closest_gridpoint( loc_of_interest )
+</pre>
+
+<H3 class=indent1>[optionally] run a test of the model interpolation routine.</H3>
+<P>
+If you like, and you have a <em class="program">test_interpolate</em> subroutine,
+this would be the place to run it.
+</P>
+<pre>
+call test_interpolate(statevector, test_pressure = 500.0_r8, &amp;
+                                   start_lon = 142.5_r8)
+</pre>
+
+<!--==================================================================-->
+<!-- Cite references, if need be.                                     -->
+<!--==================================================================-->
+
+<A NAME="References"></A>
+<HR>
+<H2>REFERENCES</H2>
+<ol>
+<li> none </li>
+</ol>
+
+<!--==================================================================-->
+<!-- Describe all the error conditions and codes.                     -->
+<!--==================================================================-->
+
+<A NAME="Errors"></A>
+<HR>
+<H2>ERROR CODES and CONDITIONS</H2>
+<div class=errors>
+<P>There are no error conditions to check. This program is intended
+to demonstrate simple checks that will allow you to proceed with
+improving and testing the <em class="program">model_mod</em>. There
+will be plenty of run-time errors, I suggest compiling your code with 
+"bounds checking" turned on - at a minimum.
+</P>
+</div>
+
+<H2>KNOWN BUGS</H2>
+<P>
+none at this time
+</P>
+
+<!--==================================================================-->
+<!-- Describe Future Plans.                                           -->
+<!--==================================================================-->
+
+<A NAME="FuturePlans"></A>
+<HR>
+<H2>FUTURE PLANS</H2>
+<P>Expanded instructions on how to add a model, and how to methodically
+test piece-by-piece.
+</P>
+
+<!--==================================================================-->
+<!-- Legalese & Metadata                                              -->
+<!--==================================================================-->
+
+<A NAME="Legalese"></A>
+<HR>
+<H2>Terms of Use</H2>
+
+<P>
+DART software - Copyright &#169; 2004 - 2010 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>


Property changes on: DART/trunk/utilities/model_mod_check.html
___________________________________________________________________
Added: svn:mime-type
   + text/html
Added: svn:keywords
   + Date Rev Author HeadURL Id
Added: svn:eol-style
   + native

Added: DART/trunk/utilities/model_mod_check.nml
===================================================================
--- DART/trunk/utilities/model_mod_check.nml	                        (rev 0)
+++ DART/trunk/utilities/model_mod_check.nml	2011-03-11 22:45:03 UTC (rev 4795)
@@ -0,0 +1,10 @@
+&model_mod_check 
+   input_file           = "dart.ics",        
+   output_file          = "check_me",
+   advance_time_present = .FALSE.,
+   x_ind                = -1,
+   loc_of_interest      = -1.0, -1.0, -1.0,
+   kind_of_interest     = 'ANY'
+   verbose              = .FALSE.,
+   /
+


Property changes on: DART/trunk/utilities/model_mod_check.nml
___________________________________________________________________
Added: svn:mime-type
   + text/plain
Added: svn:eol-style
   + native


More information about the Dart-dev mailing list