/[MITgcm]/MITgcm/pkg/mdsio/mdsio_write_meta.F
ViewVC logotype

Annotation of /MITgcm/pkg/mdsio/mdsio_write_meta.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.2 - (hide annotations) (download)
Mon Mar 19 02:30:49 2007 UTC (17 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint58x_post, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint59, checkpoint58y_post
Changes since 1.1: +11 -4 lines
to read/write compact global files: add parameter for mapping tile to global file.

1 jmc 1.2 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_write_meta.F,v 1.1 2006/12/29 05:11:52 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "MDSIO_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: MDS_WRITE_META
8     C !INTERFACE:
9     SUBROUTINE MDS_WRITE_META(
10     I mFileName,
11     I dFileName,
12     I simulName,
13     I titleLine,
14     I filePrec,
15 jmc 1.2 I nDims, dimList, map2gl,
16 jmc 1.1 I nFlds, fldList,
17     I nTimRec, timList,
18     I nrecords, myIter, myThid )
19    
20     C !DESCRIPTION: \bv
21     C *==========================================================*
22     C | S/R MDS_WRITE_META
23     C | o Write 1 meta file to disk
24     C *==========================================================*
25     C \ev
26    
27     C !USES:
28     IMPLICIT NONE
29    
30     C == Global variables / common blocks
31     #include "SIZE.h"
32     #include "EEPARAMS.h"
33     #include "PARAMS.h"
34    
35     C !INPUT PARAMETERS:
36     C mFileName (string ) :: complete name of meta-file
37     C dFileName (string ) :: complete name of data-file
38     C simulName (string) :: name of this simulation
39 jmc 1.2 C titleLine (string) :: title or any descriptive comments
40 jmc 1.1 C filePrec (integer) :: number of bits per word in data-file (32 or 64)
41     C nDims (integer) :: number of dimensions
42     C dimList (integer) :: array of dimensions, etc.
43 jmc 1.2 C map2gl (integer) :: used for mapping tiled file to global file
44 jmc 1.1 C nFlds (integer) :: number of fields in "fldList"
45     C fldList (string) :: array of field names to write
46     C nTimRec (integer) :: number of time-specification in "timList"
47     C timList (real) :: array of time-specifications to write
48     C nrecords (integer) :: record number
49     C myIter (integer) :: time-step number
50     C myThid (integer) :: my Thread Id number
51     C
52     C !OUTPUT PARAMETERS:
53     C
54     CHARACTER*(*) mFileName
55     CHARACTER*(*) dFileName
56     CHARACTER*(*) simulName
57     CHARACTER*(*) titleLine
58     INTEGER filePrec
59     INTEGER nDims
60     INTEGER dimList(3,nDims)
61 jmc 1.2 INTEGER map2gl(2)
62 jmc 1.1 INTEGER nFlds
63     CHARACTER*(8) fldList(*)
64     INTEGER nTimRec
65     _RL timList(*)
66     INTEGER nrecords
67     INTEGER myIter
68     INTEGER myThid
69     CEOP
70    
71     C !FUNCTIONS
72     INTEGER ILNBLNK
73     EXTERNAL ILNBLNK
74    
75     C !LOCAL VARIABLES:
76     INTEGER i,ii,iL
77     INTEGER mUnit
78     c LOGICAL exst
79     CHARACTER*(MAX_LEN_MBUF) msgBuf
80    
81     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
82    
83     C We should *read* the met-file IF it exists to check
84     C that the information we are writing is consistent
85     C with the current contents
86     c INQUIRE( file=mFileName, exist=exst )
87     C However, it is bloody difficult to parse files in fortran so someone
88     C else can do this.
89     C For now, we will assume everything is ok and that the last record
90     C is written to the last consecutive record in the file.
91    
92     C- Assign a free unit number as the I/O channel for this subroutine
93     CALL MDSFINDUNIT( mUnit, myThid )
94    
95     C- Open meta-file
96     OPEN( mUnit, file=mFileName, status='unknown',
97     & form='formatted' )
98    
99     C- Write the simulation name
100     iL = ILNBLNK(simulName)
101     IF ( iL.GT.0 ) THEN
102     WRITE(mUnit,'(3A)') " simulation = { '",simulName(1:iL),"' };"
103     ENDIF
104    
105     C- Write the number of dimensions
106     WRITE(mUnit,'(1X,A,I3,A)') 'nDims = [ ',nDims,' ];'
107    
108     C- For each dimension, write the following:
109     C 1 global size (ie. the size of the global dimension of all files)
110     C 2 global start (ie. the global position of the start of this file)
111     C 3 global end (ie. the global position of the end of this file)
112    
113     WRITE(mUnit,'(1X,A)') 'dimList = ['
114     DO ii=1,nDims
115     IF (ii.LT.nDims) THEN
116     WRITE(mUnit,'(1X,3(I5,","))') (dimList(i,ii),i=1,3)
117     ELSE
118     WRITE(mUnit,'(1X,I5,",",I5,",",I5)') (dimList(i,ii),i=1,3)
119     ENDIF
120     ENDDO
121     WRITE(mUnit,'(1X,A)') '];'
122 jmc 1.2 C- only write if different from default:
123     IF ( map2gl(1).NE.0 .OR. map2gl(2).NE.1 ) THEN
124     WRITE(mUnit,'(1X,2(A,I5),A)') 'map2glob = [ ',
125     & map2gl(1),',',map2gl(2),' ];'
126     ENDIF
127 jmc 1.1
128     C- Record the precision of the file
129     IF (filePrec .EQ. precFloat32) THEN
130     WRITE(mUnit,'(1X,A)') "dataprec = [ 'float32' ];"
131     ELSEIF (filePrec .EQ. precFloat64) THEN
132     WRITE(mUnit,'(1X,A)') "dataprec = [ 'float64' ];"
133     ELSE
134     WRITE(msgBuf,'(A)')
135     & ' MDSWRITEMETA: invalid filePrec'
136     CALL PRINT_ERROR( msgBuf, myThid )
137     STOP 'ABNORMAL END: S/R MDSWRITEMETA'
138     ENDIF
139    
140     C- Record the current record number
141     C This is a proxy for the actual number of records in the file.
142     C If we could read the file then we could do this properly.
143     WRITE(mUnit,'(1X,A,I5,A)') 'nrecords = [ ',nrecords,' ];'
144    
145     C- Record the file-name for the binary data
146     Cveto ii=ILNBLNK( dFileName )
147     Cveto WRITE(mUnit,'(1X,3A)') 'binarydatafile = [ ',dFileName(1:ii),' ];'
148    
149     C- Write the integer time (integer iteration number) for later record
150     C keeping. If the timestep number is less than 0 then we assume
151     C that the information is superfluous and do not write it.
152     IF ( myIter.GE.0 )
153     & WRITE(mUnit,'(1X,A,I10,A)') 'timeStepNumber = [ ',myIter,' ];'
154    
155     C- Write list of Time records
156     C note: format might change once we have a better idea of what will
157 jmc 1.2 C be the time-information to write.
158 jmc 1.1 C for now, comment out this line for rdmds (i.e.: between /* */)
159     IF ( nTimRec.GT.0 ) THEN
160     ii = MIN(nTimRec,20)
161     WRITE(msgBuf,'(1P20E20.12)') (timList(i),i=1,ii)
162     WRITE(mUnit,'(3A)')' /* modelTime = [', msgBuf(1:20*ii),' ];*/'
163     c iL = ILNBLNK(msgBuf)
164     c WRITE(mUnit,'(1X,3A)') 'modelTime = [', msgBuf(1:iL),' ];'
165     ENDIF
166    
167     C- Write list of Fields
168     IF ( nFlds.GT.0 ) THEN
169     WRITE(mUnit,'(1X,A,I4,A)') 'nFlds = [ ', nFlds, ' ];'
170     WRITE(mUnit,'(1X,A)') 'fldList = {'
171     WRITE(mUnit,'(20(A2,A8,A1))')
172     & (" '",fldList(i),"'",i=1,nFlds)
173     WRITE(mUnit,'(1X,A)') '};'
174     ENDIF
175    
176     C- Write title or comments (but ignored by rdmds)
177     iL = ILNBLNK(titleLine)
178     IF ( iL.GT.0 ) THEN
179     WRITE(mUnit,'(3A)')' /* ', titleLine(1:iL), ' */'
180     ENDIF
181    
182     C- Close meta-file
183     CLOSE(mUnit)
184    
185     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
186    
187     RETURN
188     END

  ViewVC Help
Powered by ViewVC 1.1.22