! The grid file contains the following information,
!
!
! zt = depth of tracer points
! zb = depth of tracer_boundaries
!
! +---------------+
! | |
! | |
! | |
! | |
! | +zt_k |
! | |
! | |
! | |
! +------+zb_k----+
!
!
!
use mpp_mod, only : mpp_pe, mpp_root_pe, mpp_error, FATAL, NOTE, mpp_chksum
use mpp_mod, only : lowercase
use mpp_io_mod, only : MPP_NETCDF, MPP_RDONLY, MPP_ASCII, MPP_MULTI, MPP_SINGLE
use mpp_io_mod, only : mpp_open, mpp_write_meta, mpp_write, axistype, mpp_close
use mpp_io_mod, only : mpp_get_info, mpp_get_atts, mpp_get_axes, mpp_get_axis_data
use fms_mod, only : write_version_number, open_namelist_file, string
use fms_mod, only : file_exist, close_file, check_nml_error, stdlog, stdout
use grids_type_mod, only : vgrid_data_type
use grids_util_mod, only : make_axis, get_file_unit
use constants_mod, only : PI
implicit none
private
integer, parameter :: maxlen=10000,maxbounds=11
!------ namelist interface ---------------------------------------------
!------ specify a spherical grid resolution in depth
integer :: nzdepths = 0
real, dimension(maxbounds) :: z_depth, dz_depth
logical :: read_my_grid = .false.
character(len=128) :: my_grid_file = 'my_vgrid'
logical :: debug = .false.
character(len=24) :: z_axis_t = 'zt_k'
character(len=24) :: z_axis_b = 'zw_k'
integer :: z_axis_b_offset = 1
!
!