/[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.2 - (show 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, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i
Changes since 1.1: +31 -16 lines
to read/write compact global files: add parameter for mapping tile to global file.

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

  ViewVC Help
Powered by ViewVC 1.1.22