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

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

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


Revision 1.5 - (show annotations) (download)
Thu Oct 14 18:43:39 2004 UTC (19 years, 7 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint55i_post, checkpoint55j_post, checkpoint55h_post
Changes since 1.4: +1 -5 lines
Remove STOP in _GL for adxx, weights, etc.

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_gl.F,v 1.4 2003/10/09 04:19:19 edhill Exp $
2
3 #include "MDSIO_OPTIONS.h"
4
5 C The five "public" routines supplied here are:
6 C
7 C MDSREADFIELD - read model field from direct access global or tiled MDS file
8 C MDSWRITEFIELD - write model field to direct access global or tiled MDS file
9 C MDSFINDUNIT - returns an available (unused) I/O channel
10 C MDSREADVECTOR - read vector from direct access global or tiled MDS file
11 C MDSWRITEVECTOR - write vector to direct access global or tiled MDS file
12 C
13 C all other routines are "private" to these utilities and ought
14 C not be accessed directly from the main code.
15 C
16 C Created: 03/16/99 adcroft@mit.edu
17 C Modified: 03/23/99 adcroft@mit.edu
18 C To work with multiple records
19 C Modified: 03/29/99 eckert@mit.edu
20 C Added arbitrary vector capability
21 C Modified: 07/27/99 eckert@mit.edu
22 C Customized for state estimation (--> active_file_control.F)
23 C this relates only to *mdsreadvector* and *mdswritevector*
24 C Modified: 07/28/99 eckert@mit.edu
25 C inserted calls to *print_message* and *print_error*
26 C
27 C To be modified to work with MITgcmuv message routines.
28
29 C=======================================================================
30 SUBROUTINE MDSREADFIELD_3D_GL(
31 I fName,
32 I filePrec,
33 I arrType,
34 I nNz,
35 O arr_gl,
36 I irecord,
37 I myThid )
38 C
39 C Arguments:
40 C
41 C fName string base name for file to read
42 C filePrec integer number of bits per word in file (32 or 64)
43 C arrType char(2) declaration of "arr": either "RS" or "RL"
44 C nNz integer size of third dimension: normally either 1 or Nr
45 C arr RS/RL array to read into, arr(:,:,nNz,:,:)
46 C irecord integer record number to read
47 C myThid integer thread identifier
48 C
49 C MDSREADFIELD first checks to see if the file "fName" exists, then
50 C if the file "fName.data" exists and finally the tiled files of the
51 C form "fName.xxx.yyy.data" exist. Currently, the meta-files are not
52 C read because it is difficult to parse files in fortran.
53 C The precision of the file is decsribed by filePrec, set either
54 C to floatPrec32 or floatPrec64. The precision or declaration of
55 C the array argument must be consistently described by the char*(2)
56 C string arrType, either "RS" or "RL". nNz allows for both 2-D and
57 C 3-D arrays to be handled. nNz=1 implies a 2-D model field and
58 C nNz=Nr implies a 3-D model field. irecord is the record number
59 C to be read and must be >= 1. The file data is stored in
60 C arr *but* the overlaps are *not* updated. ie. An exchange must
61 C be called. This is because the routine is sometimes called from
62 C within a MASTER_THID region.
63 C
64 C Created: 03/16/99 adcroft@mit.edu
65
66 implicit none
67 C Global variables / common blocks
68 #include "SIZE.h"
69 #include "EEPARAMS.h"
70 #include "PARAMS.h"
71
72 C Routine arguments
73 character*(*) fName
74 integer filePrec
75 character*(2) arrType
76 integer nNz
77 _RL arr_gl(sNx,nSx,nPx,sNy,nSy,nPy,Nr)
78 integer irecord
79 integer myThid
80 C Functions
81 integer ILNBLNK
82 integer MDS_RECLEN
83 C Local variables
84 character*(80) dataFName
85 integer ip,jp,iG,jG,irec,bi,bj,ii,j,k,dUnit,IL
86 logical exst
87 _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,Nr,nSx,nSy)
88 Real*4 r4seg(sNx)
89 Real*8 r8seg(sNx)
90 logical globalFile,fileIsOpen
91 integer length_of_rec
92 character*(max_len_mbuf) msgbuf
93 C ------------------------------------------------------------------
94
95 C Only do I/O if I am the master thread
96 _BEGIN_MASTER( myThid )
97
98 C Record number must be >= 1
99 if (irecord .LT. 1) then
100 write(msgbuf,'(a,i9.8)')
101 & ' MDSREADFIELD_GL: argument irecord = ',irecord
102 call print_message( msgbuf, standardmessageunit,
103 & SQUEEZE_RIGHT , mythid)
104 write(msgbuf,'(a)')
105 & ' MDSREADFIELD_GL: Invalid value for irecord'
106 call print_error( msgbuf, mythid )
107 stop 'ABNORMAL END: S/R MDSREADFIELD_GL'
108 endif
109
110 C Assume nothing
111 globalFile = .FALSE.
112 fileIsOpen = .FALSE.
113 IL=ILNBLNK( fName )
114
115 C Assign a free unit number as the I/O channel for this routine
116 call MDSFINDUNIT( dUnit, mythid )
117
118 C Check first for global file with simple name (ie. fName)
119 dataFName = fName
120 inquire( file=dataFname, exist=exst )
121 if (exst) then
122 write(msgbuf,'(a,a)')
123 & ' MDSREADFIELD: opening global file: ',dataFName
124 call print_message( msgbuf, standardmessageunit,
125 & SQUEEZE_RIGHT , mythid)
126 endif
127
128 C If negative check for global file with MDS name (ie. fName.data)
129 if (.NOT. globalFile) then
130 write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
131 inquire( file=dataFname, exist=exst )
132 if (exst) then
133 write(msgbuf,'(a,a)')
134 & ' MDSREADFIELD_GL: opening global file: ',dataFName
135 call print_message( msgbuf, standardmessageunit,
136 & SQUEEZE_RIGHT , mythid)
137 globalFile = .TRUE.
138 endif
139 endif
140 C Loop over all processors
141 do jp=1,nPy
142 do ip=1,nPx
143 C Loop over all tiles
144 do bj=1,nSy
145 do bi=1,nSx
146 C If we are reading from a tiled MDS file then we open each one here
147 if (.NOT. globalFile) then
148 iG=bi+(ip-1)*nsx ! Kludge until unstructered tiles
149 jG=bj+(jp-1)*nsy ! Kludge until unstructered tiles
150 write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
151 & fName(1:IL),'.',iG,'.',jG,'.data'
152 inquire( file=dataFname, exist=exst )
153 C Of course, we only open the file if the tile is "active"
154 C (This is a place-holder for the active/passive mechanism
155 if (exst) then
156 if ( debugLevel .GE. debLevA ) then
157 write(msgbuf,'(a,a)')
158 & ' MDSREADFIELD_GL: opening file: ',dataFName
159 call print_message( msgbuf, standardmessageunit,
160 & SQUEEZE_RIGHT , mythid)
161 endif
162 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
163 open( dUnit, file=dataFName, status='old',
164 & access='direct', recl=length_of_rec )
165 fileIsOpen=.TRUE.
166 else
167 fileIsOpen=.FALSE.
168 write(msgbuf,'(a,a)')
169 & ' MDSREADFIELD_GL: filename: ',dataFName
170 call print_message( msgbuf, standardmessageunit,
171 & SQUEEZE_RIGHT , mythid)
172 write(msgbuf,'(a)')
173 & ' MDSREADFIELD_GL: File does not exist'
174 call print_error( msgbuf, mythid )
175 stop 'ABNORMAL END: S/R MDSREADFIELD_GL'
176 endif
177 endif
178
179 if (fileIsOpen) then
180 do k=1,Nr
181 do j=1,sNy
182 iG = 0
183 jG = 0
184 irec=j + sNy*(k-1) + sNy*Nr*(irecord-1)
185 if (filePrec .eq. precFloat32) then
186 read(dUnit,rec=irec) r4seg
187 #ifdef _BYTESWAPIO
188 call MDS_BYTESWAPR4( sNx, r4seg )
189 #endif
190 if (arrType .eq. 'RS') then
191 call MDS_SEG4toRS( j,bi,bj,k,Nr, r4seg, .TRUE., arr )
192 elseif (arrType .eq. 'RL') then
193 call MDS_SEG4toRL( j,bi,bj,k,Nr, r4seg, .TRUE., arr )
194 else
195 write(msgbuf,'(a)')
196 & ' MDSREADFIELD_GL: illegal value for arrType'
197 call print_error( msgbuf, mythid )
198 stop 'ABNORMAL END: S/R MDSREADFIELD_GL'
199 endif
200 elseif (filePrec .eq. precFloat64) then
201 read(dUnit,rec=irec) r8seg
202 #ifdef _BYTESWAPIO
203 call MDS_BYTESWAPR8( sNx, r8seg )
204 #endif
205 if (arrType .eq. 'RS') then
206 call MDS_SEG8toRS( j,bi,bj,k,Nr, r8seg, .TRUE., arr )
207 elseif (arrType .eq. 'RL') then
208 call MDS_SEG8toRL( j,bi,bj,k,Nr, r8seg, .TRUE., arr )
209 else
210 write(msgbuf,'(a)')
211 & ' MDSREADFIELD_GL: illegal value for arrType'
212 call print_error( msgbuf, mythid )
213 stop 'ABNORMAL END: S/R MDSREADFIELD_GL'
214 endif
215 else
216 write(msgbuf,'(a)')
217 & ' MDSREADFIELD_GL: illegal value for filePrec'
218 call print_error( msgbuf, mythid )
219 stop 'ABNORMAL END: S/R MDSREADFIELD_GL'
220 endif
221 do ii=1,sNx
222 arr_gl(ii,bi,ip,j,bj,jp,k)=arr(ii,j,k,bi,bj)
223 enddo
224
225 C End of j loop
226 enddo
227 C End of k loop
228 enddo
229 if (.NOT. globalFile) then
230 close( dUnit )
231 fileIsOpen = .FALSE.
232 endif
233 endif
234 C End of bi,bj loops
235 enddo
236 enddo
237 C End of ip,jp loops
238 enddo
239 enddo
240
241 C If global file was opened then close it
242 if (fileIsOpen .AND. globalFile) then
243 close( dUnit )
244 fileIsOpen = .FALSE.
245 endif
246
247 _END_MASTER( myThid )
248
249 C ------------------------------------------------------------------
250 return
251 end
252 C=======================================================================
253
254 C=======================================================================
255 SUBROUTINE MDSWRITEFIELD_3D_GL(
256 I fName,
257 I filePrec,
258 I arrType,
259 I nNz,
260 I arr_gl,
261 I irecord,
262 I myIter,
263 I myThid )
264 C
265 C Arguments:
266 C
267 C fName string base name for file to written
268 C filePrec integer number of bits per word in file (32 or 64)
269 C arrType char(2) declaration of "arr": either "RS" or "RL"
270 C nNz integer size of third dimension: normally either 1 or Nr
271 C arr RS/RL array to write, arr(:,:,nNz,:,:)
272 C irecord integer record number to read
273 C myIter integer time step number
274 C myThid integer thread identifier
275 C
276 C MDSWRITEFIELD creates either a file of the form "fName.data" and
277 C "fName.meta" if the logical flag "globalFile" is set true. Otherwise
278 C it creates MDS tiled files of the form "fName.xxx.yyy.data" and
279 C "fName.xxx.yyy.meta". A meta-file is always created.
280 C Currently, the meta-files are not read because it is difficult
281 C to parse files in fortran. We should read meta information before
282 C adding records to an existing multi-record file.
283 C The precision of the file is decsribed by filePrec, set either
284 C to floatPrec32 or floatPrec64. The precision or declaration of
285 C the array argument must be consistently described by the char*(2)
286 C string arrType, either "RS" or "RL". nNz allows for both 2-D and
287 C 3-D arrays to be handled. nNz=1 implies a 2-D model field and
288 C nNz=Nr implies a 3-D model field. irecord is the record number
289 C to be read and must be >= 1. NOTE: It is currently assumed that
290 C the highest record number in the file was the last record written.
291 C Nor is there a consistency check between the routine arguments and file.
292 C ie. if your write record 2 after record 4 the meta information
293 C will record the number of records to be 2. This, again, is because
294 C we have read the meta information. To be fixed.
295 C
296 C Created: 03/16/99 adcroft@mit.edu
297 C
298 C Changed: 05/31/00 heimbach@mit.edu
299 C open(dUnit, ..., status='old', ... -> status='unknown'
300
301 implicit none
302 C Global variables / common blocks
303 #include "SIZE.h"
304 #include "EEPARAMS.h"
305 #include "PARAMS.h"
306
307 C Routine arguments
308 character*(*) fName
309 integer filePrec
310 character*(2) arrType
311 integer nNz
312 cph(
313 cph Real arr(*)
314 _RL arr_gl(sNx,nSx,nPx,sNy,nSy,nPy,Nr)
315 cph)
316 integer irecord
317 integer myIter
318 integer myThid
319 C Functions
320 integer ILNBLNK
321 integer MDS_RECLEN
322 C Local variables
323 character*(80) dataFName,metaFName
324 integer ip,jp,iG,jG,irec,bi,bj,ii,j,k,dUnit,IL
325 Real*4 r4seg(sNx)
326 Real*8 r8seg(sNx)
327 _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,Nr,nSx,nSy)
328 integer dimList(3,3),ndims
329 integer length_of_rec
330 logical fileIsOpen
331 character*(max_len_mbuf) msgbuf
332 C ------------------------------------------------------------------
333
334 C Only do I/O if I am the master thread
335 _BEGIN_MASTER( myThid )
336
337 C Record number must be >= 1
338 if (irecord .LT. 1) then
339 write(msgbuf,'(a,i9.8)')
340 & ' MDSWRITEFIELD_GL: argument irecord = ',irecord
341 call print_message( msgbuf, standardmessageunit,
342 & SQUEEZE_RIGHT , mythid)
343 write(msgbuf,'(a)')
344 & ' MDSWRITEFIELD_GL: invalid value for irecord'
345 call print_error( msgbuf, mythid )
346 stop 'ABNORMAL END: S/R MDSWRITEFIELD_GL'
347 endif
348
349 C Assume nothing
350 fileIsOpen=.FALSE.
351 IL=ILNBLNK( fName )
352
353 C Assign a free unit number as the I/O channel for this routine
354 call MDSFINDUNIT( dUnit, mythid )
355
356
357 C Loop over all processors
358 do jp=1,nPy
359 do ip=1,nPx
360 C Loop over all tiles
361 do bj=1,nSy
362 do bi=1,nSx
363 C If we are writing to a tiled MDS file then we open each one here
364 iG=bi+(ip-1)*nsx ! Kludge until unstructered tiles
365 jG=bj+(jp-1)*nsy ! Kludge until unstructered tiles
366 write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
367 & fName(1:IL),'.',iG,'.',jG,'.data'
368 if (irecord .EQ. 1) then
369 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
370 open( dUnit, file=dataFName, status=_NEW_STATUS,
371 & access='direct', recl=length_of_rec )
372 fileIsOpen=.TRUE.
373 else
374 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
375 open( dUnit, file=dataFName, status=_OLD_STATUS,
376 & access='direct', recl=length_of_rec )
377 fileIsOpen=.TRUE.
378 endif
379 if (fileIsOpen) then
380 do k=1,Nr
381 do j=1,sNy
382 do ii=1,sNx
383 arr(ii,j,k,bi,bj)=arr_gl(ii,bi,ip,j,bj,jp,k)
384 enddo
385 iG = 0
386 jG = 0
387 irec=j + sNy*(k-1) + sNy*Nr*(irecord-1)
388 if (filePrec .eq. precFloat32) then
389 if (arrType .eq. 'RS') then
390 call MDS_SEG4toRS( j,bi,bj,k,Nr, r4seg, .FALSE., arr )
391 elseif (arrType .eq. 'RL') then
392 call MDS_SEG4toRL( j,bi,bj,k,Nr, r4seg, .FALSE., arr )
393 else
394 write(msgbuf,'(a)')
395 & ' MDSWRITEFIELD_GL: illegal value for arrType'
396 call print_error( msgbuf, mythid )
397 stop 'ABNORMAL END: S/R MDSWRITEFIELD_GL'
398 endif
399 #ifdef _BYTESWAPIO
400 call MDS_BYTESWAPR4( sNx, r4seg )
401 #endif
402 write(dUnit,rec=irec) r4seg
403 elseif (filePrec .eq. precFloat64) then
404 if (arrType .eq. 'RS') then
405 call MDS_SEG8toRS( j,bi,bj,k,Nr, r8seg, .FALSE., arr )
406 elseif (arrType .eq. 'RL') then
407 call MDS_SEG8toRL( j,bi,bj,k,Nr, r8seg, .FALSE., arr )
408 else
409 write(msgbuf,'(a)')
410 & ' MDSWRITEFIELD_GL: illegal value for arrType'
411 call print_error( msgbuf, mythid )
412 stop 'ABNORMAL END: S/R MDSWRITEFIELD_GL'
413 endif
414 #ifdef _BYTESWAPIO
415 call MDS_BYTESWAPR8( sNx, r8seg )
416 #endif
417 write(dUnit,rec=irec) r8seg
418 else
419 write(msgbuf,'(a)')
420 & ' MDSWRITEFIELD_GL: illegal value for filePrec'
421 call print_error( msgbuf, mythid )
422 stop 'ABNORMAL END: S/R MDSWRITEFIELD_GL'
423 endif
424 C End of j loop
425 enddo
426 C End of k loop
427 enddo
428 else
429 write(msgbuf,'(a)')
430 & ' MDSWRITEFIELD_GL: I should never get to this point'
431 call print_error( msgbuf, mythid )
432 stop 'ABNORMAL END: S/R MDSWRITEFIELD_GL'
433 endif
434 C If we were writing to a tiled MDS file then we close it here
435 if (fileIsOpen) then
436 close( dUnit )
437 fileIsOpen = .FALSE.
438 endif
439 C Create meta-file for each tile if we are tiling
440 iG=bi+(ip-1)*nsx ! Kludge until unstructered tiles
441 jG=bj+(jp-1)*nsy ! Kludge until unstructered tiles
442 write(metaFname(1:80),'(2a,i3.3,a,i3.3,a)')
443 & fName(1:IL),'.',iG,'.',jG,'.meta'
444 dimList(1,1)=Nx
445 dimList(2,1)=((ip-1)*nSx+(bi-1))*sNx+1
446 dimList(3,1)=((ip-1)*nSx+bi)*sNx
447 dimList(1,2)=Ny
448 dimList(2,2)=((jp-1)*nSy+(bj-1))*sNy+1
449 dimList(3,2)=((jp-1)*nSy+bj)*sNy
450 dimList(1,3)=Nr
451 dimList(2,3)=1
452 dimList(3,3)=Nr
453 ndims=3
454 if (Nr .EQ. 1) ndims=2
455 call MDSWRITEMETA( metaFName, dataFName,
456 & filePrec, ndims, dimList, irecord, myIter, mythid )
457 C End of bi,bj loops
458 enddo
459 enddo
460 C End of ip,jp loops
461 enddo
462 enddo
463
464
465 _END_MASTER( myThid )
466
467 C ------------------------------------------------------------------
468 return
469 end
470 C=======================================================================
471
472 C=======================================================================
473 SUBROUTINE MDSREADFIELD_2D_GL(
474 I fName,
475 I filePrec,
476 I arrType,
477 I nNz,
478 O arr_gl,
479 I irecord,
480 I myThid )
481 C
482 C Arguments:
483 C
484 C fName string base name for file to read
485 C filePrec integer number of bits per word in file (32 or 64)
486 C arrType char(2) declaration of "arr": either "RS" or "RL"
487 C nNz integer size of third dimension: normally either 1 or Nr
488 C arr RS/RL array to read into, arr(:,:,nNz,:,:)
489 C irecord integer record number to read
490 C myThid integer thread identifier
491 C
492 C MDSREADFIELD first checks to see if the file "fName" exists, then
493 C if the file "fName.data" exists and finally the tiled files of the
494 C form "fName.xxx.yyy.data" exist. Currently, the meta-files are not
495 C read because it is difficult to parse files in fortran.
496 C The precision of the file is decsribed by filePrec, set either
497 C to floatPrec32 or floatPrec64. The precision or declaration of
498 C the array argument must be consistently described by the char*(2)
499 C string arrType, either "RS" or "RL". nNz allows for both 2-D and
500 C 3-D arrays to be handled. nNz=1 implies a 2-D model field and
501 C nNz=Nr implies a 3-D model field. irecord is the record number
502 C to be read and must be >= 1. The file data is stored in
503 C arr *but* the overlaps are *not* updated. ie. An exchange must
504 C be called. This is because the routine is sometimes called from
505 C within a MASTER_THID region.
506 C
507 C Created: 03/16/99 adcroft@mit.edu
508
509 implicit none
510 C Global variables / common blocks
511 #include "SIZE.h"
512 #include "EEPARAMS.h"
513 #include "PARAMS.h"
514
515 C Routine arguments
516 character*(*) fName
517 integer filePrec
518 character*(2) arrType
519 integer nNz, nLocz
520 parameter (nLocz = 1)
521 _RL arr_gl(sNx,nSx,nPx,sNy,nSy,nPy,nLocz)
522 integer irecord
523 integer myThid
524 C Functions
525 integer ILNBLNK
526 integer MDS_RECLEN
527 C Local variables
528 character*(80) dataFName
529 integer ip,jp,iG,jG,irec,bi,bj,ii,j,k,dUnit,IL
530 logical exst
531 _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nLocz,nSx,nSy)
532 Real*4 r4seg(sNx)
533 Real*8 r8seg(sNx)
534 logical globalFile,fileIsOpen
535 integer length_of_rec
536 character*(max_len_mbuf) msgbuf
537 C ------------------------------------------------------------------
538
539 C Only do I/O if I am the master thread
540 _BEGIN_MASTER( myThid )
541
542 C Record number must be >= 1
543 if (irecord .LT. 1) then
544 write(msgbuf,'(a,i9.8)')
545 & ' MDSREADFIELD_GL: argument irecord = ',irecord
546 call print_message( msgbuf, standardmessageunit,
547 & SQUEEZE_RIGHT , mythid)
548 write(msgbuf,'(a)')
549 & ' MDSREADFIELD_GL: Invalid value for irecord'
550 call print_error( msgbuf, mythid )
551 stop 'ABNORMAL END: S/R MDSREADFIELD_GL'
552 endif
553
554 C Assume nothing
555 globalFile = .FALSE.
556 fileIsOpen = .FALSE.
557 IL=ILNBLNK( fName )
558
559 C Assign a free unit number as the I/O channel for this routine
560 call MDSFINDUNIT( dUnit, mythid )
561
562 C Check first for global file with simple name (ie. fName)
563 dataFName = fName
564 inquire( file=dataFname, exist=exst )
565 if (exst) then
566 write(msgbuf,'(a,a)')
567 & ' MDSREADFIELD: opening global file: ',dataFName
568 call print_message( msgbuf, standardmessageunit,
569 & SQUEEZE_RIGHT , mythid)
570 endif
571
572 C If negative check for global file with MDS name (ie. fName.data)
573 if (.NOT. globalFile) then
574 write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
575 inquire( file=dataFname, exist=exst )
576 if (exst) then
577 write(msgbuf,'(a,a)')
578 & ' MDSREADFIELD_GL: opening global file: ',dataFName
579 call print_message( msgbuf, standardmessageunit,
580 & SQUEEZE_RIGHT , mythid)
581 globalFile = .TRUE.
582 endif
583 endif
584 C Loop over all processors
585 do jp=1,nPy
586 do ip=1,nPx
587 C Loop over all tiles
588 do bj=1,nSy
589 do bi=1,nSx
590 C If we are reading from a tiled MDS file then we open each one here
591 if (.NOT. globalFile) then
592 iG=bi+(ip-1)*nsx ! Kludge until unstructered tiles
593 jG=bj+(jp-1)*nsy ! Kludge until unstructered tiles
594 write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
595 & fName(1:IL),'.',iG,'.',jG,'.data'
596 inquire( file=dataFname, exist=exst )
597 C Of course, we only open the file if the tile is "active"
598 C (This is a place-holder for the active/passive mechanism
599 if (exst) then
600 if ( debugLevel .GE. debLevA ) then
601 write(msgbuf,'(a,a)')
602 & ' MDSREADFIELD_GL: opening file: ',dataFName
603 call print_message( msgbuf, standardmessageunit,
604 & SQUEEZE_RIGHT , mythid)
605 endif
606 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
607 open( dUnit, file=dataFName, status='old',
608 & access='direct', recl=length_of_rec )
609 fileIsOpen=.TRUE.
610 else
611 fileIsOpen=.FALSE.
612 write(msgbuf,'(a,a)')
613 & ' MDSREADFIELD_GL: filename: ',dataFName
614 call print_message( msgbuf, standardmessageunit,
615 & SQUEEZE_RIGHT , mythid)
616 write(msgbuf,'(a)')
617 & ' MDSREADFIELD_GL: File does not exist'
618 call print_error( msgbuf, mythid )
619 stop 'ABNORMAL END: S/R MDSREADFIELD_GL'
620 endif
621 endif
622
623 if (fileIsOpen) then
624 do k=1,nLocz
625 do j=1,sNy
626 iG = 0
627 jG = 0
628 irec=j + sNy*(k-1) + sNy*nLocz*(irecord-1)
629 if (filePrec .eq. precFloat32) then
630 read(dUnit,rec=irec) r4seg
631 #ifdef _BYTESWAPIO
632 call MDS_BYTESWAPR4( sNx, r4seg )
633 #endif
634 if (arrType .eq. 'RS') then
635 call MDS_SEG4toRS( j,bi,bj,k,nLocz, r4seg, .TRUE., arr )
636 elseif (arrType .eq. 'RL') then
637 call MDS_SEG4toRL( j,bi,bj,k,nLocz, r4seg, .TRUE., arr )
638 else
639 write(msgbuf,'(a)')
640 & ' MDSREADFIELD_GL: illegal value for arrType'
641 call print_error( msgbuf, mythid )
642 stop 'ABNORMAL END: S/R MDSREADFIELD_GL'
643 endif
644 elseif (filePrec .eq. precFloat64) then
645 read(dUnit,rec=irec) r8seg
646 #ifdef _BYTESWAPIO
647 call MDS_BYTESWAPR8( sNx, r8seg )
648 #endif
649 if (arrType .eq. 'RS') then
650 call MDS_SEG8toRS( j,bi,bj,k,nLocz, r8seg, .TRUE., arr )
651 elseif (arrType .eq. 'RL') then
652 call MDS_SEG8toRL( j,bi,bj,k,nLocz, r8seg, .TRUE., arr )
653 else
654 write(msgbuf,'(a)')
655 & ' MDSREADFIELD_GL: illegal value for arrType'
656 call print_error( msgbuf, mythid )
657 stop 'ABNORMAL END: S/R MDSREADFIELD_GL'
658 endif
659 else
660 write(msgbuf,'(a)')
661 & ' MDSREADFIELD_GL: illegal value for filePrec'
662 call print_error( msgbuf, mythid )
663 stop 'ABNORMAL END: S/R MDSREADFIELD_GL'
664 endif
665 do ii=1,sNx
666 arr_gl(ii,bi,ip,j,bj,jp,k)=arr(ii,j,k,bi,bj)
667 enddo
668
669 C End of j loop
670 enddo
671 C End of k loop
672 enddo
673 if (.NOT. globalFile) then
674 close( dUnit )
675 fileIsOpen = .FALSE.
676 endif
677 endif
678 C End of bi,bj loops
679 enddo
680 enddo
681 C End of ip,jp loops
682 enddo
683 enddo
684
685 C If global file was opened then close it
686 if (fileIsOpen .AND. globalFile) then
687 close( dUnit )
688 fileIsOpen = .FALSE.
689 endif
690
691 _END_MASTER( myThid )
692
693 C ------------------------------------------------------------------
694 return
695 end
696 C=======================================================================
697
698 C=======================================================================
699 SUBROUTINE MDSWRITEFIELD_2D_GL(
700 I fName,
701 I filePrec,
702 I arrType,
703 I nNz,
704 I arr_gl,
705 I irecord,
706 I myIter,
707 I myThid )
708 C
709 C Arguments:
710 C
711 C fName string base name for file to written
712 C filePrec integer number of bits per word in file (32 or 64)
713 C arrType char(2) declaration of "arr": either "RS" or "RL"
714 C nNz integer size of third dimension: normally either 1 or Nr
715 C arr RS/RL array to write, arr(:,:,nNz,:,:)
716 C irecord integer record number to read
717 C myIter integer time step number
718 C myThid integer thread identifier
719 C
720 C MDSWRITEFIELD creates either a file of the form "fName.data" and
721 C "fName.meta" if the logical flag "globalFile" is set true. Otherwise
722 C it creates MDS tiled files of the form "fName.xxx.yyy.data" and
723 C "fName.xxx.yyy.meta". A meta-file is always created.
724 C Currently, the meta-files are not read because it is difficult
725 C to parse files in fortran. We should read meta information before
726 C adding records to an existing multi-record file.
727 C The precision of the file is decsribed by filePrec, set either
728 C to floatPrec32 or floatPrec64. The precision or declaration of
729 C the array argument must be consistently described by the char*(2)
730 C string arrType, either "RS" or "RL". nNz allows for both 2-D and
731 C 3-D arrays to be handled. nNz=1 implies a 2-D model field and
732 C nNz=Nr implies a 3-D model field. irecord is the record number
733 C to be read and must be >= 1. NOTE: It is currently assumed that
734 C the highest record number in the file was the last record written.
735 C Nor is there a consistency check between the routine arguments and file.
736 C ie. if your write record 2 after record 4 the meta information
737 C will record the number of records to be 2. This, again, is because
738 C we have read the meta information. To be fixed.
739 C
740 C Created: 03/16/99 adcroft@mit.edu
741 C
742 C Changed: 05/31/00 heimbach@mit.edu
743 C open(dUnit, ..., status='old', ... -> status='unknown'
744
745 implicit none
746 C Global variables / common blocks
747 #include "SIZE.h"
748 #include "EEPARAMS.h"
749 #include "PARAMS.h"
750
751 C Routine arguments
752 character*(*) fName
753 integer filePrec
754 character*(2) arrType
755 integer nNz, nLocz
756 parameter (nLocz = 1)
757 cph(
758 cph Real arr(*)
759 _RL arr_gl(sNx,nSx,nPx,sNy,nSy,nPy,nLocz)
760 cph)
761 integer irecord
762 integer myIter
763 integer myThid
764 C Functions
765 integer ILNBLNK
766 integer MDS_RECLEN
767 C Local variables
768 character*(80) dataFName,metaFName
769 integer ip,jp,iG,jG,irec,bi,bj,ii,j,k,dUnit,IL
770 Real*4 r4seg(sNx)
771 Real*8 r8seg(sNx)
772 _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nLocz,nSx,nSy)
773 integer dimList(3,3),ndims
774 integer length_of_rec
775 logical fileIsOpen
776 character*(max_len_mbuf) msgbuf
777 C ------------------------------------------------------------------
778
779 C Only do I/O if I am the master thread
780 _BEGIN_MASTER( myThid )
781
782 C Record number must be >= 1
783 if (irecord .LT. 1) then
784 write(msgbuf,'(a,i9.8)')
785 & ' MDSWRITEFIELD_GL: argument irecord = ',irecord
786 call print_message( msgbuf, standardmessageunit,
787 & SQUEEZE_RIGHT , mythid)
788 write(msgbuf,'(a)')
789 & ' MDSWRITEFIELD_GL: invalid value for irecord'
790 call print_error( msgbuf, mythid )
791 stop 'ABNORMAL END: S/R MDSWRITEFIELD_GL'
792 endif
793
794 C Assume nothing
795 fileIsOpen=.FALSE.
796 IL=ILNBLNK( fName )
797
798 C Assign a free unit number as the I/O channel for this routine
799 call MDSFINDUNIT( dUnit, mythid )
800
801
802 C Loop over all processors
803 do jp=1,nPy
804 do ip=1,nPx
805 C Loop over all tiles
806 do bj=1,nSy
807 do bi=1,nSx
808 C If we are writing to a tiled MDS file then we open each one here
809 iG=bi+(ip-1)*nsx ! Kludge until unstructered tiles
810 jG=bj+(jp-1)*nsy ! Kludge until unstructered tiles
811 write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
812 & fName(1:IL),'.',iG,'.',jG,'.data'
813 if (irecord .EQ. 1) then
814 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
815 open( dUnit, file=dataFName, status=_NEW_STATUS,
816 & access='direct', recl=length_of_rec )
817 fileIsOpen=.TRUE.
818 else
819 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
820 open( dUnit, file=dataFName, status=_OLD_STATUS,
821 & access='direct', recl=length_of_rec )
822 fileIsOpen=.TRUE.
823 endif
824 if (fileIsOpen) then
825 do k=1,nLocz
826 do j=1,sNy
827 do ii=1,sNx
828 arr(ii,j,k,bi,bj)=arr_gl(ii,bi,ip,j,bj,jp,k)
829 enddo
830 iG = 0
831 jG = 0
832 irec=j + sNy*(k-1) + sNy*nLocz*(irecord-1)
833 if (filePrec .eq. precFloat32) then
834 if (arrType .eq. 'RS') then
835 call MDS_SEG4toRS( j,bi,bj,k,nLocz, r4seg, .FALSE., arr )
836 elseif (arrType .eq. 'RL') then
837 call MDS_SEG4toRL( j,bi,bj,k,nLocz, r4seg, .FALSE., arr )
838 else
839 write(msgbuf,'(a)')
840 & ' MDSWRITEFIELD_GL: illegal value for arrType'
841 call print_error( msgbuf, mythid )
842 stop 'ABNORMAL END: S/R MDSWRITEFIELD_GL'
843 endif
844 #ifdef _BYTESWAPIO
845 call MDS_BYTESWAPR4( sNx, r4seg )
846 #endif
847 write(dUnit,rec=irec) r4seg
848 elseif (filePrec .eq. precFloat64) then
849 if (arrType .eq. 'RS') then
850 call MDS_SEG8toRS( j,bi,bj,k,nLocz, r8seg, .FALSE., arr )
851 elseif (arrType .eq. 'RL') then
852 call MDS_SEG8toRL( j,bi,bj,k,nLocz, r8seg, .FALSE., arr )
853 else
854 write(msgbuf,'(a)')
855 & ' MDSWRITEFIELD_GL: illegal value for arrType'
856 call print_error( msgbuf, mythid )
857 stop 'ABNORMAL END: S/R MDSWRITEFIELD_GL'
858 endif
859 #ifdef _BYTESWAPIO
860 call MDS_BYTESWAPR8( sNx, r8seg )
861 #endif
862 write(dUnit,rec=irec) r8seg
863 else
864 write(msgbuf,'(a)')
865 & ' MDSWRITEFIELD_GL: illegal value for filePrec'
866 call print_error( msgbuf, mythid )
867 stop 'ABNORMAL END: S/R MDSWRITEFIELD_GL'
868 endif
869 C End of j loop
870 enddo
871 C End of k loop
872 enddo
873 else
874 write(msgbuf,'(a)')
875 & ' MDSWRITEFIELD_GL: I should never get to this point'
876 call print_error( msgbuf, mythid )
877 stop 'ABNORMAL END: S/R MDSWRITEFIELD_GL'
878 endif
879 C If we were writing to a tiled MDS file then we close it here
880 if (fileIsOpen) then
881 close( dUnit )
882 fileIsOpen = .FALSE.
883 endif
884 C Create meta-file for each tile if we are tiling
885 iG=bi+(ip-1)*nsx ! Kludge until unstructered tiles
886 jG=bj+(jp-1)*nsy ! Kludge until unstructered tiles
887 write(metaFname(1:80),'(2a,i3.3,a,i3.3,a)')
888 & fName(1:IL),'.',iG,'.',jG,'.meta'
889 dimList(1,1)=Nx
890 dimList(2,1)=((ip-1)*nSx+(bi-1))*sNx+1
891 dimList(3,1)=((ip-1)*nSx+bi)*sNx
892 dimList(1,2)=Ny
893 dimList(2,2)=((jp-1)*nSy+(bj-1))*sNy+1
894 dimList(3,2)=((jp-1)*nSy+bj)*sNy
895 dimList(1,3)=Nr
896 dimList(2,3)=1
897 dimList(3,3)=Nr
898 ndims=3
899 if (nLocz .EQ. 1) ndims=2
900 call MDSWRITEMETA( metaFName, dataFName,
901 & filePrec, ndims, dimList, irecord, myIter, mythid )
902 C End of bi,bj loops
903 enddo
904 enddo
905 C End of ip,jp loops
906 enddo
907 enddo
908
909
910 _END_MASTER( myThid )
911
912 C ------------------------------------------------------------------
913 return
914 end
915 C=======================================================================

  ViewVC Help
Powered by ViewVC 1.1.22