[Dart-dev] [3308] DART/trunk/models/MITgcm_ocean: The trans_pv_sv program takes snapshot files [S,T,U,V,SSH]."timestepcount" .[data,meta]

thoar at subversion.ucar.edu thoar at subversion.ucar.edu
Thu Apr 10 14:30:34 MDT 2008


An HTML attachment was scrubbed...
URL: http://mailman.ucar.edu/pipermail/dart-dev/attachments/20080410/c476a878/attachment-0001.html
-------------- next part --------------
Modified: DART/trunk/models/MITgcm_ocean/model_mod.f90
===================================================================
--- DART/trunk/models/MITgcm_ocean/model_mod.f90	2008-04-10 19:57:25 UTC (rev 3307)
+++ DART/trunk/models/MITgcm_ocean/model_mod.f90	2008-04-10 20:30:33 UTC (rev 3308)
@@ -15,10 +15,11 @@
 
 ! Modules that are absolutely required for use are listed
 use        types_mod, only : r4, r8
-use time_manager_mod, only : time_type, set_time, set_date, set_calendar_type, &
+use time_manager_mod, only : time_type, set_time, set_date, get_date, get_time, &
+                             set_calendar_type, GREGORIAN, print_time, print_date, &
                              operator(*),  operator(+), operator(-), &
                              operator(>),  operator(<), operator(/), &
-                             operator(/=), operator(<=), GREGORIAN
+                             operator(/=), operator(<=)
 use     location_mod, only : location_type,      get_close_maxdist_init, &
                              get_close_obs_init, get_close_obs, set_location, &
                              VERTISHEIGHT, get_location, vert_is_height, &
@@ -57,7 +58,8 @@
           MIT_meta_type, read_meta, write_meta, &
           read_snapshot, write_snapshot, get_gridsize, &
           snapshot_files_to_sv, sv_to_snapshot_files, &
-          MITtime_to_DARTtime
+          timestep_to_DARTtime, DARTtime_to_MITtime, &
+          DARTtime_to_timestepindex
 
 ! version controlled file description for error handling, do not edit
 character(len=128), parameter :: &
@@ -69,10 +71,10 @@
 logical,save :: module_initialized = .false.
 
 
-!! FIXME: on ifort, this must be 1
-!!        on xlf,   this must be 4 or 8?
-!! see the comments in the read_2d_snapshot code for more info
-integer, parameter :: item_size_direct_read = 8
+!! FIXME: This is horrid ... 'reclen' is machine-dependent.
+!! IBM XLF -- item_size_direct_access == 4,8
+!! IFORT   -- item_size_direct_access == 1   (number of 32bit words)
+integer, parameter :: item_size_direct_access = 1
 
 !------------------------------------------------------------------
 !
@@ -192,7 +194,6 @@
       rkFac, groundAtK1
 
 !--   Input files namelist
-! FIXME ... does DART even need these files?
 NAMELIST /PARM05/ &
       bathyFile, topoFile, shelfIceFile, &
       hydrogThetaFile, hydrogSaltFile, diffKrFile, &
@@ -237,7 +238,7 @@
 ! Grid parameters - the values will be read from a
 ! standard MITgcm namelist and filled in here.
 
-integer :: Nx, Ny, Nz    ! grid counts for each field
+integer :: Nx=-1, Ny=-1, Nz=-1    ! grid counts for each field
 
 ! locations of cell centers (C) and edges (G) for each axis.
 real(r8), allocatable :: XC(:), XG(:), YC(:), YG(:), ZC(:), ZG(:)
@@ -250,9 +251,7 @@
 !real(r8) :: delta_lat, delta_lon, delta_depth
 !real(r8), allocatable :: lat_grid(:), lon_grid(:), depth_grid(:)
 
-! fixme The natural model timestep?
 real(r8)        :: timestep = 900.0_r4
-!integer         :: timestepcount = 40992
 integer         :: timestepcount = 0
 type(time_type) :: model_time, model_timestep
 
@@ -355,6 +354,8 @@
    write(msgstring,*)"only have support for Gregorian"
    call error_handler(E_ERR,"static_init_model", msgstring, source, revision, revdate)
 endif
+write(*,*)'model_mod:namelist cal_NML',startDate_1,startDate_2
+write(*,nml=CAL_NML)
 
 ! Time stepping parameters are in PARM03
 call find_namelist_in_file("data", "PARM03", iunit)
@@ -364,10 +365,8 @@
 if ((deltaTmom   == deltaTtracer) .and. &
     (deltaTmom   == deltaTClock ) .and. &
     (deltaTClock == deltaTtracer)) then
-   ! FIXME ... what happens with deltaTmom > 86400 ? 
-   ! The time_step in terms of a time type must also be initialized.
-   model_timestep = set_time(nint(deltaTmom), 0)
-   timestep       = deltaTmom
+   model_timestep = set_time(nint(deltaTmom), 0) ! works with deltaTmom > 86400
+   timestep       = deltaTmom                    ! need a time_type version
 else
    write(msgstring,*)"namelist PARM03 has deltaTmom /= deltaTtracer /= deltaTClock"
    call error_handler(E_MSG,"static_init_model", msgstring, source, revision, revdate)
@@ -377,7 +376,7 @@
    call error_handler(E_ERR,"static_init_model", msgstring, source, revision, revdate)
 endif
 
-model_time = MITtime_to_DARTtime(timestepcount)
+model_time = timestep_to_DARTtime(timestepcount)
 
 ! Grid-related variables are in PARM04
 delX(:) = 0.0_r4
@@ -1738,11 +1737,11 @@
    filename = trim(fbase)//'.meta'
 endif
 
-! Initialize to bogus values
+! Initialize to (mostly) bogus values
 
 read_meta%nDims = 0
-read_meta%dimList = (/ 0, 0, 0 /)
-read_meta%dataprec = 'null'
+read_meta%dimList = (/ Nx, Ny, Nz /)
+read_meta%dataprec = 'float32'
 read_meta%reclen = 0
 read_meta%nrecords = 0
 read_meta%timeStepNumber = timestepcount
@@ -1926,7 +1925,7 @@
 open(unit=iunit, file=filename, action='write', form='formatted', iostat = io)
 if (io /= 0) then
    write(msgstring,*) 'unable to open file ', trim(filename), ' for writing'
-   call error_handler(E_ERR,'model_mod:read_meta',msgstring,source,revision,revdate)
+   call error_handler(E_ERR,'model_mod:write_meta',msgstring,source,revision,revdate)
 endif
 
 write(iunit, "(A,I5,A)") "nDims = [ ", metadata%nDims, " ];"
@@ -1942,7 +1941,7 @@
 
 write(iunit, "(A)") "];"
 
-write(iunit, "(3A)") "dataprec = [ ", trim(metadata%dataprec), " ];"
+write(iunit, "(3A)") "dataprec = [ '", trim(metadata%dataprec), "' ];"
 
 write(iunit, "(A,I5,A)") "nrecords = [ ", metadata%nrecords, " ];"
 
@@ -2019,13 +2018,10 @@
    call error_handler(E_ERR,"model_mod:read_2d_snapshot",msgstring,source,revision,revdate)
 endif
 
-!! FIXME: This is horrid ... 'reclen' is machine-dependent.
-!! IBM XLF -- item_size_direct_read == 4   (number of bytes)
-!! IFORT   -- item_size_direct_read == 1   (number of 32bit words)
-reclen = product(shape(x)) * item_size_direct_read
+reclen = product(shape(x)) * item_size_direct_access
 
-write(logfileunit,*)'item_size is ',item_size_direct_read, ' reclen is ',reclen
-write(     *     ,*)'item_size is ',item_size_direct_read, ' reclen is ',reclen
+write(logfileunit,*)'item_size is ',item_size_direct_access, ' reclen is ',reclen
+write(     *     ,*)'item_size is ',item_size_direct_access, ' reclen is ',reclen
 
 ! Get next available unit number, read file.
 
@@ -2121,7 +2117,7 @@
    call error_handler(E_ERR,"model_mod:read_3d_snapshot",msgstring,source,revision,revdate)
 endif
 
-reclen = product(shape(x)) * item_size_direct_read
+reclen = product(shape(x)) * item_size_direct_access
 
 ! Get next available unit number, read file.
 
@@ -2144,7 +2140,7 @@
 
 
 
-subroutine write_2d_snapshot(x, fbase)
+subroutine write_2d_snapshot(x, fbase, timestepindex)
 !------------------------------------------------------------------
 !
 ! This routine writes the Fortran direct access binary files ... eg
@@ -2153,8 +2149,9 @@
 !
 ! As it stands now ... the .data files appear to be big-endian.
 
-real(r4), dimension(:,:), intent(in)  :: x
-character(len=*), intent(in) :: fbase
+real(r4), dimension(:,:), intent(in) :: x
+character(len=*),         intent(in) :: fbase
+integer, optional,        intent(in) :: timestepindex
 
 character(len=128) :: metafilename, datafilename
 type(MIT_meta_type) :: metadata
@@ -2171,12 +2168,15 @@
 metadata%dataprec = "float32"
 metadata%reclen = Nx * Ny 
 metadata%nrecords = 1
-! FIXME: make this an optional input and if(present()) write it
-metadata%timeStepNumber = 0
+if (present(timestepindex)) then
+   metadata%timeStepNumber = timestepindex
+else
+   metadata%timeStepNumber = 0
+endif
 
 call write_meta(metadata, fbase)
 
-reclen = metadata%reclen * item_size_direct_read
+reclen = metadata%reclen * item_size_direct_access
 
 iunit = get_unit()
 open(unit=iunit, file=datafilename, action='write', access='direct', recl=reclen, iostat=io)
@@ -2196,7 +2196,7 @@
 end subroutine write_2d_snapshot
 
 
-subroutine write_3d_snapshot(x, fbase)
+subroutine write_3d_snapshot(x, fbase, timestepindex)
 !------------------------------------------------------------------
 !
 ! This routine writes the Fortran direct access binary files ... eg
@@ -2205,8 +2205,9 @@
 !
 ! As it stands now ... the .data files appear to be big-endian.
 
-real(r4), dimension(:,:,:), intent(in)  :: x
-character(len=*), intent(in) :: fbase
+real(r4), dimension(:,:,:), intent(in) :: x
+character(len=*),           intent(in) :: fbase
+integer, optional,          intent(in) :: timestepindex
 
 character(len=128) :: metafilename, datafilename
 type(MIT_meta_type) :: metadata
@@ -2220,15 +2221,18 @@
 
 metadata%nDims = 3
 metadata%dimList(:) = (/ Nx, Ny, Nz /)
-metadata%dataprec = "float32"
+metadata%dataprec = "float32"     ! FIXME depends on defn of 'r4' 
 metadata%reclen = Nx * Ny * Nz
 metadata%nrecords = 1
-! FIXME: make this an optional input and if(present()) write it
-metadata%timeStepNumber = 0
+if (present(timestepindex)) then
+   metadata%timeStepNumber = timestepindex
+else
+   metadata%timeStepNumber = 0
+endif
 
 call write_meta(metadata, fbase)
 
-reclen = metadata%reclen * item_size_direct_read
+reclen = metadata%reclen * item_size_direct_access
 
 ! Get next available unit number, write file.
 
@@ -2310,12 +2314,11 @@
 
 
 
-subroutine sv_to_snapshot_files(state_vector, basename, timestepcount)
+subroutine sv_to_snapshot_files(state_vector, date1, date2)
 !------------------------------------------------------------------
 !
- real(r8), intent(in) :: state_vector(:)
- character(len=*), intent(in) :: basename
- integer, intent(in) :: timestepcount 
+real(r8), intent(in) :: state_vector(:)
+integer,  intent(in) :: date1, date2 
 
 ! temp space to hold data while we are writing it
 real(r4) :: data_2d_array(Nx,Ny), data_3d_array(Nx,Ny,Nz)
@@ -2335,11 +2338,10 @@
 do l=1, n3dfields
 
    ! the filenames are going to be constructed here and assumed to be:
-   !  Varable.Basename.Timestep.data  and .meta
+   !  Variable.Basename.Timestep.data  and .meta
    ! e.g. S.Prior.0000000672.data
    !      S.Prior.0000000672.meta
-   write(prefixstring, "(A,I10.10)") &
-         trim(progvarnames(l))//'.'//trim(basename)//'.', timestepcount
+   write(prefixstring, '(A,''.'',I8.8,''.'',I6.6)') trim(progvarnames(l)),date1,date2
 
    do k = 1, Nz
    do j = 1, Ny
@@ -2349,15 +2351,14 @@
    enddo
    enddo
    enddo
-   call write_snapshot(data_3d_array, prefixstring)
+   call write_snapshot(data_3d_array, prefixstring, timestepcount)
 
 enddo
 
 ! and finally, SSH (and any other 2d fields)
 do l=(n3dfields+1), (n3dfields+n2dfields)
 
-   write(prefixstring, "(A,I10.10)") &
-         trim(progvarnames(l))//'.'//trim(basename)//'.', timestepcount
+   write(prefixstring, '(A,''.'',I8.8,''.'',I6.6)') trim(progvarnames(l)),date1,date2
 
    do j = 1, Ny
    do i = 1, Nx
@@ -2365,7 +2366,7 @@
       indx = indx + 1
    enddo
    enddo
-   call write_snapshot(data_2d_array, prefixstring)
+   call write_snapshot(data_2d_array, prefixstring, timestepcount)
 
 enddo
 
@@ -2498,11 +2499,11 @@
 
 if (dim1 /= Nx) then
    write(msgstring,*)trim(varname),' 2d array dim 1 ',dim1,' /= ',Nx
-   call error_handler(E_ERR,'model_mod:vector_to_prog_var',msgstring,source,revision,revdate) 
+   call error_handler(E_ERR,'model_mod:vector_to_2d__prog_var',msgstring,source,revision,revdate) 
 endif
 if (dim2 /= Ny) then
    write(msgstring,*)trim(varname),' 2d array dim 2 ',dim2,' /= ',Ny
-   call error_handler(E_ERR,'model_mod:vector_to_prog_var',msgstring,source,revision,revdate) 
+   call error_handler(E_ERR,'model_mod:vector_to__2d_prog_var',msgstring,source,revision,revdate) 
 endif
 
 ii = start_index(varindex)
@@ -2539,15 +2540,15 @@
 
 if (dim1 /= Nx) then
    write(msgstring,*)trim(varname),' 3d array dim 1 ',dim1,' /= ',Nx
-   call error_handler(E_ERR,'model_mod:vector_to_prog_var',msgstring,source,revision,revdate) 
+   call error_handler(E_ERR,'model_mod:vector_to_3d_prog_var',msgstring,source,revision,revdate) 
 endif
 if (dim2 /= Ny) then
    write(msgstring,*)trim(varname),' 3d array dim 2 ',dim2,' /= ',Ny
-   call error_handler(E_ERR,'model_mod:vector_to_prog_var',msgstring,source,revision,revdate) 
+   call error_handler(E_ERR,'model_mod:vector_to_3d_prog_var',msgstring,source,revision,revdate) 
 endif
 if (dim3 /= Nz) then
    write(msgstring,*)trim(varname),' 3d array dim 3 ',dim3,' /= ',Nz
-   call error_handler(E_ERR,'model_mod:vector_to_prog_var',msgstring,source,revision,revdate) 
+   call error_handler(E_ERR,'model_mod:vector_to_3d_prog_var',msgstring,source,revision,revdate) 
 endif
 
 ii = start_index(varindex)
@@ -2565,7 +2566,7 @@
 
 
 
-function MITtime_to_DARTtime(TimeStepIndex)
+function timestep_to_DARTtime(TimeStepIndex)
 !
 ! The MITtime is composed of an offset to a fixed time base.
 ! The base time is derived from the namelist in 'date.cal',
@@ -2578,7 +2579,7 @@
 ! (namelist) deltaTmom   aka 'timestep' ... r4 ... implies roundoff nuances
 !
 integer, intent(in) :: TimeStepIndex
-type(time_type)     :: MITtime_to_DARTtime
+type(time_type)     :: timestep_to_DARTtime
 
 integer         :: yy,mn,dd,hh,mm,ss
 integer         :: modeloffset, maxtimestep
@@ -2598,7 +2599,7 @@
 if (TimeStepIndex >= maxtimestep) then
    write(msgstring,*)' timestepindex (',TimeStepIndex, &
                      ') * timestep (',timestep,') overflows.'
-   call error_handler(E_ERR,'model_mod:MITtime_to_DARTtime',msgstring,source,revision,revdate) 
+   call error_handler(E_ERR,'model_mod:timestep_to_DARTtime',msgstring,source,revision,revdate) 
 endif
 
 modeloffset = nint(TimeStepIndex * timestep)
@@ -2616,11 +2617,80 @@
 mm = mod(startDate_2/100,100)
 ss = mod(startDate_2,100)
 
-MITtime_to_DARTtime =  set_date(yy,mn,dd,hh,mm,ss) + offset
+timestep_to_DARTtime =  set_date(yy,mn,dd,hh,mm,ss) + offset
 
-end function MITtime_to_DARTtime
+end function timestep_to_DARTtime
 
 
+
+subroutine DARTtime_to_MITtime(darttime,date1,date2)
+!
+! The MITtime is composed of an offset to a fixed time base.
+! The base time is derived from the namelist in 'date.cal',
+! the model timestep (deltaT) is from the namelist 'PARM03',
+! and the timestepindex is the middle portion of the filename
+! of the MIT files   [S,T,U,V,SSH].nnnnnnnnnn.dat 
+!
+! (namelist) startDate_1  yyyymmdd (year/month/day)
+! (namelist) startDate_2    hhmmss (hours/minutes/seconds)
+! (namelist) deltaTmom   aka 'timestep' ... r4 ... implies roundoff nuances
+!
+type(time_type), intent(in)  :: darttime
+integer,         intent(out) :: date1, date2
+
+integer         :: yy,mn,dd,hh,mm,ss
+
+if ( .not. module_initialized ) call static_init_model
+
+write(*,*)'DART2MIT ',startDate_1,startDate_2
+
+call print_date(darttime,'DART2MIT dart model time')
+
+call get_date(darttime,yy,mn,dd,hh,mm,ss)
+
+date1 = yy*10000 + mn*100 + dd
+date2 = hh*10000 + mm*100 + ss
+
+end subroutine DARTtime_to_MITtime
+
+
+
+function DARTtime_to_timestepindex(mytime)
+!
+! The MITtime is composed of an offset to a fixed time base.
+! The base time is derived from the namelist in 'date.cal',
+! the model timestep (deltaT) is from the namelist 'PARM03',
+! and the timestepindex is the middle portion of the filename
+! of the MIT files   [S,T,U,V,SSH].nnnnnnnnnn.dat 
+!
+! (namelist) startDate_1  yyyymmdd (year/month/day)
+! (namelist) startDate_2    hhmmss (hours/minutes/seconds)
+! (namelist) deltaTmom   aka 'timestep' ... r4 ... implies roundoff nuances
+!
+type(time_type), intent(in)  :: mytime
+integer                      :: DARTtime_to_timestepindex
+
+integer :: dd,ss
+type(time_type) :: timeorigin, offset
+
+if ( .not. module_initialized ) call static_init_model
+
+timeorigin = timestep_to_DARTtime(0)
+offset     = mytime - timeorigin
+call get_time(offset,ss,dd)
+
+if (dd >= (HUGE(dd)/86400)) then   ! overflow situation
+   call print_time(mytime,'DART time is',logfileunit)
+   write(msgstring,*)'Trying to convert DART time to MIT timestep overflows'
+   call error_handler(E_ERR,'model_mod:DARTtime_to_timestepindex',msgstring,source,revision,revdate) 
+endif
+
+DARTtime_to_timestepindex = nint((dd*86400+ss) / timestep)
+
+end function DARTtime_to_timestepindex
+
+
+
 subroutine get_gridsize(num_x, num_y, num_z)
 !------------------------------------------------------------------
 !

Modified: DART/trunk/models/MITgcm_ocean/trans_pv_sv.f90
===================================================================
--- DART/trunk/models/MITgcm_ocean/trans_pv_sv.f90	2008-04-10 19:57:25 UTC (rev 3307)
+++ DART/trunk/models/MITgcm_ocean/trans_pv_sv.f90	2008-04-10 20:30:33 UTC (rev 3308)
@@ -34,7 +34,7 @@
 use    utilities_mod, only : E_ERR, E_WARN, E_MSG, error_handler, logfileunit, &
                              initialize_utilities, finalize_utilities
 use        model_mod, only : snapshot_files_to_sv, static_init_model, &
-                             get_model_size, MITtime_to_DARTtime
+                             get_model_size, timestep_to_DARTtime
 use  assim_model_mod, only : awrite_state_restart, open_restart_write, close_restart
 use time_manager_mod, only : time_type, print_time, print_date
 
@@ -51,12 +51,11 @@
 ! Reading from stdin 
 ! eg. [S,T,U,V,Eta].0000040992.[data,meta]
 integer :: timestep = 40992
-character (len = 128) :: file_base = '0000040992'
+character (len = 128) :: file_base
 character (len = 128) :: file_out  = 'assim_model_state_ud'
 
 integer                :: io, iunit, x_size
-integer                :: Nx, Ny, Nz
-type(time_type)        :: model_time, adv_to_time
+type(time_type)        :: model_time
 real(r8), allocatable  :: statevector(:)
 
 !----------------------------------------------------------------------
@@ -89,11 +88,11 @@
 ! Use the MIT namelist and timestepcount in the meta file to construct
 ! the current time, allocate the local state vector, and fill
 
-!model_time = MITtime_to_DARTtime(0)
+!model_time = timestep_to_DARTtime(0)
 !call print_time(model_time,'time for timestep 0')
 !call print_date(model_time,'time for timestep 0')
 
-model_time = MITtime_to_DARTtime(timestep)
+model_time = timestep_to_DARTtime(timestep)
 
 call print_time(model_time,'time for '//file_base)
 call print_date(model_time,'time for '//file_base)
@@ -103,6 +102,8 @@
 allocate(statevector(x_size))
 call snapshot_files_to_sv(timestep, statevector) ! model_mod() knows all this
 
+! could also compare the timestep from the snapshot file to model_time ...
+! extra layer of bulletproofing.
 
 iunit = open_restart_write(file_out)
 call awrite_state_restart(model_time, statevector, iunit)

Modified: DART/trunk/models/MITgcm_ocean/trans_sv_pv.f90
===================================================================
--- DART/trunk/models/MITgcm_ocean/trans_sv_pv.f90	2008-04-10 19:57:25 UTC (rev 3307)
+++ DART/trunk/models/MITgcm_ocean/trans_sv_pv.f90	2008-04-10 20:30:33 UTC (rev 3308)
@@ -3,160 +3,121 @@
 ! University Corporation for Atmospheric Research
 ! Licensed under the GPL -- www.gpl.org/licenses/gpl.html
  
-program trans_pv_sv
+program trans_sv_pv
 
 !----------------------------------------------------------------------
-! purpose: interface between MITgcm_ocean and DART
+! purpose: interface between DART and the MITgcm_ocean model
 !
-! method: Read MITgcm_ocean "snapshot" files of model state
-!         Reform fields into a DART state vector (control vector).
-!         Write out state vector in "proprietary" format for DART.
-!         The output is a "DART restart file" format.
+! method: Read DART state vector (in file 'assim_model_state_ic') and 
+!         write out MITgcm_ocean "snapshot" files.
 !
-! author: Tim Hoar 3/13/08
-! more mangling:  nancy collins 14mar08
+! author: Tim Hoar 5Apr08
 !
 !----------------------------------------------------------------------
 
 ! <next few lines under version control, do not edit>
-! $URL: http://subversion.ucar.edu/DAReS/DART/trunk/models/MITgcm_ocean/trans_pv_sv.f90 $
-! $Id: trans_pv_sv.f90 3258 2008-03-14 15:58:36Z thoar $
+! $URL: http://subversion.ucar.edu/DAReS/DART/trunk/models/MITgcm_ocean/trans_sv_pv.f90 $
+! $Id: trans_sv_pv.f90 3258 2008-03-14 15:58:36Z thoar $
 ! $Revision: 3258 $
 ! $Date: 2008-03-14 09:58:36 -0600 (Fri, 14 Mar 2008) $
 
 use        types_mod, only : r4, r8
-use    utilities_mod, only : get_unit, file_exist, E_ERR, E_WARN, E_MSG, &
+use    utilities_mod, only : E_ERR, E_WARN, E_MSG, error_handler, open_file, &
                              initialize_utilities, finalize_utilities, &
-                             error_handler
-use        model_mod, only : MIT_meta_type, read_meta, read_snapshot, &
-                             prog_var_to_vector, static_init_model, &
-                             get_model_size, get_gridsize
-use  assim_model_mod, only : assim_model_type, static_init_assim_model, &
-                             init_assim_model, get_model_size, set_model_state_vector, &
-                             write_state_restart, set_model_time, open_restart_read, &
-                             open_restart_write, close_restart, aread_state_restart
-use time_manager_mod, only : time_type, read_time
+                             find_namelist_in_file, check_namelist_read
+use        model_mod, only : sv_to_snapshot_files, static_init_model, &
+                             get_model_size, DARTtime_to_MITtime, &
+                             get_model_time_step
+use  assim_model_mod, only : open_restart_read, aread_state_restart, close_restart
+use time_manager_mod, only : time_type, get_time, print_time, print_date, &
+                             operator(-)
 
 implicit none
 
 ! version controlled file description for error handling, do not edit
 character(len=128), parameter :: &
-   source   = "$URL: http://subversion.ucar.edu/DAReS/DART/trunk/models/MITgcm_ocean/trans_pv_sv.f90 $", &
+   source   = "$URL: http://subversion.ucar.edu/DAReS/DART/trunk/models/MITgcm_ocean/trans_sv_pv.f90 $", &
    revision = "$Revision: 3258 $", &
    revdate  = "$Date: 2008-03-14 09:58:36 -0600 (Fri, 14 Mar 2008) $"
 
-character (len = 128) :: msgstring
+character (len = 128) :: file_in  = 'assim_model_state_ic'
 
-! eg. [S,T,U,V,SSH].0000040992.[data,meta]
+!------------------------------------------------------------------
+! The time manager namelist variables
+! some types/etc come from   <mitsource>/pkg/cal/cal.h
+! some useful insight from   cal_set.F, cal_convdate.F
 !
-! The '.meta' file contains matlab-format information about shapes, etc.
+! startDate_1 (integer) yyyymmdd   "start date of the integration"
+! startDate_2 (integer) hhmmss
+!------------------------------------------------------------------
 
-character (len = 128) :: file_base = '0000000672'
-character (len = 128) :: S_filename
-character (len = 128) :: T_filename
-character (len = 128) :: U_filename
-character (len = 128) :: V_filename
-character (len = 128) :: SSH_filename
+character(len=9) :: TheCalendar = 'gregorian'
+integer          :: startDate_1 = 19530101
+integer          :: startDate_2 =          60000
+logical          :: calendarDumps = .false.
 
-character (len = 128) :: file_out = 'temp_ud', file_time = 'temp_ic'
+NAMELIST /CAL_NML/ TheCalendar, startDate_1, startDate_2, calendarDumps
 
-! Temporary allocatable storage to read in a native format for cam state
-type(assim_model_type) :: x
-!type(model_type)       :: var
-type(time_type)        :: model_time, adv_to_time
+!----------------------------------------------------------------------
 
-real(r4), allocatable  :: S(:,:,:)
-real(r4), allocatable  :: T(:,:,:)
-real(r4), allocatable  :: U(:,:,:)
-real(r4), allocatable  :: V(:,:,:)
-real(r4), allocatable  :: SSH(:,:)
+integer               :: iunit, io, x_size
+integer               :: secs, days
+type(time_type)       :: model_time, adv_to_time
+type(time_type)       :: model_timestep, offset
+real(r8), allocatable :: statevector(:)
 
-real(r8), allocatable  :: x_state(:)
-
-integer                :: file_unit, x_size, timestep
-integer                :: Nx,Ny,Nz
-type(MIT_meta_type) :: mitmeta
-
-!
-! end of variable decls
-! 
 !----------------------------------------------------------------------
-!
-! code start
-!
 
-! The strategy here is to use the 'write_state_restart()' routine - 
-! which requires an 'assim_model_type' variable.  
-! Read the individual variables and pack them
-! into one big state vector, add a time type and make nn
+call initialize_utilities('trans_sv_pv')
+call static_init_model()
 
-call initialize_utilities('trans_pv_sv')
+! MIT calendar information. The namelist is already read in 
+! static_init_model(), so no further bulletproofing is needed here.
+call find_namelist_in_file("data.cal", "CAL_NML", iunit)
+read(iunit, nml = CAL_NML, iostat = io)
+call check_namelist_read(iunit, io, "CAL_NML")
 
-call read_snapshot('XC',SSH,timestep)
+x_size = get_model_size()
+allocate(statevector(x_size))
 
-! Static init assim model calls static_init_model
-call static_init_assim_model()
-call init_assim_model(x)
+!----------------------------------------------------------------------
+! Reads the valid time, the state, and the target time.
+!----------------------------------------------------------------------
 
-write(*,*)'dimensions are ',shape(SSH)
-write(*,*)'model size is ',get_model_size()
+iunit = open_restart_read(file_in)
+call aread_state_restart(model_time, statevector, iunit, adv_to_time)
+call close_restart(iunit)
 
-print *, ' !! THIS FILE IS NOT DONE -- IT WAS A COPY OF PV -> SV'
-print *, ' !! IN REALITY IT NEEDS TO GO SV -> PV'
-stop
+! call print_date(model_time,'dart model date')
+! call print_time(model_time,'dart model time')
+! call print_date(adv_to_time,'advance_to date')
+! call print_time(adv_to_time,'advance_to time')
 
-! Read the [meta,data] files 
+!----------------------------------------------------------------------
+! update the CAL_NML variables so we can rewrite that namelist.
+! Ultimately, we want to keep data:&PARM03:startTime = 0.,
+!----------------------------------------------------------------------
 
-mitmeta = read_meta(file_base,'U')
-write(*,*)'timestep is ',timestep
+call DARTtime_to_MITtime(  model_time, startDate_1, startDate_2)
+call sv_to_snapshot_files(statevector, startDate_1, startDate_2)
 
-allocate(S(Nx,Ny,Nz))
-allocate(T(Nx,Ny,Nz))
-allocate(U(Nx,Ny,Nz))
-allocate(V(Nx,Ny,Nz))
-allocate(SSH(Nx,Ny))
+iunit = open_file('data.cal.new',form='formatted',action='rewind')
+write(iunit, nml=CAL_NML)
+close(iunit)
 
-call read_snapshot(file_base,S,timestep,'S')
-call read_snapshot(file_base,T,timestep,'T')
-call read_snapshot(file_base,U,timestep,'U')
-call read_snapshot(file_base,V,timestep,'V')
-call read_snapshot(file_base,SSH,timestep,'ETA')
+!----------------------------------------------------------------------
+! convert the adv_to_time to the appropriate number of seconds.
+!----------------------------------------------------------------------
 
-! matlab debug messages
-! write(8)mitmeta%dimList
-! write(8)S
-! close(8)
+model_timestep = get_model_time_step()
+offset         = adv_to_time - model_time
 
-! Allocate the local state vector and fill it up.
+call get_time(offset, secs, days)
 
-x_size = size(S) + size(T) + size(U) + size(V) + size(SSH)
+write(*, nml=CAL_NML)
+write(*, *)'PARM03 startTime ',0.0
+write(*, *)'PARM03   endTime ',(secs + days*86400)
 
-if ( x_size /= get_model_size() ) then
-   write(msgstring,*)'data size ',x_size,' /= ',get_model_size(),' model size'
-   call error_handler(E_ERR,'trans_pv_sv',msgstring,source,revision,revdate)
-endif
-
-allocate(x_state(x_size))
-
-! transform fields into state vector for DART
-call prog_var_to_vector(S,T,U,V,SSH,x_state)
-
-! use the MIT namelist and timestepcount in the meta file to construct
-! the current time.  we do not have a restart file to read; this program
-! is creating one.
-
-! We're done with x_state, so it can be uselessly filled in aread_state_restart,
-! while getting model_time.
-!call aread_state_restart(model_time, x_state, file_unit, adv_to_time)
-!call set_model_time (x, adv_to_time)
-!call close_restart(file_unit)
-
-! Get channel for output,
-! write out state vector in "proprietary" format
-!file_unit = open_restart_write(file_out)
-!call write_state_restart(x, file_unit)
-!call close_restart(file_unit)
-
 call finalize_utilities()
 
-end program trans_pv_sv
+end program trans_sv_pv


More information about the Dart-dev mailing list