/[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.7 - (show annotations) (download)
Sun Aug 2 20:42:43 2009 UTC (14 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64a, checkpoint64b, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint62, checkpoint63, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint61v, checkpoint61w, checkpoint61u, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.6: +3 -3 lines
changed to pass when compiling with strick checking of arguments across S/R

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_wr_metafiles.F,v 1.6 2009/06/28 01:06:39 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_SIZE.h"
50 #include "W2_EXCH2_TOPOLOGY.h"
51 #include "W2_EXCH2_PARAMS.h"
52 #endif /* ALLOW_EXCH2 */
53 C Arguments:
54 C
55 C fName (string) :: base name for file to write
56 C filePrec (integer) :: number of bits per word in file (32 or 64)
57 C globalFile (logical):: selects between writing a global or tiled file
58 C useCurrentDir(logic):: always write to the current directory (even if
59 C "mdsioLocalDir" is set)
60 C nNx,nNy (integer) :: used for writing YZ or XZ slice
61 C nNz (integer) :: number of vertical levels to be written
62 C titleLine (string) :: title or any descriptive comments
63 C nFlds (integer) :: number of fields from "fldList" to write
64 C fldList (string) :: array of fields name to write
65 C nTimRec (integer) :: number of time-info from "fldList" to write
66 C timList (real) :: array of time-info to write
67 C irecord (integer) :: record number to write
68 C myIter (integer) :: time step number
69 C myThid (integer) :: thread identifier
70 C
71 C Routine arguments
72 CHARACTER*(*) fName
73 INTEGER filePrec
74 LOGICAL globalFile
75 LOGICAL useCurrentDir
76 INTEGER nNx, nNy, nNz
77 CHARACTER*(*) titleLine
78 INTEGER nFlds
79 CHARACTER*(8) fldList(*)
80 INTEGER nTimRec
81 _RL timList(*)
82 INTEGER irecord
83 INTEGER myIter
84 INTEGER myThid
85 CEOP
86
87 C Functions
88 INTEGER ILNBLNK
89 EXTERNAL ILNBLNK
90 LOGICAL MASTER_CPU_IO
91 EXTERNAL MASTER_CPU_IO
92 C Local variables
93 CHARACTER*(MAX_LEN_FNAM) dataFName, metaFName, pfName
94 INTEGER iG,jG, bi,bj, IL,pIL
95 INTEGER dimList(3,3), nDims, map2gl(2)
96 INTEGER xSize, ySize
97 INTEGER tBx, tBy
98 #ifdef ALLOW_EXCH2
99 INTEGER tN
100 #endif /* ALLOW_EXCH2 */
101
102 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
103 C- Set dimensions:
104 xSize = Nx
105 ySize = Ny
106 #ifdef ALLOW_EXCH2
107 IF ( W2_useE2ioLayOut ) THEN
108 xSize = exch2_global_Nx
109 ySize = exch2_global_Ny
110 ENDIF
111 #endif /* ALLOW_EXCH2 */
112 IF (nNx.EQ.1) xSize = 1
113 IF (nNy.EQ.1) ySize = 1
114
115 C Only do I/O if I am the master thread (and mpi process 0 IF useSingleCpuIO):
116 IF ( MASTER_CPU_IO(myThid) ) THEN
117
118 IF ( useSingleCpuIO .OR. globalFile ) THEN
119
120 IL = ILNBLNK( fName )
121 WRITE(dataFName,'(2A)') fName(1:IL),'.data'
122 WRITE(metaFName,'(2A)') fName(1:IL),'.meta'
123 dimList(1,1) = xSize
124 dimList(2,1) = 1
125 dimList(3,1) = xSize
126 dimList(1,2) = ySize
127 dimList(2,2) = 1
128 dimList(3,2) = ySize
129 dimList(1,3) = nNz
130 dimList(2,3) = 1
131 dimList(3,3) = nNz
132 nDims=3
133 IF (nNz.EQ.1) nDims=2
134 map2gl(1) = 0
135 map2gl(2) = 1
136 CALL MDS_WRITE_META(
137 I metaFName, dataFName, the_run_name, titleLine,
138 I filePrec, nDims,dimList,map2gl, nFlds, fldList,
139 I nTimRec, timList, irecord, myIter, myThid )
140
141 ELSE
142
143 C Assign special directory
144 pIL = ILNBLNK( mdsioLocalDir )
145 IF ( useCurrentDir .OR. pIL.EQ.0 ) THEN
146 pfName = fName
147 ELSE
148 IL = ILNBLNK( fName )
149 WRITE(pfName,'(2A)') mdsioLocalDir(1:pIL), fName(1:IL)
150 ENDIF
151 pIL=ILNBLNK( pfName )
152
153 C Loop over all tiles
154 DO bj=1,nSy
155 DO bi=1,nSx
156 C If we are writing to a tiled MDS file then we open each one here
157 iG=bi+(myXGlobalLo-1)/sNx
158 jG=bj+(myYGlobalLo-1)/sNy
159 WRITE(dataFName,'(2a,i3.3,a,i3.3,a)')
160 & pfName(1:pIL),'.',iG,'.',jG,'.data'
161 C Create meta-file for each tile IF we are tiling
162 WRITE(metaFname,'(2a,i3.3,a,i3.3,a)')
163 & pfName(1:pIL),'.',iG,'.',jG,'.meta'
164 tBx = myXGlobalLo-1 + (bi-1)*sNx
165 tBy = myYGlobalLo-1 + (bj-1)*sNy
166 map2gl(1) = 0
167 map2gl(2) = 1
168 #ifdef ALLOW_EXCH2
169 IF ( W2_useE2ioLayOut ) THEN
170 tN = W2_myTileList(bi,bj)
171 tBx = exch2_txGlobalo(tN) - 1
172 tBy = exch2_tyGlobalo(tN) - 1
173 IF (nNx.EQ.0 .AND. nNy.EQ.0) THEN
174 IF ( exch2_mydNx(tN) .GT. xSize ) THEN
175 C- face x-size larger than glob-size : fold it
176 map2gl(1) = 0
177 map2gl(2) = exch2_mydNx(tN) / xSize
178 ELSEIF ( exch2_tNy(tN) .GT. ySize ) THEN
179 C- tile y-size larger than glob-size : make a long line
180 map2gl(1) = exch2_mydNx(tN)
181 map2gl(2) = 0
182 ELSE
183 C- default (face fit into global-IO-array)
184 map2gl(1) = 0
185 map2gl(2) = 1
186 ENDIF
187 ENDIF
188 ENDIF
189 #endif /* ALLOW_EXCH2 */
190 dimList(1,1) = xSize
191 dimList(2,1) = tBx + 1
192 dimList(3,1) = tBx + sNx
193 dimList(1,2) = ySize
194 dimList(2,2) = tBy + 1
195 dimList(3,2) = tBy + sNy
196 dimList(1,3) = nNz
197 dimList(2,3) = 1
198 dimList(3,3) = nNz
199 nDims=3
200 IF (nNz.EQ.1) nDims=2
201 IF (nNx.EQ.1) dimList(2,1) = 1
202 IF (nNx.EQ.1) dimList(3,1) = 1
203 IF (nNy.EQ.1) dimList(2,2) = 1
204 IF (nNy.EQ.1) dimList(3,2) = 1
205 CALL MDS_WRITE_META(
206 I metaFName, dataFName, the_run_name, titleLine,
207 I filePrec, nDims,dimList,map2gl, nFlds, fldList,
208 I nTimRec, timList, irecord, myIter, myThid )
209 C End of bi,bj loops
210 ENDDO
211 ENDDO
212
213 C endif useSingleCpuIO or globalFile
214 ENDIF
215
216 C endif MASTER_CPU_IO
217 ENDIF
218
219 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
220
221 RETURN
222 END

  ViewVC Help
Powered by ViewVC 1.1.22