/[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.3 - (hide annotations) (download)
Sun Jul 20 12:26:10 2008 UTC (16 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i
Changes since 1.2: +1 -2 lines
PARAMS.h no longer needed

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

  ViewVC Help
Powered by ViewVC 1.1.22