chore: append -dev to version number (#1641)
[FMS.git] / mpp / mpp_io.F90
blob297f2df41e4543fe1ea51d3a91afbcbc7e01d6b5
1 !***********************************************************************
2 !*                   GNU Lesser General Public License
3 !*
4 !* This file is part of the GFDL Flexible Modeling System (FMS).
5 !*
6 !* FMS is free software: you can redistribute it and/or modify it under
7 !* the terms of the GNU Lesser General Public License as published by
8 !* the Free Software Foundation, either version 3 of the License, or (at
9 !* your option) any later version.
11 !* FMS is distributed in the hope that it will be useful, but WITHOUT
12 !* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
13 !* FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
14 !* for more details.
16 !* You should have received a copy of the GNU Lesser General Public
17 !* License along with FMS.  If not, see <http://www.gnu.org/licenses/>.
18 !***********************************************************************
19 !-----------------------------------------------------------------------
20 !                 Parallel I/O for message-passing codes
22 ! AUTHOR: V. Balaji (vb@gfdl.gov)
23 !         SGI/GFDL Princeton University
25 !-----------------------------------------------------------------------
27 !> @defgroup mpp_io_mod mpp_io_mod
28 !> @ingroup mpp
29 !> @brief a set of simple calls for parallel I/O on
30 !!   distributed systems. It is geared toward the writing of data in netCDF
31 !!   format
32 !> @author V. Balaji <"vb@gfdl.noaa.gov">
34 !> In massively parallel environments, an often difficult problem is
35 !! the reading and writing of data to files on disk. MPI-IO and MPI-2 IO
36 !! are moving toward providing this capability, but are currently not
37 !! widely implemented. Further, it is a rather abstruse
38 !! API. @ref mpp_io_mod is an attempt at a simple API encompassing a
39 !! certain variety of the I/O tasks that will be required. It does not
40 !! attempt to be an all-encompassing standard such as MPI, however, it
41 !! can be implemented in MPI if so desired. It is equally simple to add
42 !! parallel I/O capability to @ref mpp_io_mod based on vendor-specific
43 !! APIs while providing a layer of insulation for user codes.
45 !! The @ref mpp_io_mod parallel I/O API built on top of the <LINK
46 !! SRC="mpp_domains.html">mpp_domains_mod</LINK> and <LINK
47 !! SRC="mpp.html">mpp_mod</LINK> API for domain decomposition and
48 !! message passing. Features of @ref mpp_io_mod include:
50 !! 1) Simple, minimal API, with free access to underlying API for more
51 !! complicated stuff.<BR/>
52 !! 2) Self-describing files: comprehensive header information
53 !! (metadata) in the file itself.<BR/>
54 !! 3) Strong focus on performance of parallel write: the climate models
55 !! for which it is designed typically read a minimal amount of data
56 !! (typically at the beginning of the run); but on the other hand, tend
57 !! to write copious amounts of data during the run. An interface for
58 !! reading is also supplied, but its performance has not yet been optimized.<BR/>
59 !! 4) Integrated netCDF capability: <LINK SRC
60 !! ="http://www.unidata.ucar.edu/packages/netcdf/">netCDF</LINK> is a
61 !! data format widely used in the climate/weather modeling
62 !! community. netCDF is considered the principal medium of data storage
63 !! for @ref mpp_io_mod. But I provide a raw unformatted
64 !! fortran I/O capability in case netCDF is not an option, either due to
65 !! unavailability, inappropriateness, or poor performance.<BR/>
66 !! 5) May require off-line post-processing: a tool for this purpose,
67 !! <TT>mppnccombine</TT>, is available. GFDL users may use
68 !! <TT>~hnv/pub/mppnccombine</TT>. Outside users may obtain the
69 !! source <LINK SRC
70 !! ="ftp://ftp.gfdl.gov/perm/hnv/mpp/mppnccombine.c">here</LINK>.  It
71 !! can be compiled on any C compiler and linked with the netCDF
72 !! library. The program is free and is covered by the <LINK SRC
73 !! ="ftp://ftp.gfdl.gov/perm/hnv/mpp/LICENSE">GPL license</LINK>.
75 !! The internal representation of the data being written out is
76 !! assumed be the default real type, which can be 4 or 8-byte. Time data
77 !! is always written as 8-bytes to avoid overflow on climatic time scales
78 !! in units of seconds.
80 !! <LINK SRC="modes"></LINK><H4>I/O modes in @ref mpp_io_mod</H4>
82 !! The I/O activity critical to performance in the models for which
83 !! @ref mpp_io_mod is designed is typically the writing of large
84 !! datasets on a model grid volume produced at intervals during
85 !! a run. Consider a 3D grid volume, where model arrays are stored as
86 !! <TT>(i,j,k)</TT>. The domain decomposition is typically along
87 !! <TT>i</TT> or <TT>j</TT>: thus to store data to disk as a global
88 !! volume, the distributed chunks of data have to be seen as
89 !! non-contiguous. If we attempt to have all PEs write this data into a
90 !! single file, performance can be seriously compromised because of the
91 !! data reordering that will be required. Possible options are to have
92 !! one PE acquire all the data and write it out, or to have all the PEs
93 !! write independent files, which are recombined offline. These three
94 !! modes of operation are described in the @ref mpp_io_mod terminology
95 !! in terms of two parameters, <I>threading</I> and <I>fileset</I>,
96 !! as follows:
98 !! <I>Single-threaded I/O:</I> a single PE acquires all the data
99 !! and writes it out.<BR/>
100 !! <I>Multi-threaded, single-fileset I/O:</I> many PEs write to a
101 !! single file.<BR/>
102 !! <I>Multi-threaded, multi-fileset I/O:</I> many PEs write to
103 !! independent files. This is also called <I>distributed I/O</I>.
105 !! The middle option is the most difficult to achieve performance. The
106 !! choice of one of these modes is made when a file is opened for I/O, in
107 !! <LINK SRC="#mpp_open">mpp_open</LINK>.
109 !! <LINK name="metadata"></LINK><H4>Metadata in @ref mpp_io_mod</H4>
111 !! A requirement of the design of @ref mpp_io_mod is that the file must
112 !! be entirely self-describing: comprehensive header information
113 !! describing its contents is present in the header of every file. The
114 !! header information follows the model of netCDF. Variables in the file
115 !! are divided into <I>axes</I> and <I>fields</I>. An axis describes a
116 !! co-ordinate variable, e.g <TT>x,y,z,t</TT>. A field consists of data in
117 !! the space described by the axes. An axis is described in
118 !! @ref mpp_io_mod using the defined type <TT>axistype</TT>:
120 !! <PRE>
121 !!   type, public :: axistype
122 !!      sequence
123 !!      character(len=128) :: name
124 !!      character(len=128) :: units
125 !!      character(len=256) :: longname
126 !!      character(len=8) :: cartesian
127 !!      integer :: len
128 !!      integer :: sense           !+/-1, depth or height?
129 !!      type(domain1D), pointer :: domain
130 !!      real, dimension(:), pointer :: data
131 !!      integer :: id, did
132 !!      integer :: type  ! external NetCDF type format for axis data
133 !!      integer :: natt
134 !!      type(atttype), pointer :: Att(:) ! axis attributes
135 !!   end type axistype
136 !!   </PRE>
138 !!   A field is described using the type <TT>fieldtype</TT>:
140 !!   <PRE>
141 !!   type, public :: fieldtype
142 !!      sequence
143 !!      character(len=128) :: name
144 !!      character(len=128) :: units
145 !!      character(len=256) :: longname
146 !!      real :: min, max, missing, fill, scale, add
147 !!      integer :: pack
148 !!      type(axistype), dimension(:), pointer :: axes
149 !!      integer, dimension(:), pointer :: size
150 !!      integer :: time_axis_index
151 !!      integer :: id
152 !!      integer :: type ! external NetCDF format for field data
153 !!      integer :: natt, ndim
154 !!      type(atttype), pointer :: Att(:) ! field metadata
155 !!   end type fieldtype
156 !!   </PRE>
158 !!   An attribute (global, field or axis) is described using the <TT>atttype</TT>:
160 !!   <PRE>
161 !!   type, public :: atttype
162 !!      sequence
163 !!      integer :: type, len
164 !!      character(len=128) :: name
165 !!      character(len=256)  :: catt
166 !!      real(r4_kind), pointer :: fatt(:)
167 !!   end type atttype
168 !!   </PRE>
170 !!   <LINK name="packing"></LINK>This default set of field attributes corresponds
171 !!   closely to various conventions established for netCDF files. The
172 !!   <TT>pack</TT> attribute of a field defines whether or not a
173 !!   field is to be packed on output. Allowed values of
174 !!   <TT>pack</TT> are 1,2,4 and 8. The value of
175 !!   <TT>pack</TT> is the number of variables written into 8
176 !!   bytes. In typical use, we write 4-byte reals to netCDF output; thus
177 !!   the default value of <TT>pack</TT> is 2. For
178 !!   <TT>pack</TT> = 4 or 8, packing uses a simple-minded linear
179 !!   scaling scheme using the <TT>scale</TT> and <TT>add</TT>
180 !!   attributes. There is thus likely to be a significant loss of dynamic
181 !!   range with packing. When a field is declared to be packed, the
182 !!   <TT>missing</TT> and <TT>fill</TT> attributes, if
183 !!   supplied, are packed also.
185 !!   Please note that the pack values are the same even if the default
186 !!   real is 4 bytes, i.e <TT>PACK=1</TT> still follows the definition
187 !!   above and writes out 8 bytes.
189 !!   A set of <I>attributes</I> for each variable is also available. The
190 !!   variable definitions and attribute information is written/read by calling
191 !!   <LINK SRC="#mpp_write_meta">mpp_write_meta</LINK> or <LINK SRC="#mpp_read_meta">mpp_read_meta</LINK>. A typical
192 !!   calling sequence for writing data might be:
194 !!   <PRE>
195 !!   ...
196 !!     type(domain2D), dimension(:), allocatable, target :: domain
197 !!     type(fieldtype) :: field
198 !!     type(axistype) :: x, y, z, t
199 !!   ...
200 !!     call mpp_define_domains( (/1,nx,1,ny/), domain )
201 !!     allocate( a(domain(pe)%x%data%start_index:domain(pe)%x%data%end_index, &
202 !!                 domain(pe)%y%data%start_index:domain(pe)%y%data%end_index,nz) )
203 !!   ...
204 !!     call mpp_write_meta( unit, x, 'X', 'km', 'X distance', &
205 !!          domain=domain(pe)%x, data=(/(float(i),i=1,nx)/) )
206 !!     call mpp_write_meta( unit, y, 'Y', 'km', 'Y distance', &
207 !!          domain=domain(pe)%y, data=(/(float(i),i=1,ny)/) )
208 !!     call mpp_write_meta( unit, z, 'Z', 'km', 'Z distance', &
209 !!          data=(/(float(i),i=1,nz)/) )
210 !!     call mpp_write_meta( unit, t, 'Time', 'second', 'Time' )
212 !!     call mpp_write_meta( unit, field, (/x,y,z,t/), 'a', '(m/s)', AAA', &
213 !!          missing=-1e36 )
214 !!   ...
215 !!     call mpp_write( unit, x )
216 !!     call mpp_write( unit, y )
217 !!     call mpp_write( unit, z )
218 !!   ...
219 !!   </PRE>
221 !!   In this example, <TT>x</TT> and <TT>y</TT> have been
222 !!   declared as distributed axes, since a domain decomposition has been
223 !!   associated. <TT>z</TT> and <TT>t</TT> are undistributed
224 !!   axes. <TT>t</TT> is known to be a <I>record</I> axis (netCDF
225 !!   terminology) since we do not allocate the <TT>data</TT> element
226 !!   of the <TT>axistype</TT>. <I>Only one record axis may be
227 !!   associated with a file.</I> The call to <LINK
228 !!   SRC="#mpp_write_meta">mpp_write_meta</LINK> initializes
229 !!   the axes, and associates a unique variable ID with each axis. The call
230 !!   to <TT>mpp_write_meta</TT> with argument <TT>field</TT>
231 !!   declared <TT>field</TT> to be a 4D variable that is a function
232 !!   of <TT>(x,y,z,t)</TT>, and a unique variable ID is associated
233 !!   with it. A 3D field will be written at each call to
234 !!   <TT>mpp_write(field)</TT>.
236 !!   The data to any variable, including axes, is written by
237 !!   <TT>mpp_write</TT>.
239 !!   Any additional attributes of variables can be added through
240 !!   subsequent <TT>mpp_write_meta</TT> calls, using the variable ID as a
241 !!   handle. <I>Global</I> attributes, associated with the dataset as a
242 !!   whole, can also be written thus. See the <LINK
243 !!   SRC="#mpp_write_meta">mpp_write_meta</LINK> call syntax below
244 !!   for further details.
246 !!   You cannot interleave calls to <TT>mpp_write</TT> and
247 !!   <TT>mpp_write_meta</TT>: the first call to
248 !!   <TT>mpp_write</TT> implies that metadata specification is
249 !!   complete.
251 !!   A typical calling sequence for reading data might be:
253 !!   <PRE>
254 !!   ...
255 !!     integer :: unit, natt, nvar, ntime
256 !!     type(domain2D), dimension(:), allocatable, target :: domain
257 !!     type(fieldtype), allocatable, dimension(:) :: fields
258 !!     type(atttype), allocatable, dimension(:) :: global_atts
259 !!     real, allocatable, dimension(:) :: times
260 !!   ...
261 !!     call mpp_define_domains( (/1,nx,1,ny/), domain )
263 !!     call mpp_read_meta(unit)
264 !!     call mpp_get_info(unit,natt,nvar,ntime)
265 !!     allocate(global_atts(natt))
266 !!     call mpp_get_atts(unit,global_atts)
267 !!     allocate(fields(nvar))
268 !!     call mpp_get_vars(unit, fields)
269 !!     allocate(times(ntime))
270 !!     call mpp_get_times(unit, times)
272 !!     allocate( a(domain(pe)%x%data%start_index:domain(pe)%x%data%end_index, &
273 !!                 domain(pe)%y%data%start_index:domain(pe)%y%data%end_index,nz) )
274 !!   ...
275 !!     do i=1, nvar
276 !!       if (fields(i)%name == 'a')  call mpp_read(unit,fields(i),domain(pe), a,
277 !!                                                 tindex)
278 !!     enddo
279 !!   ...
280 !!   </PRE>
282 !!   In this example, the data are distributed as in the previous
283 !!   example. The call to <LINK
284 !!   SRC="#mpp_read_meta">mpp_read_meta</LINK> initializes
285 !!   all of the metadata associated with the file, including global
286 !!   attributes, variable attributes and non-record dimension data. The
287 !!   call to <TT>mpp_get_info</TT> returns the number of global
288 !!   attributes (<TT>natt</TT>), variables (<TT>nvar</TT>) and
289 !!   time levels (<TT>ntime</TT>) associated with the file
290 !!   identified by a unique ID (<TT>unit</TT>).
291 !!   <TT>mpp_get_atts</TT> returns all global attributes for
292 !!   the file in the derived type <TT>atttype(natt)</TT>.
293 !!   <TT>mpp_get_vars</TT> returns variable types
294 !!   (<TT>fieldtype(nvar)</TT>).  Since the record dimension data are not allocated for calls to
295 !!   <LINK SRC="#mpp_write">mpp_write</LINK>, a separate call to  <TT>mpp_get_times</TT> is required to access record
296 !!   dimension data.  Subsequent calls to
297 !!   <TT>mpp_read</TT> return the field data arrays corresponding to
298 !!   the fieldtype.  The <TT>domain</TT> type is an optional
299 !!   argument.  If <TT>domain</TT> is omitted, the incoming field
300 !!   array should be dimensioned for the global domain, otherwise, the
301 !!   field data is assigned to the computational domain of a local array.
303 !!   <I>Multi-fileset</I> reads are not supported with <TT>mpp_read</TT>.
305 !! </DESCRIPTION>
306 !! @endhtmlonly
308 !> @addtogroup mpp_io_mod
309 !> @{
311 module mpp_io_mod
312 #ifdef use_deprecated_io
314 #define _MAX_FILE_UNITS 1024
316 #ifdef use_netCDF
317 use netcdf
318 use netcdf_nf_data
319 use netcdf_nf_interfaces
320 use netcdf4_nf_interfaces
321 #endif
323 use mpp_parameter_mod,  only : MPP_WRONLY, MPP_RDONLY, MPP_APPEND, MPP_OVERWR, MPP_ASCII
324 use mpp_parameter_mod,  only : MPP_IEEE32, MPP_NATIVE, MPP_NETCDF, MPP_SEQUENTIAL
325 use mpp_parameter_mod,  only : MPP_DIRECT, MPP_SINGLE, MPP_MULTI, MPP_DELETE, MPP_COLLECT
326 use mpp_parameter_mod,  only : MPP_DEBUG, MPP_VERBOSE, NULLUNIT, NULLTIME, ALL_PES
327 use mpp_parameter_mod,  only : CENTER, EAST, NORTH, CORNER
328 use mpp_parameter_mod,  only : MAX_FILE_SIZE, GLOBAL_ROOT_ONLY, XUPDATE, YUPDATE
329 use mpp_mod,            only : mpp_error, FATAL, WARNING, NOTE, stdin, stdout, stderr, stdlog
330 use mpp_mod,            only : mpp_pe, mpp_root_pe, mpp_npes, lowercase, mpp_transmit, mpp_sync_self
331 use mpp_mod,            only : mpp_init, mpp_sync, mpp_clock_id, mpp_clock_begin, mpp_clock_end
332 use mpp_mod,            only : MPP_CLOCK_SYNC, MPP_CLOCK_DETAILED, CLOCK_ROUTINE
333 use mpp_mod,            only : input_nml_file, mpp_gather, mpp_broadcast
334 use mpp_mod,            only : mpp_send, mpp_recv, mpp_sync_self, EVENT_RECV, COMM_TAG_1
335 use mpp_domains_mod,    only : domain1d, domain2d, NULL_DOMAIN1D, mpp_domains_init
336 use mpp_domains_mod,    only : mpp_get_global_domain, mpp_get_compute_domain
337 use mpp_domains_mod,    only : mpp_get_data_domain, mpp_get_memory_domain, mpp_get_pelist
338 use mpp_domains_mod,    only : mpp_update_domains, mpp_global_field, mpp_domain_is_symmetry
339 use mpp_domains_mod,    only : operator( .NE. ), mpp_get_domain_shift, mpp_get_UG_compute_domains
340 use mpp_domains_mod,    only : mpp_get_io_domain, mpp_domain_is_tile_root_pe, mpp_get_domain_tile_root_pe
341 use mpp_domains_mod,    only : mpp_get_tile_id, mpp_get_tile_npes, mpp_get_io_domain_layout
342 use mpp_domains_mod,    only : mpp_get_domain_name, mpp_get_domain_npes
343 use mpp_parameter_mod,  only : MPP_FILL_DOUBLE,MPP_FILL_INT
344 use mpp_mod,            only : mpp_chksum
346 !----------
347 !ug support
348 use mpp_domains_mod, only: domainUG, &
349                            mpp_get_UG_io_domain, &
350                            mpp_domain_UG_is_tile_root_pe, &
351                            mpp_get_UG_domain_tile_id, &
352                            mpp_get_UG_domain_npes, &
353                            mpp_get_io_domain_UG_layout, &
354                            mpp_get_UG_compute_domain, &
355                            mpp_get_UG_domain_pelist
356 use platform_mod
357 !----------
359 implicit none
360 private
362   !--- public parameters  -----------------------------------------------
363   public :: MPP_WRONLY, MPP_RDONLY, MPP_APPEND, MPP_OVERWR, MPP_ASCII, MPP_IEEE32
364   public :: MPP_NATIVE, MPP_NETCDF, MPP_SEQUENTIAL, MPP_DIRECT, MPP_SINGLE
365   public :: MPP_MULTI, MPP_DELETE, MPP_COLLECT
366   public :: FILE_TYPE_USED
367   public :: MAX_FILE_SIZE
368   !--- public data type ------------------------------------------------
369   public :: axistype, atttype, fieldtype, validtype, filetype
371   !--- public data -----------------------------------------------------
372   public :: default_field, default_axis, default_att
374   !--- public interface from mpp_io_util.h ----------------------
375   public :: mpp_get_id, mpp_get_ncid, mpp_is_valid
376   public :: mpp_get_info, mpp_get_atts, mpp_get_fields
377   public :: mpp_get_times, mpp_get_axes, mpp_get_recdimid, mpp_get_axis_data, mpp_get_axis_by_name
378   public :: mpp_io_set_stack_size, mpp_get_field_index, mpp_get_axis_index
379   public :: mpp_get_field_name, mpp_get_att_value, mpp_get_att_length
380   public :: mpp_get_att_type, mpp_get_att_name, mpp_get_att_real, mpp_get_att_char
381   public :: mpp_get_att_real_scalar, mpp_get_axis_length, mpp_is_dist_ioroot
382   public :: mpp_get_file_name, mpp_file_is_opened, mpp_attribute_exist
383   public :: mpp_io_clock_on, mpp_get_time_axis, mpp_get_default_calendar
384   public :: mpp_get_dimension_length, mpp_get_axis_bounds
386   !--- public interface from mpp_io_misc.h ----------------------
387   public :: mpp_io_init, mpp_io_exit, netcdf_err, mpp_flush, mpp_get_maxunits, do_cf_compliance
389   !--- public interface from mpp_io_write.h ---------------------
390   public :: mpp_write, mpp_write_meta, mpp_copy_meta, mpp_modify_meta, mpp_write_axis_data, mpp_def_dim
392   !--- public interface from mpp_io_read.h ---------------------
393   public :: mpp_read, mpp_read_meta, mpp_get_tavg_info
394   public :: mpp_read_compressed, mpp_write_compressed, mpp_read_distributed_ascii, mpp_write_unlimited_axis
396   !--- public interface from mpp_io_switch.h ---------------------
397   public :: mpp_open, mpp_close
398   public :: fillin_fieldtype
399   !-----------------------------------------------------------------------------
400   !--- mpp_io data types
401   !-----------------------------------------------------------------------------
402 integer FILE_TYPE_USED
403 integer, parameter :: MAX_ATT_LENGTH = 1280
404 !> @}
405 !> @ingroup mpp_io_mod
406 type :: atttype
407      private
408      integer             :: type, len
409      character(len=128)  :: name
410      character(len=MAX_ATT_LENGTH) :: catt
411      real, pointer       :: fatt(:) =>NULL() ! just use type conversion for integers
412   end type atttype
414   !> @ingroup mpp_io_mod
415   type :: axistype
416      private
417      character(len=128) :: name
418      character(len=128) :: name_bounds
419      character(len=128) :: units
420      character(len=256) :: longname
421      character(len=8)   :: cartesian
422      character(len=256) :: compressed
423      character(len=24)  :: calendar
424      integer            :: sense, len          !+/-1, depth or height?
425      type(domain1D)     :: domain              !if pointer is associated, it is a distributed data axis
426      real, pointer      :: data(:) =>NULL()    !axis values (not used if time axis)
427      real, pointer      :: data_bounds(:) =>NULL()    !axis bounds values
428      integer, pointer   :: idata(:) =>NULL()   !compressed axis valuesi
429      integer            :: id, did, type, natt !id is the "variable ID", did is the "dimension ID":
430                                                !netCDF requires 2 IDs for axes
431      integer            :: shift               !normally is 0. when domain is symmetry, its value maybe 1.
432      type(atttype), pointer :: Att(:) =>NULL()
433   end type axistype
435   !> @ingroup mpp_io_mod
436   type :: validtype
437      private
438      logical :: is_range ! if true, then the data represent the valid range
439      real    :: min,max  ! boundaries of the valid range or missing value
440   end type validtype
442   !> @ingroup mpp_io_mod
443   type :: fieldtype
444      private
445      character(len=128)      :: name
446      character(len=128)      :: units
447      character(len=256)      :: longname
448      character(len=256)      :: standard_name   ! CF standard name
449      real                    :: min, max, missing, fill, scale, add
450      integer                 :: pack
451      integer(i8_kind), dimension(3) :: checksum
452      type(axistype), pointer :: axes(:) =>NULL() !axes associated with field size, time_axis_index redundantly
453                                         !hold info already contained in axes. it's clunky and inelegant,
454                                         !but required so that axes can be shared among multiple files
455      integer, pointer        :: size(:) =>NULL()
456      integer                 :: time_axis_index
457      integer                 :: id, type, natt, ndim
458      type(atttype), pointer  :: Att(:) =>NULL()
459      integer                 :: position ! indicate the location of the data ( CENTER, NORTH, EAST, CORNER )
460   end type fieldtype
462   !> @ingroup mpp_io_mod
463   type :: filetype
464      private
465      character(len=256) :: name
466      integer            :: action, format, access, threading, fileset, record, ncid
467      logical            :: opened, initialized, nohdrs
468      integer            :: time_level
469      real(r8_kind)  :: time
470      logical            :: valid
471      logical            :: write_on_this_pe   ! indicate if will write out from this pe
472      logical            :: read_on_this_pe    ! indicate if will read from this pe
473      logical            :: io_domain_exist    ! indicate if io_domain exist or not.
474      integer            :: id       !variable ID of time axis associated with file (only one time axis per file)
475      integer            :: recdimid !dim ID of time axis associated with file (only one time axis per file)
476      real(r8_kind), pointer :: time_values(:) =>NULL() ! time axis values are stored here instead of axis%data
477                                                   ! since mpp_write assumes these values are not time values.
478                                                   ! Not used in mpp_write
479      ! additional elements of filetype for mpp_read (ignored for mpp_write)
480      integer :: ndim, nvar, natt  ! number of dimensions, non-dimension variables and global attributes
481                                   ! redundant axis types stored here and in associated fieldtype
482                                   ! some axes are not used by any fields, i.e. "edges"
483      type(axistype), pointer  :: axis(:) =>NULL()
484      type(fieldtype), pointer :: var(:) =>NULL()
485      type(atttype), pointer   :: att(:) =>NULL()
486      type(domain2d), pointer  :: domain =>NULL()
487 !----------
488 !ug support
489      type(domainUG),pointer :: domain_ug => null() !Is this actually pointed to?
490 !----------
491   end type filetype
493 !> @addtogroup mpp_io_mod
494 !> @{
495 !***********************************************************************
497 !     public interface from mpp_io_util.h
499 !***********************************************************************
500   interface mpp_get_id
501      module procedure mpp_get_axis_id
502      module procedure mpp_get_field_id
503   end interface
505 ! <INTERFACE NAME="mpp_get_atts">
506 !   <OVERVIEW>
507 !     Get file global metdata.
508 !   </OVERVIEW>
509 !   <DESCRIPTION>
510 !     Get file global metdata.
511 !   </DESCRIPTION>
512 !   <TEMPLATE>
513 !     call mpp_get_atts( unit, global_atts)
514 !   </TEMPLATE>
515 !  <IN NAME="unit"></IN>
516 !  <IN NAME="global_atts"></IN>
517 ! </INTERFACE>
518   !> @brief Get file global metadata.
519   !!
520   !> <br>Example usage:
521   !!                    call mpp_get_atts( unit, global_atts)
522   interface mpp_get_atts
523      module procedure mpp_get_global_atts
524      module procedure mpp_get_field_atts
525      module procedure mpp_get_axis_atts
526   end interface
528   interface mpp_get_att_value
529      module procedure mpp_get_field_att_text
530   end interface
533 !***********************************************************************
535 !      public interface from mpp_io_read.h
537 !***********************************************************************
538 ! <INTERFACE NAME="mpp_read">
539 !   <OVERVIEW>
540 !     Read from an open file.
541 !   </OVERVIEW>
542 !   <DESCRIPTION>
543 !      <TT>mpp_read</TT> is used to read data to the file on an I/O unit
544 !      using the file parameters supplied by <LINK
545 !      SRC="#mpp_open"><TT>mpp_open</TT></LINK>. There are two
546 !      forms of <TT>mpp_read</TT>, one to read
547 !      distributed field data, and one to read non-distributed field
548 !      data. <I>Distributed</I> data refer to arrays whose two
549 !      fastest-varying indices are domain-decomposed. Distributed data must
550 !      be 2D or 3D (in space). Non-distributed data can be 0-3D.
552 !      The <TT>data</TT> argument for distributed data is expected by
553 !      <TT>mpp_read</TT> to contain data specified on the <I>data</I> domain,
554 !      and will read the data belonging to the <I>compute</I> domain,
555 !      fetching data as required by the parallel I/O <LINK
556 !      SRC="#modes">mode</LINK> specified in the <TT>mpp_open</TT> call. This
557 !      is consistent with our definition of <LINK
558 !      SRC="http:mpp_domains.html#domains">domains</LINK>, where all arrays are
559 !      expected to be dimensioned on the data domain, and all operations
560 !      performed on the compute domain.
561 !   </DESCRIPTION>
562 !   <TEMPLATE>
563 !     call mpp_read( unit, field, data, time_index )
564 !   </TEMPLATE>
565 !   <TEMPLATE>
566 !     call mpp_read( unit, field, domain, data, time_index )
567 !   </TEMPLATE>
568 !  <IN NAME="unit"></IN>
569 !  <IN NAME="field"></IN>
570 !  <INOUT NAME="data"></INOUT>
571 !  <IN NAME="domain"></IN>
572 !  <IN NAME="time_index">
573 !     time_index is an optional argument. It is to be omitted if the
574 !     field was defined not to be a function of time. Results are
575 !     unpredictable if the argument is supplied for a time- independent
576 !     field, or omitted for a time-dependent field.
577 !  </IN>
578 !  <NOTE>
579 !     The type of read performed by <TT>mpp_read</TT> depends on
580 !     the file characteristics on the I/O unit specified at the <LINK
581 !     SRC="#mpp_open"><TT>mpp_open</TT></LINK> call. Specifically, the
582 !     format of the input data (e.g netCDF or IEEE) and the
583 !     <TT>threading</TT> flags, etc., can be changed there, and
584 !     require no changes to the <TT>mpp_read</TT>
585 !     calls. (<TT>fileset</TT> = MPP_MULTI is not supported by
586 !     <TT>mpp_read</TT>; IEEE is currently not supported).
588 !     Packed variables are unpacked using the <TT>scale</TT> and
589 !     <TT>add</TT> attributes.
591 !     <TT>mpp_read_meta</TT> must be called prior to calling <TT>mpp_read.</TT>
592 !  </NOTE>
593 ! </INTERFACE>
594   interface mpp_read
595      module procedure mpp_read_2ddecomp_r2d_r4
596      module procedure mpp_read_2ddecomp_r3d_r4
597      module procedure mpp_read_2ddecomp_r4d_r4
598      module procedure mpp_read_2ddecomp_r2d_r8
599      module procedure mpp_read_2ddecomp_r3d_r8
600      module procedure mpp_read_2ddecomp_r4d_r8
601      module procedure mpp_read_region_r2D_r4
602      module procedure mpp_read_region_r3D_r4
603      module procedure mpp_read_region_r2D_r8
604      module procedure mpp_read_region_r3D_r8
605      module procedure mpp_read_r0D_r4
606      module procedure mpp_read_r1D_r4
607      module procedure mpp_read_r2D_r4
608      module procedure mpp_read_r3D_r4
609      module procedure mpp_read_r4D_r4
610      module procedure mpp_read_r0D_r8
611      module procedure mpp_read_r1D_r8
612      module procedure mpp_read_r2D_r8
613      module procedure mpp_read_r3D_r8
614      module procedure mpp_read_r4D_r8
615      module procedure mpp_read_text
616   end interface
618 !***********************************************************************
620 !      public interfaces from mpp_io_read_distributed_ascii.inc
622 !***********************************************************************
623 ! <INTERFACE NAME="mpp_read_distributed_ascii">
624 !   <OVERVIEW>
625 !     Read from an opened, ascii file, translating data to the desired format
626 !   </OVERVIEW>
627 !   <DESCRIPTION>
628 !     These routines are part of the mpp_read family. It is intended to
629 !     provide a general purpose, distributed, list directed read
630 !  </DESCRIPTION>
631 !   <TEMPLATE>
632 !     call mpp_read_distributed_ascii(unit,fmt,ssize,data,iostat)
633 !   </TEMPLATE>
634 !  <IN NAME="unit"></IN>
635 !  <IN NAME="fmt"></IN>
636 !  <IN NAME="ssize"></IN>
637 !  <INOUT NAME="data"></IN>
638 !  <OUT NAME="iostat">
639 !  </IN>
640 !  <NOTE>
641 !     <TT>mpp_read_distributed_ascii</TT>
642 !     The stripe size must be greater than or equal to 1. The stripe
643 !     size does not have to be a common denominator of the number of
644 !     MPI ranks.
645 !  </NOTE>
646 ! </INTERFACE>
647   interface mpp_read_distributed_ascii
648      module procedure mpp_read_distributed_ascii_r1d
649      module procedure mpp_read_distributed_ascii_i1d
650      module procedure mpp_read_distributed_ascii_a1d
651   end interface
654 !***********************************************************************
656 !      public interfaces from mpp_io_read_compressed.h
658 !***********************************************************************
659 ! <INTERFACE NAME="mpp_read_compressed">
660 !   <OVERVIEW>
661 !     Read from an opened, sparse data, compressed file (e.g. land_model)
662 !   </OVERVIEW>
663 !   <DESCRIPTION>
664 !     These routines are similar to mpp_read except that they are designed
665 !     to handle sparse, compressed vectors of data such as from the
666 !     land model. Currently, the sparse vector may vary in z. Hence
667 !     the need for the rank 2 treatment.
668 !  </DESCRIPTION>
669 !   <TEMPLATE>
670 !     call mpp_read_compressed( unit, field, domain, data, time_index )
671 !   </TEMPLATE>
672 !  <IN NAME="unit"></IN>
673 !  <IN NAME="field"></IN>
674 !  <IN NAME="domain"></IN>
675 !  <INOUT NAME="data"></INOUT>
676 !  <IN NAME="time_index">
677 !     time_index is an optional argument. It is to be omitted if the
678 !     field was defined not to be a function of time. Results are
679 !     unpredictable if the argument is supplied for a time- independent
680 !     field, or omitted for a time-dependent field.
681 !  </IN>
682 !  <NOTE>
683 !     <TT>mpp_read_meta</TT> must be called prior to calling
684 !     <TT>mpp_read_compressed.</TT>
685 !     Since in general, the vector is distributed across the io-domain
686 !     The read expects the io_domain to be defined.
687 !  </NOTE>
688 ! </INTERFACE>
689   interface mpp_read_compressed
690      module procedure mpp_read_compressed_r1d_r4
691      module procedure mpp_read_compressed_r2d_r4
692      module procedure mpp_read_compressed_r3d_r4
693      module procedure mpp_read_compressed_r1d_r8
694      module procedure mpp_read_compressed_r2d_r8
695      module procedure mpp_read_compressed_r3d_r8
696   end interface mpp_read_compressed
699 !***********************************************************************
701 !    public interface from mpp_io_write.h
703 !***********************************************************************
705 ! <INTERFACE NAME="mpp_write_meta">
706 !   <OVERVIEW>
707 !     Write metadata.
708 !   </OVERVIEW>
709 !   <DESCRIPTION>
710 !     This routine is used to write the <LINK SRC="#metadata">metadata</LINK>
711 !     describing the contents of a file being written. Each file can contain
712 !     any number of fields, which are functions of 0-3 space axes and 0-1
713 !     time axes. (Only one time axis can be defined per file). The basic
714 !     metadata defined <LINK SRC="#metadata">above</LINK> for <TT>axistype</TT>
715 !     and <TT>fieldtype</TT> are written in the first two forms of the call
716 !     shown below. These calls will associate a unique variable ID with each
717 !     variable (axis or field). These can be used to attach any other real,
718 !     integer or character attribute to a variable. The last form is used to
719 !     define a <I>global</I> real, integer or character attribute that
720 !     applies to the dataset as a whole.
721 !   </DESCRIPTION>
722 !  <TEMPLATE>
723 !    call mpp_write_meta( unit, axis, name, units, longname,
724 !      cartesian, sense, domain, data )
725 !  </TEMPLATE>
726 !  <NOTE>
727 !    The first form defines a time or space axis. Metadata corresponding to the type
728 !    above are written to the file on &lt;unit&gt;. A unique ID for subsequen
729 !    references to this axis is returned in axis%id. If the &lt;domain&gt;
730 !    element is present, this is recognized as a distributed data axis
731 !    and domain decomposition information is also written if required (the
732 !    domain decomposition info is required for multi-fileset multi-threaded
733 !    I/O). If the &lt;data&gt; element is allocated, it is considered to be a
734 !    space axis, otherwise it is a time axis with an unlimited dimension. Only
735 !    one time axis is allowed per file.
736 !  </NOTE>
737 !  <TEMPLATE>
738 !    call mpp_write_meta( unit, field, axes, name, units, longname,
739 !                              min, max, missing, fill, scale, add, pack )
740 !  </TEMPLATE>
741 !  <NOTE>
742 !    The second form defines a field. Metadata corresponding to the type
743 !    above are written to the file on &lt;unit&gt;. A unique ID for subsequen
744 !    references to this field is returned in field%id. At least one axis
745 !    must be associated, 0D variables are not considered. mpp_write_meta
746 !    must previously have been called on all axes associated with this
747 !    field.
748 !  </NOTE>
749 !  <TEMPLATE>
750 !    call mpp_write_meta( unit, id, name, rval=rval, pack=pack )
751 !  </TEMPLATE>
752 !  <TEMPLATE>
753 !    call mpp_write_meta( unit, id, name, ival=ival )
754 !  </TEMPLATE>
755 !  <TEMPLATE>
756 !    call mpp_write_meta( unit, id, name, cval=cval )
757 !  </TEMPLATE>
758 !  <NOTE>
759 !    The third form (3 - 5) defines metadata associated with a previously defined
760 !    axis or field, identified to mpp_write_meta by its unique ID &lt;id&gt;.
761 !    The attribute is named &lt;name&gt; and can take on a real, integer
762 !    or character value. &lt;rval&gt; and &lt;ival&gt; can be scalar or 1D arrays.
763 !    This need not be called for attributes already contained in
764 !    the type.
765 !  </NOTE>
766 !  <TEMPLATE>
767 !    call mpp_write_meta( unit, name, rval=rval, pack=pack )
768 !  </TEMPLATE>
769 !  <TEMPLATE>
770 !    call mpp_write_meta( unit, name, ival=ival )
771 !  </TEMPLATE>
772 !  <TEMPLATE>
773 !    call mpp_write_meta( unit, name, cval=cval )
774 !  </TEMPLATE>
775 !  <NOTE>
776 !    The last form (6 - 8) defines global metadata associated with the file as a
777 !    whole. The attribute is named &lt;name&gt; and can take on a real, integer
778 !    or character value. &lt;rval&gt; and &lt;ival&gt; can be scalar or 1D arrays.
779 !  </NOTE>
780 !  <IN NAME="unit"></IN>
781 !  <OUT NAME="axis"></OUT>
782 !  <IN NAME="name"></IN>
783 !  <IN NAME="units"></IN>
784 !  <IN NAME="longname"></IN>
785 !  <IN NAME="cartesian"></IN>
786 !  <IN NAME="sense"></IN>
787 !  <IN NAME="domain"></IN>
788 !  <IN NAME="data"></IN>
789 !  <OUT NAME="field"></OUT>
790 !  <IN NAME="min, max"></IN>
791 !  <IN NAME="missing"></IN>
792 !  <IN NAME="fill"></IN>
793 !  <IN NAME="scale"></IN>
794 !  <IN NAME="add"></IN>
795 !  <IN NAME="pack"></IN>
796 !  <IN NAME="id"></IN>
797 !  <IN NAME="cval"></IN>
798 !  <IN NAME="ival"></IN>
799 !  <IN NAME="rval"></IN>
801 !> Each file can contain any number of fields,
802 !! which can be functions of 0-3 spatial axes and 0-1 time axes. Axis
803 !! descriptors are stored in the <axistype> structure and field
804 !! descriptors in the <fieldtype> structure.
806 !! The metadata contained in the type is always written for each axis and
807 !! field. Any other metadata one wishes to attach to an axis or field
808 !! can subsequently be passed to mpp_write_meta using the ID, as shown below.
810 !! mpp_write_meta can take several forms:
812 !!  mpp_write_meta( unit, name, rval=rval, pack=pack )
813 !!  mpp_write_meta( unit, name, ival=ival )
814 !!  mpp_write_meta( unit, name, cval=cval )
815 !!      integer, intent(in) :: unit
816 !!      character(len=*), intent(in) :: name
817 !!      real, intent(in), optional :: rval(:)
818 !!      integer, intent(in), optional :: ival(:)
819 !!      character(len=*), intent(in), optional :: cval
821 !! This form defines global metadata associated with the file as a
822 !! whole. The attribute is named <name> and can take on a real, integer
823 !! or character value. <rval> and <ival> can be scalar or 1D arrays.
825 !!  mpp_write_meta( unit, id, name, rval=rval, pack=pack )
826 !!  mpp_write_meta( unit, id, name, ival=ival )
827 !!  mpp_write_meta( unit, id, name, cval=cval )
828 !!      integer, intent(in) :: unit, id
829 !!      character(len=*), intent(in) :: name
830 !!      real, intent(in), optional :: rval(:)
831 !!      integer, intent(in), optional :: ival(:)
832 !!      character(len=*), intent(in), optional :: cval
834 !! This form defines metadata associated with a previously defined
835 !! axis or field, identified to mpp_write_meta by its unique ID <id>.
836 !! The attribute is named <name> and can take on a real, integer
837 !! or character value. <rval> and <ival> can be scalar or 1D arrays.
838 !! This need not be called for attributes already contained in
839 !! the type.
841 !! PACK can take values 1,2,4,8. This only has meaning when writing
842 !! floating point numbers. The value of PACK defines the number of words
843 !! written into 8 bytes. For pack=4 and pack=8, an integer value is
844 !! written: rval is assumed to have been scaled to the appropriate dynamic
845 !! range.
846 !! PACK currently only works for netCDF files, and is ignored otherwise.
848 !!  subroutine mpp_write_meta_axis( unit, axis, name, units, longname, &
849 !!        cartesian, sense, domain, data )
850 !!     integer, intent(in) :: unit
851 !!     type(axistype), intent(inout) :: axis
852 !!     character(len=*), intent(in) :: name, units, longname
853 !!     character(len=*), intent(in), optional :: cartesian
854 !!     integer, intent(in), optional :: sense
855 !!     type(domain1D), intent(in), optional :: domain
856 !!     real, intent(in), optional :: data(:)
858 !! This form defines a time or space axis. Metadata corresponding to the
859 !! type above are written to the file on <unit>. A unique ID for subsequent
860 !! references to this axis is returned in axis%id. If the <domain>
861 !! element is present, this is recognized as a distributed data axis
862 !! and domain decomposition information is also written if required (the
863 !! domain decomposition info is required for multi-fileset multi-threaded
864 !! I/O). If the <datLINK> element is allocated, it is considered to be a
865 !! space axis, otherwise it is a time axis with an unlimited dimension.
866 !! Only one time axis is allowed per file.
867 !! @code{.F90}
868 !!  subroutine mpp_write_meta_field( unit, field, axes, name, units, longname
869 !!                                   standard_name, min, max, missing, fill, scale, add, pack)
870 !!     integer, intent(in) :: unit
871 !!     type(fieldtype), intent(out) :: field
872 !!     type(axistype), intent(in) :: axes(:)
873 !!     character(len=*), intent(in) :: name, units, longname, standard_name
874 !!     real, intent(in), optional :: min, max, missing, fill, scale, add
875 !!     integer, intent(in), optional :: pack
876 !! @endcode
877 !! This form defines a field. Metadata corresponding to the type
878 !! above are written to the file on <unit>. A unique ID for subsequent
879 !! references to this field is returned in field%id. At least one axis
880 !! must be associated, 0D variables are not considered. mpp_write_meta
881 !! must previously have been called on all axes associated with this
882 !! field.
884 !! The mpp_write_meta package also includes subroutines write_attribute and
885 !! write_attribute_netcdf, that are private to this module.
886   interface mpp_write_meta
887      module procedure mpp_write_meta_var
888      module procedure mpp_write_meta_scalar_r
889      module procedure mpp_write_meta_scalar_i
890      module procedure mpp_write_meta_axis_r1d
891      module procedure mpp_write_meta_axis_i1d
892      module procedure mpp_write_meta_axis_unlimited
893      module procedure mpp_write_meta_field
894      module procedure mpp_write_meta_global
895      module procedure mpp_write_meta_global_scalar_r
896      module procedure mpp_write_meta_global_scalar_i
897   end interface
899   interface mpp_copy_meta
900      module procedure mpp_copy_meta_axis
901      module procedure mpp_copy_meta_field
902      module procedure mpp_copy_meta_global
903   end interface
905   interface mpp_modify_meta
906 !     module procedure mpp_modify_att_meta
907      module procedure mpp_modify_field_meta
908      module procedure mpp_modify_axis_meta
909   end interface
911 ! <INTERFACE NAME="mpp_write">
912 !   <OVERVIEW>
913 !     Write to an open file.
914 !   </OVERVIEW>
915 !   <DESCRIPTION>
916 !    <TT>mpp_write</TT> is used to write data to the file on an I/O unit
917 !    using the file parameters supplied by <LINK
918 !    SRC="#mpp_open"><TT>mpp_open</TT></LINK>. Axis and field definitions must
919 !    have previously been written to the file using <LINK
920 !    SRC="#mpp_write_meta"><TT>mpp_write_meta</TT></LINK>.  There are three
921 !    forms of <TT>mpp_write</TT>, one to write axis data, one to write
922 !    distributed field data, and one to write non-distributed field
923 !    data. <I>Distributed</I> data refer to arrays whose two
924 !    fastest-varying indices are domain-decomposed. Distributed data must
925 !    be 2D or 3D (in space). Non-distributed data can be 0-3D.
927 !    The <TT>data</TT> argument for distributed data is expected by
928 !    <TT>mpp_write</TT> to contain data specified on the <I>data</I> domain,
929 !    and will write the data belonging to the <I>compute</I> domain,
930 !    fetching or sending data as required by the parallel I/O <LINK
931 !    SRC="#modes">mode</LINK> specified in the <TT>mpp_open</TT> call. This
932 !    is consistent with our definition of <LINK
933 !    SRC="http:mpp_domains.html#domains">domains</LINK>, where all arrays are
934 !    expected to be dimensioned on the data domain, and all operations
935 !    performed on the compute domain.
937 !     The type of the <TT>data</TT> argument must be a <I>default
938 !     real</I>, which can be 4 or 8 byte.
939 !   </DESCRIPTION>
940 !  <TEMPLATE>
941 !    mpp_write( unit, axis )
942 !  </TEMPLATE>
943 !  <TEMPLATE>
944 !    mpp_write( unit, field, data, tstamp )
945 !  </TEMPLATE>
946 !  <TEMPLATE>
947 !    mpp_write( unit, field, domain, data, tstamp )
948 !  </TEMPLATE>
949 !  <IN NAME="tstamp">
950 !    <TT>tstamp</TT> is an optional argument. It is to
951 !    be omitted if the field was defined not to be a function of time.
952 !    Results are unpredictable if the argument is supplied for a time-
953 !    independent field, or omitted for a time-dependent field. Repeated
954 !    writes of a time-independent field are also not recommended. One
955 !    time level of one field is written per call. tstamp must be an 8-byte
956 !    real, even if the default real type is 4-byte.
957 !  </IN>
958 !  <NOTE>
959 !    The type of write performed by <TT>mpp_write</TT> depends on the file
960 !    characteristics on the I/O unit specified at the <LINK
961 !    SRC="#mpp_open"><TT>mpp_open</TT></LINK> call. Specifically, the format of
962 !    the output data (e.g netCDF or IEEE), the <TT>threading</TT> and
963 !    <TT>fileset</TT> flags, etc., can be changed there, and require no
964 !    changes to the <TT>mpp_write</TT> calls.
966 !    Packing is currently not implemented for non-netCDF files, and the
967 !    <TT>pack</TT> attribute is ignored. On netCDF files,
968 !    <TT>NF_DOUBLE</TT>s (8-byte IEEE floating point numbers) are
969 !    written for <TT>pack</TT>=1 and <TT>NF_FLOAT</TT>s for
970 !    <TT>pack</TT>=2. (<TT>pack</TT>=2 gives the customary
971 !    and default behaviour). We write <TT>NF_SHORT</TT>s (2-byte
972 !    integers) for <TT>pack=4</TT>, or <TT>NF_BYTE</TT>s
973 !    (1-byte integers) for <TT>pack=8</TT>. Integer scaling is done
974 !    using the <TT>scale</TT> and <TT>add</TT> attributes at
975 !    <TT>pack</TT>=4 or 8, satisfying the relation
977 !    <PRE>
978 !    data = packed_data*scale + add
979 !    </PRE>
981 !    <TT>NOTE: mpp_write</TT> does not check to see if the scaled
982 !    data in fact fits into the dynamic range implied by the specified
983 !    packing. It is incumbent on the user to supply correct scaling
984 !    attributes.
986 !    You cannot interleave calls to <TT>mpp_write</TT> and
987 !    <TT>mpp_write_meta</TT>: the first call to
988 !    <TT>mpp_write</TT> implies that metadata specification is
989 !    complete.
990 ! </NOTE>
991 ! </INTERFACE>
994   interface write_record
995      module procedure write_record_r8
996      module procedure write_record_r4
997   end interface
999   interface mpp_write
1000      module procedure mpp_write_2ddecomp_r2d_r8
1001      module procedure mpp_write_2ddecomp_r3d_r8
1002      module procedure mpp_write_2ddecomp_r4d_r8
1003      module procedure mpp_write_2ddecomp_r2d_r4
1004      module procedure mpp_write_2ddecomp_r3d_r4
1005      module procedure mpp_write_2ddecomp_r4d_r4
1006      module procedure mpp_write_r0D_r8
1007      module procedure mpp_write_r1D_r8
1008      module procedure mpp_write_r2D_r8
1009      module procedure mpp_write_r3D_r8
1010      module procedure mpp_write_r4D_r8
1011      module procedure mpp_write_r0D_r4
1012      module procedure mpp_write_r1D_r4
1013      module procedure mpp_write_r2D_r4
1014      module procedure mpp_write_r3D_r4
1015      module procedure mpp_write_r4D_r4
1016      module procedure mpp_write_axis
1017   end interface
1020 !***********************************************************************
1021 ! <INTERFACE NAME="mpp_write_compressed">
1022 !   <OVERVIEW>
1023 !     Write to an opened, sparse data, compressed file (e.g. land_model)
1024 !   </OVERVIEW>
1025 !   <DESCRIPTION>
1026 !     These routines are similar to mpp_write except that they are
1027 !     designed to handle sparse, compressed vectors of data such
1028 !     as from the land model. Currently, the sparse vector may vary in z.
1029 !     Hence the need for the rank 2 treatment.
1030 !  </DESCRIPTION>
1031 !   <TEMPLATE>
1032 !     call mpp_write(unit, field, domain, data, nelems_io, tstamp, default_data )
1033 !   </TEMPLATE>
1034 !  <IN NAME="unit"></IN>
1035 !  <IN NAME="field"></IN>
1036 !  <IN NAME="domain"></IN>
1037 !  <INOUT NAME="data"></INOUT>
1038 !  <IN NAME="nelems_io">
1039 !    <TT>nelems</TT> is a vector containing the number of elements expected
1040 !    from each member of the io_domain. It MUST have the same order as
1041 !    the io_domain pelist.
1042 !  </IN>
1043 !  <IN NAME="tstamp">
1044 !    <TT>tstamp</TT> is an optional argument. It is to
1045 !    be omitted if the field was defined not to be a function of time.
1046 !    Results are unpredictable if the argument is supplied for a time-
1047 !    independent field, or omitted for a time-dependent field. Repeated
1048 !    writes of a time-independent field are also not recommended. One
1049 !    time level of one field is written per call. tstamp must be an 8-byte
1050 !    real, even if the default real type is 4-byte.
1051 !  </IN>
1052 !  <IN NAME="default_data"></IN>
1053 !  <NOTE>
1054 !     <TT>mpp_write_meta</TT> must be called prior to calling
1055 !     <TT>mpp_write_compressed.</TT>
1056 !     Since in general, the vector is distributed across the io-domain
1057 !     The write expects the io_domain to be defined.
1058 !  </NOTE>
1059 ! </INTERFACE>
1060   interface mpp_write_compressed
1061      module procedure mpp_write_compressed_r1d_r8
1062      module procedure mpp_write_compressed_r2d_r8
1063      module procedure mpp_write_compressed_r3d_r8
1064      module procedure mpp_write_compressed_r1d_r4
1065      module procedure mpp_write_compressed_r2d_r4
1066      module procedure mpp_write_compressed_r3d_r4
1067   end interface mpp_write_compressed
1069 !***********************************************************************
1070 ! <INTERFACE NAME="mpp_write_unlimited_axis">
1071 !   <OVERVIEW>
1072 !     Write to an opened file along the unlimited axis (e.g. icebergs)
1073 !   </OVERVIEW>
1074 !   <DESCRIPTION>
1075 !     These routines are similar to mpp_write except that they are
1076 !     designed to handle data written along the unlimited axis that
1077 !     is not time (e.g. icebergs).
1078 !  </DESCRIPTION>
1079 !   <TEMPLATE>
1080 !     call mpp_write(unit, field, domain, data, nelems_io)
1081 !   </TEMPLATE>
1082 !  <IN NAME="unit"></IN>
1083 !  <IN NAME="field"></IN>
1084 !  <IN NAME="domain"></IN>
1085 !  <INOUT NAME="data"></INOUT>
1086 !  <IN NAME="nelems">
1087 !    <TT>nelems</TT> is a vector containing the number of elements expected
1088 !    from each member of the io_domain. It MUST have the same order as
1089 !    the io_domain pelist.
1090 !  </IN>
1091 !  <NOTE>
1092 !     <TT>mpp_write_meta</TT> must be called prior to calling
1093 !     <TT>mpp_write_unlimited_axis.</TT>
1094 !     Since in general, the vector is distributed across the io-domain
1095 !     The write expects the io_domain to be defined.
1096 !  </NOTE>
1097 ! </INTERFACE>
1098   interface mpp_write_unlimited_axis
1099      module procedure mpp_write_unlimited_axis_r1d
1100   end interface mpp_write_unlimited_axis
1103 !***********************************************************************
1104 ! <INTERFACE NAME="mpp_def_dim">
1105 !   <OVERVIEW>
1106 !     Define an dimension variable
1107 !   </OVERVIEW>
1108 !   <DESCRIPTION>
1109 !     Similar to the mpp_write_meta routines, but simply defines the
1110 !     a dimension variable with the optional attributes
1111 !  </DESCRIPTION>
1112 !   <TEMPLATE>
1113 !     call mpp_def_dim( unit, name, dsize, longname, data )
1114 !   </TEMPLATE>
1115 !  <IN NAME="unit"></IN>
1116 !  <IN NAME="name"></IN>
1117 !  <IN NAME="dsize"></IN>
1118 !  <IN NAME="data"></INOUT>
1119 ! </INTERFACE>
1120   interface mpp_def_dim
1121      module procedure mpp_def_dim_nodata
1122      module procedure mpp_def_dim_int
1123      module procedure mpp_def_dim_real
1124   end interface mpp_def_dim
1126 !***********************************************************************
1128 !            module variables
1130 !***********************************************************************
1131   logical            :: module_is_initialized = .FALSE.
1132   logical            :: verbose =.FALSE.
1133   logical            :: debug = .FALSE.
1134   integer            :: maxunits, unit_begin, unit_end
1135   integer            :: mpp_io_stack_size=0, mpp_io_stack_hwm=0
1136   integer            :: varnum=0
1137   integer            :: pe, npes
1138   character(len=256) :: text
1139   integer            :: error
1140   integer            :: records_per_pe
1141   integer            :: mpp_read_clock=0, mpp_write_clock=0
1142   integer            :: mpp_open_clock=0, mpp_close_clock=0
1145 !initial value of buffer between meta_data and data in .nc file
1146   integer            :: header_buffer_val = 16384  ! value used in NF__ENDDEF
1147   logical            :: global_field_on_root_pe = .true.
1148   logical            :: io_clocks_on = .false.
1149   integer            :: shuffle = 0
1150   integer            :: deflate = 0
1151   integer            :: deflate_level = -1
1152   logical            :: cf_compliance = .false.
1154   namelist /mpp_io_nml/header_buffer_val, global_field_on_root_pe, io_clocks_on, &
1155                        shuffle, deflate_level, cf_compliance
1157   real(r8_kind), allocatable :: mpp_io_stack(:)
1158   type(axistype),save            :: default_axis      !provided to users with default components
1159   type(fieldtype),save           :: default_field     !provided to users with default components
1160   type(atttype),save             :: default_att       !provided to users with default components
1161   type(filetype), allocatable    :: mpp_file(:)
1163   integer :: pack_size ! = 1 when compiling with -r8 and = 2 when compiling with -r4.
1165 ! Include variable "version" to be written to log file.
1166 #include<file_version.h>
1168 !----------
1169 !ug support
1170 public :: mpp_io_unstructured_write
1171 public :: mpp_io_unstructured_read
1173 interface mpp_io_unstructured_write
1174     module procedure mpp_io_unstructured_write_r8_1D
1175     module procedure mpp_io_unstructured_write_r8_2D
1176     module procedure mpp_io_unstructured_write_r8_3D
1177     module procedure mpp_io_unstructured_write_r8_4D
1178     module procedure mpp_io_unstructured_write_r4_1D
1179     module procedure mpp_io_unstructured_write_r4_2D
1180     module procedure mpp_io_unstructured_write_r4_3D
1181     module procedure mpp_io_unstructured_write_r4_4D
1182 end interface mpp_io_unstructured_write
1184 interface mpp_io_unstructured_read
1185     module procedure mpp_io_unstructured_read_r8_1D
1186     module procedure mpp_io_unstructured_read_r8_2D
1187     module procedure mpp_io_unstructured_read_r8_3D
1188     module procedure mpp_io_unstructured_read_r4_1D
1189     module procedure mpp_io_unstructured_read_r4_2D
1190     module procedure mpp_io_unstructured_read_r4_3D
1191 end interface mpp_io_unstructured_read
1192 !----------
1194 contains
1196 #include <mpp_io_util.inc>
1197 #include <mpp_io_misc.inc>
1198 #include <mpp_io_connect.inc>
1199 #include <mpp_io_read.inc>
1200 #include <mpp_io_write.inc>
1202 !----------
1203 !ug support
1204 #include <mpp_io_unstructured_write.inc>
1205 #include <mpp_io_unstructured_read.inc>
1206 !----------
1207 #endif
1208 end module mpp_io_mod
1209 !> @}
1210 ! close documentation grouping