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

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

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


Revision 1.8 - (show annotations) (download)
Sun Jan 13 22:43:53 2013 UTC (11 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64c, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, HEAD
Changes since 1.7: +6 -3 lines
- add missing value argument to S/R MDS_WRITE_META argument list

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_wr_metafiles.F,v 1.7 2009/08/02 20:42:43 jmc Exp $
2 C $Name: $
3
4 #include "MDSIO_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 CBOP
8 C !ROUTINE: MDS_WR_METAFILES
9 C !INTERFACE:
10 SUBROUTINE MDS_WR_METAFILES(
11 I fName,
12 I filePrec,
13 I globalFile,
14 I useCurrentDir,
15 I nNx, nNy, nNz,
16 I titleLine,
17 I nFlds, fldList,
18 I nTimRec, timList,
19 I misVal,
20 I irecord,
21 I myIter,
22 I myThid )
23
24 C !DESCRIPTION:
25 C
26 C MDS_WR_METAFILES creates either a file of the form "fName.meta" IF the
27 C logical flag "globalFile" or "useSingleCPUIO" are set true. Otherwise
28 C it creates MDS tiled files of the form "fName.xxx.yyy.meta".
29 C Currently, the meta-files are not read because it is difficult
30 C to parse files in fortran. We should read meta information before
31 C adding records to an existing multi-record file.
32 C The precision of the file is decsribed by filePrec, set either
33 C to floatPrec32 or floatPrec64.
34 C nNz=1 implies a 2-D model field and nNz=Nr implies a 3-D model field.
35 C irecord is the record number to be written and must be >= 1.
36 C NOTE: It is currently assumed that
37 C the highest record number in the file was the last record written.
38 C Nor is there a consistency check between the routine arguments and file.
39 C ie. if you write record 2 after record 4 the meta information
40 C will record the number of records to be 2. This, again, is because
41 C we have read the meta information. To be fixed.
42
43 C !USES:
44 IMPLICIT NONE
45 C Global variables / COMMON blocks
46 #include "SIZE.h"
47 #include "EEPARAMS.h"
48 #include "PARAMS.h"
49 #ifdef ALLOW_EXCH2
50 #include "W2_EXCH2_SIZE.h"
51 #include "W2_EXCH2_TOPOLOGY.h"
52 #include "W2_EXCH2_PARAMS.h"
53 #endif /* ALLOW_EXCH2 */
54 C Arguments:
55 C
56 C fName (string) :: base name for file to write
57 C filePrec (integer) :: number of bits per word in file (32 or 64)
58 C globalFile (logical):: selects between writing a global or tiled file
59 C useCurrentDir(logic):: always write to the current directory (even if
60 C "mdsioLocalDir" is set)
61 C nNx,nNy (integer) :: used for writing YZ or XZ slice
62 C nNz (integer) :: number of vertical levels to be written
63 C titleLine (string) :: title or any descriptive comments
64 C nFlds (integer) :: number of fields from "fldList" to write
65 C fldList (string) :: array of fields name to write
66 C nTimRec (integer) :: number of time-info from "fldList" to write
67 C timList (real) :: array of time-info to write
68 C misVal (real) :: missing value (ignored if = 1.)
69 C irecord (integer) :: record number to write
70 C myIter (integer) :: time step number
71 C myThid (integer) :: thread identifier
72 C
73 C Routine arguments
74 CHARACTER*(*) fName
75 INTEGER filePrec
76 LOGICAL globalFile
77 LOGICAL useCurrentDir
78 INTEGER nNx, nNy, nNz
79 CHARACTER*(*) titleLine
80 INTEGER nFlds
81 CHARACTER*(8) fldList(*)
82 INTEGER nTimRec
83 _RL timList(*)
84 _RL misVal
85 INTEGER irecord
86 INTEGER myIter
87 INTEGER myThid
88 CEOP
89
90 C Functions
91 INTEGER ILNBLNK
92 EXTERNAL ILNBLNK
93 LOGICAL MASTER_CPU_IO
94 EXTERNAL MASTER_CPU_IO
95 C Local variables
96 CHARACTER*(MAX_LEN_FNAM) dataFName, metaFName, pfName
97 INTEGER iG,jG, bi,bj, IL,pIL
98 INTEGER dimList(3,3), nDims, map2gl(2)
99 INTEGER xSize, ySize
100 INTEGER tBx, tBy
101 #ifdef ALLOW_EXCH2
102 INTEGER tN
103 #endif /* ALLOW_EXCH2 */
104
105 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
106 C- Set dimensions:
107 xSize = Nx
108 ySize = Ny
109 #ifdef ALLOW_EXCH2
110 IF ( W2_useE2ioLayOut ) THEN
111 xSize = exch2_global_Nx
112 ySize = exch2_global_Ny
113 ENDIF
114 #endif /* ALLOW_EXCH2 */
115 IF (nNx.EQ.1) xSize = 1
116 IF (nNy.EQ.1) ySize = 1
117
118 C Only do I/O if I am the master thread (and mpi process 0 IF useSingleCpuIO):
119 IF ( MASTER_CPU_IO(myThid) ) THEN
120
121 IF ( useSingleCpuIO .OR. globalFile ) THEN
122
123 IL = ILNBLNK( fName )
124 WRITE(dataFName,'(2A)') fName(1:IL),'.data'
125 WRITE(metaFName,'(2A)') fName(1:IL),'.meta'
126 dimList(1,1) = xSize
127 dimList(2,1) = 1
128 dimList(3,1) = xSize
129 dimList(1,2) = ySize
130 dimList(2,2) = 1
131 dimList(3,2) = ySize
132 dimList(1,3) = nNz
133 dimList(2,3) = 1
134 dimList(3,3) = nNz
135 nDims=3
136 IF (nNz.EQ.1) nDims=2
137 map2gl(1) = 0
138 map2gl(2) = 1
139 CALL MDS_WRITE_META(
140 I metaFName, dataFName, the_run_name, titleLine,
141 I filePrec, nDims,dimList,map2gl, nFlds, fldList,
142 I nTimRec, timList, misVal, irecord, myIter, myThid )
143
144 ELSE
145
146 C Assign special directory
147 pIL = ILNBLNK( mdsioLocalDir )
148 IF ( useCurrentDir .OR. pIL.EQ.0 ) THEN
149 pfName = fName
150 ELSE
151 IL = ILNBLNK( fName )
152 WRITE(pfName,'(2A)') mdsioLocalDir(1:pIL), fName(1:IL)
153 ENDIF
154 pIL=ILNBLNK( pfName )
155
156 C Loop over all tiles
157 DO bj=1,nSy
158 DO bi=1,nSx
159 C If we are writing to a tiled MDS file then we open each one here
160 iG=bi+(myXGlobalLo-1)/sNx
161 jG=bj+(myYGlobalLo-1)/sNy
162 WRITE(dataFName,'(2a,i3.3,a,i3.3,a)')
163 & pfName(1:pIL),'.',iG,'.',jG,'.data'
164 C Create meta-file for each tile IF we are tiling
165 WRITE(metaFname,'(2a,i3.3,a,i3.3,a)')
166 & pfName(1:pIL),'.',iG,'.',jG,'.meta'
167 tBx = myXGlobalLo-1 + (bi-1)*sNx
168 tBy = myYGlobalLo-1 + (bj-1)*sNy
169 map2gl(1) = 0
170 map2gl(2) = 1
171 #ifdef ALLOW_EXCH2
172 IF ( W2_useE2ioLayOut ) THEN
173 tN = W2_myTileList(bi,bj)
174 tBx = exch2_txGlobalo(tN) - 1
175 tBy = exch2_tyGlobalo(tN) - 1
176 IF (nNx.EQ.0 .AND. nNy.EQ.0) THEN
177 IF ( exch2_mydNx(tN) .GT. xSize ) THEN
178 C- face x-size larger than glob-size : fold it
179 map2gl(1) = 0
180 map2gl(2) = exch2_mydNx(tN) / xSize
181 ELSEIF ( exch2_tNy(tN) .GT. ySize ) THEN
182 C- tile y-size larger than glob-size : make a long line
183 map2gl(1) = exch2_mydNx(tN)
184 map2gl(2) = 0
185 ELSE
186 C- default (face fit into global-IO-array)
187 map2gl(1) = 0
188 map2gl(2) = 1
189 ENDIF
190 ENDIF
191 ENDIF
192 #endif /* ALLOW_EXCH2 */
193 dimList(1,1) = xSize
194 dimList(2,1) = tBx + 1
195 dimList(3,1) = tBx + sNx
196 dimList(1,2) = ySize
197 dimList(2,2) = tBy + 1
198 dimList(3,2) = tBy + sNy
199 dimList(1,3) = nNz
200 dimList(2,3) = 1
201 dimList(3,3) = nNz
202 nDims=3
203 IF (nNz.EQ.1) nDims=2
204 IF (nNx.EQ.1) dimList(2,1) = 1
205 IF (nNx.EQ.1) dimList(3,1) = 1
206 IF (nNy.EQ.1) dimList(2,2) = 1
207 IF (nNy.EQ.1) dimList(3,2) = 1
208 CALL MDS_WRITE_META(
209 I metaFName, dataFName, the_run_name, titleLine,
210 I filePrec, nDims,dimList,map2gl, nFlds, fldList,
211 I nTimRec, timList, misVal, irecord, myIter, myThid )
212 C End of bi,bj loops
213 ENDDO
214 ENDDO
215
216 C endif useSingleCpuIO or globalFile
217 ENDIF
218
219 C endif MASTER_CPU_IO
220 ENDIF
221
222 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
223
224 RETURN
225 END

  ViewVC Help
Powered by ViewVC 1.1.22