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

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

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


Revision 1.1 - (show annotations) (download)
Fri Dec 29 05:11:52 2006 UTC (18 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58u_post, checkpoint58w_post, checkpoint58t_post, checkpoint58v_post
new S/R: write meta file with options to add more informations in it.
  (intended to replace S/R MDSWRITEMETA)

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

  ViewVC Help
Powered by ViewVC 1.1.22