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

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

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


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

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

  ViewVC Help
Powered by ViewVC 1.1.22