/[MITgcm]/MITgcm/eesupp/src/mdsio.F
ViewVC logotype

Contents of /MITgcm/eesupp/src/mdsio.F

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


Revision 1.4 - (show annotations) (download)
Wed Jul 28 17:39:17 1999 UTC (24 years, 9 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint24
Changes since 1.3: +281 -91 lines
Implemented error/informational messages using print_message.
Changes made by C.E.

1 C $Header: /u/gcmpack/models/MITgcmUV/eesupp/src/mdsio.F,v 1.3 1999/05/17 14:40:36 adcroft Exp $
2
3 #include "CPP_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 #undef SAFE_IO
30
31 #ifdef SAFE_IO
32 #define _NEW_STATUS 'new'
33 #else
34 #define _NEW_STATUS 'unknown'
35 #endif
36
37 C=======================================================================
38 SUBROUTINE MDSREADFIELD(
39 I fName,
40 I filePrec,
41 I arrType,
42 I nNz,
43 O arr,
44 I irecord,
45 I myThid )
46 C
47 C Arguments:
48 C
49 C fName string base name for file to read
50 C filePrec integer number of bits per word in file (32 or 64)
51 C arrType char(2) declaration of "arr": either "RS" or "RL"
52 C nNz integer size of third dimension: normally either 1 or Nr
53 C arr RS/RL array to read into, arr(:,:,nNz,:,:)
54 C irecord integer record number to read
55 C myThid integer thread identifier
56 C
57 C MDSREADFIELD first checks to see if the file "fName" exists, then
58 C if the file "fName.data" exists and finally the tiled files of the
59 C form "fName.xxx.yyy.data" exist. Currently, the meta-files are not
60 C read because it is difficult to parse files in fortran.
61 C The precision of the file is decsribed by filePrec, set either
62 C to floatPrec32 or floatPrec64. The precision or declaration of
63 C the array argument must be consistently described by the char*(2)
64 C string arrType, either "RS" or "RL". nNz allows for both 2-D and
65 C 3-D arrays to be handled. nNz=1 implies a 2-D model field and
66 C nNz=Nr implies a 3-D model field. irecord is the record number
67 C to be read and must be >= 1. The file data is stored in
68 C arr *but* the overlaps are *not* updated. ie. An exchange must
69 C be called. This is because the routine is sometimes called from
70 C within a MASTER_THID region.
71 C
72 C Created: 03/16/99 adcroft@mit.edu
73
74 implicit none
75 C Global variables / common blocks
76 #include "SIZE.h"
77 #include "EEPARAMS.h"
78 #include "PARAMS.h"
79
80 C Routine arguments
81 character*(*) fName
82 integer filePrec
83 character*(2) arrType
84 integer nNz
85 Real arr(*)
86 integer irecord
87 integer myThid
88 C Functions
89 integer ILNBLNK
90 integer MDS_RECLEN
91 C Local variables
92 character*(80) dataFName
93 integer iG,jG,irec,bi,bj,j,k,dUnit,IL
94 logical exst
95 Real*4 r4seg(sNx)
96 Real*8 r8seg(sNx)
97 logical globalFile,fileIsOpen
98 integer length_of_rec
99 character*(max_len_mbuf) msgbuf
100 C ------------------------------------------------------------------
101
102 C Only do I/O if I am the master thread
103 _BEGIN_MASTER( myThid )
104
105 C Record number must be >= 1
106 if (irecord .LT. 1) then
107 write(msgbuf,'(a,i9.8)')
108 & ' MDSREADFIELD: argument irecord = ',irecord
109 call print_message( msgbuf, standardmessageunit,
110 & SQUEEZE_RIGHT , mythid)
111 write(msgbuf,'(a)')
112 & ' MDSREADFIELD: Invalid value for irecord'
113 call print_error( msgbuf, mythid )
114 stop 'ABNORMAL END: S/R MDSREADFIELD'
115 endif
116
117 C Assume nothing
118 globalFile = .FALSE.
119 fileIsOpen = .FALSE.
120 IL=ILNBLNK( fName )
121
122 C Assign a free unit number as the I/O channel for this routine
123 call MDSFINDUNIT( dUnit, mythid )
124
125 C Check first for global file with simple name (ie. fName)
126 dataFName = fName
127 inquire( file=dataFname, exist=exst )
128 if (exst) then
129 write(msgbuf,'(a,a)')
130 & ' MDSREADFIELD: opening global file: ',dataFName
131 call print_message( msgbuf, standardmessageunit,
132 & SQUEEZE_RIGHT , mythid)
133 globalFile = .TRUE.
134 endif
135
136 C If negative check for global file with MDS name (ie. fName.data)
137 if (.NOT. globalFile) then
138 write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
139 inquire( file=dataFname, exist=exst )
140 if (exst) then
141 write(msgbuf,'(a,a)')
142 & ' MDSREADFIELD: opening global file: ',dataFName
143 call print_message( msgbuf, standardmessageunit,
144 & SQUEEZE_RIGHT , mythid)
145 globalFile = .TRUE.
146 endif
147 endif
148
149 C If we are reading from a global file then we open it here
150 if (globalFile) then
151 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
152 open( dUnit, file=dataFName, status='old',
153 & access='direct', recl=length_of_rec )
154 fileIsOpen=.TRUE.
155 endif
156
157 C Loop over all tiles
158 do bj=1,nSy
159 do bi=1,nSx
160 C If we are reading from a tiled MDS file then we open each one here
161 if (.NOT. globalFile) then
162 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
163 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
164 write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
165 & fName(1:IL),'.',iG,'.',jG,'.data'
166 inquire( file=dataFname, exist=exst )
167 C Of course, we only open the file if the tile is "active"
168 C (This is a place-holder for the active/passive mechanism
169 if (exst) then
170 write(msgbuf,'(a,a)')
171 & ' MDSREADFIELD: opening file: ',dataFName
172 call print_message( msgbuf, standardmessageunit,
173 & SQUEEZE_RIGHT , mythid)
174 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
175 open( dUnit, file=dataFName, status='old',
176 & access='direct', recl=length_of_rec )
177 fileIsOpen=.TRUE.
178 else
179 fileIsOpen=.FALSE.
180 write(msgbuf,'(a,a)')
181 & ' MDSREADFIELD: filename: ',dataFName
182 call print_message( msgbuf, standardmessageunit,
183 & SQUEEZE_RIGHT , mythid)
184 write(msgbuf,'(a)')
185 & ' MDSREADFIELD: File does not exist'
186 call print_error( msgbuf, mythid )
187 stop 'ABNORMAL END: S/R MDSREADFIELD'
188 endif
189 endif
190
191 if (fileIsOpen) then
192 do k=1,nNz
193 do j=1,sNy
194 if (globalFile) then
195 iG = myXGlobalLo-1 + (bi-1)*sNx
196 jG = myYGlobalLo-1 + (bj-1)*sNy
197 irec=1 + INT(iG/sNx) + nSx*nPx*(jG+j-1) + nSx*nPx*Ny*(k-1)
198 & + nSx*nPx*Ny*nNz*(irecord-1)
199 else
200 iG = 0
201 jG = 0
202 irec=j + sNy*(k-1) + sNy*nNz*(irecord-1)
203 endif
204 if (filePrec .eq. precFloat32) then
205 read(dUnit,rec=irec) r4seg
206 #ifdef _BYTESWAPIO
207 call MDS_BYTESWAPR4( sNx, r4seg )
208 #endif
209 if (arrType .eq. 'RS') then
210 call MDS_SEG4toRS( j,bi,bj,k,nNz, r4seg, .TRUE., arr )
211 elseif (arrType .eq. 'RL') then
212 call MDS_SEG4toRL( j,bi,bj,k,nNz, r4seg, .TRUE., arr )
213 else
214 write(msgbuf,'(a)')
215 & ' MDSREADFIELD: illegal value for arrType'
216 call print_error( msgbuf, mythid )
217 stop 'ABNORMAL END: S/R MDSREADFIELD'
218 endif
219 elseif (filePrec .eq. precFloat64) then
220 read(dUnit,rec=irec) r8seg
221 #ifdef _BYTESWAPIO
222 call MDS_BYTESWAPR8( sNx, r8seg )
223 #endif
224 if (arrType .eq. 'RS') then
225 call MDS_SEG8toRS( j,bi,bj,k,nNz, r8seg, .TRUE., arr )
226 elseif (arrType .eq. 'RL') then
227 call MDS_SEG8toRL( j,bi,bj,k,nNz, r8seg, .TRUE., arr )
228 else
229 write(msgbuf,'(a)')
230 & ' MDSREADFIELD: illegal value for arrType'
231 call print_error( msgbuf, mythid )
232 stop 'ABNORMAL END: S/R MDSREADFIELD'
233 endif
234 else
235 write(msgbuf,'(a)')
236 & ' MDSREADFIELD: illegal value for filePrec'
237 call print_error( msgbuf, mythid )
238 stop 'ABNORMAL END: S/R MDSREADFIELD'
239 endif
240 C End of j loop
241 enddo
242 C End of k loop
243 enddo
244 if (.NOT. globalFile) then
245 close( dUnit )
246 fileIsOpen = .FALSE.
247 endif
248 endif
249 C End of bi,bj loops
250 enddo
251 enddo
252
253 C If global file was opened then close it
254 if (fileIsOpen .AND. globalFile) then
255 close( dUnit )
256 fileIsOpen = .FALSE.
257 endif
258
259 _END_MASTER( myThid )
260
261 C ------------------------------------------------------------------
262 return
263 end
264 C=======================================================================
265
266 C=======================================================================
267 SUBROUTINE MDSWRITEFIELD(
268 I fName,
269 I filePrec,
270 I globalFile,
271 I arrType,
272 I nNz,
273 I arr,
274 I irecord,
275 I myIter,
276 I myThid )
277 C
278 C Arguments:
279 C
280 C fName string base name for file to written
281 C filePrec integer number of bits per word in file (32 or 64)
282 C globalFile logical selects between writing a global or tiled file
283 C arrType char(2) declaration of "arr": either "RS" or "RL"
284 C nNz integer size of third dimension: normally either 1 or Nr
285 C arr RS/RL array to write, arr(:,:,nNz,:,:)
286 C irecord integer record number to read
287 C myIter integer time step number
288 C myThid integer thread identifier
289 C
290 C MDSWRITEFIELD creates either a file of the form "fName.data" and
291 C "fName.meta" if the logical flag "globalFile" is set true. Otherwise
292 C it creates MDS tiled files of the form "fName.xxx.yyy.data" and
293 C "fName.xxx.yyy.meta". A meta-file is always created.
294 C Currently, the meta-files are not read because it is difficult
295 C to parse files in fortran. We should read meta information before
296 C adding records to an existing multi-record file.
297 C The precision of the file is decsribed by filePrec, set either
298 C to floatPrec32 or floatPrec64. The precision or declaration of
299 C the array argument must be consistently described by the char*(2)
300 C string arrType, either "RS" or "RL". nNz allows for both 2-D and
301 C 3-D arrays to be handled. nNz=1 implies a 2-D model field and
302 C nNz=Nr implies a 3-D model field. irecord is the record number
303 C to be read and must be >= 1. NOTE: It is currently assumed that
304 C the highest record number in the file was the last record written.
305 C Nor is there a consistency check between the routine arguments and file.
306 C ie. if your write record 2 after record 4 the meta information
307 C will record the number of records to be 2. This, again, is because
308 C we have read the meta information. To be fixed.
309 C
310 C Created: 03/16/99 adcroft@mit.edu
311
312 implicit none
313 C Global variables / common blocks
314 #include "SIZE.h"
315 #include "EEPARAMS.h"
316 #include "PARAMS.h"
317
318 C Routine arguments
319 character*(*) fName
320 integer filePrec
321 logical globalFile
322 character*(2) arrType
323 integer nNz
324 Real arr(*)
325 integer irecord
326 integer myIter
327 integer myThid
328 C Functions
329 integer ILNBLNK
330 integer MDS_RECLEN
331 C Local variables
332 character*(80) dataFName,metaFName
333 integer iG,jG,irec,bi,bj,j,k,dUnit,IL
334 Real*4 r4seg(sNx)
335 Real*8 r8seg(sNx)
336 integer dimList(3,3),ndims
337 integer length_of_rec
338 logical fileIsOpen
339 character*(max_len_mbuf) msgbuf
340 C ------------------------------------------------------------------
341
342 C Only do I/O if I am the master thread
343 _BEGIN_MASTER( myThid )
344
345 C Record number must be >= 1
346 if (irecord .LT. 1) then
347 write(msgbuf,'(a,i9.8)')
348 & ' MDSWRITEFIELD: argument irecord = ',irecord
349 call print_message( msgbuf, standardmessageunit,
350 & SQUEEZE_RIGHT , mythid)
351 write(msgbuf,'(a)')
352 & ' MDSWRITEFIELD: invalid value for irecord'
353 call print_error( msgbuf, mythid )
354 stop 'ABNORMAL END: S/R MDSWRITEFIELD'
355 endif
356
357 C Assume nothing
358 fileIsOpen=.FALSE.
359 IL=ILNBLNK( fName )
360
361 C Assign a free unit number as the I/O channel for this routine
362 call MDSFINDUNIT( dUnit, mythid )
363
364 C If we are writing to a global file then we open it here
365 if (globalFile) then
366 write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
367 if (irecord .EQ. 1) then
368 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
369 open( dUnit, file=dataFName, status=_NEW_STATUS,
370 & access='direct', recl=length_of_rec )
371 fileIsOpen=.TRUE.
372 else
373 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
374 open( dUnit, file=dataFName, status='old',
375 & access='direct', recl=length_of_rec )
376 fileIsOpen=.TRUE.
377 endif
378 endif
379
380 C Loop over all tiles
381 do bj=1,nSy
382 do bi=1,nSx
383 C If we are writing to a tiled MDS file then we open each one here
384 if (.NOT. globalFile) then
385 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
386 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
387 write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
388 & fName(1:IL),'.',iG,'.',jG,'.data'
389 if (irecord .EQ. 1) then
390 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
391 open( dUnit, file=dataFName, status=_NEW_STATUS,
392 & access='direct', recl=length_of_rec )
393 fileIsOpen=.TRUE.
394 else
395 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
396 open( dUnit, file=dataFName, status='old',
397 & access='direct', recl=length_of_rec )
398 fileIsOpen=.TRUE.
399 endif
400 endif
401 if (fileIsOpen) then
402 do k=1,nNz
403 do j=1,sNy
404 if (globalFile) then
405 iG = myXGlobalLo-1+(bi-1)*sNx
406 jG = myYGlobalLo-1+(bj-1)*sNy
407 irec=1+INT(iG/sNx)+nSx*nPx*(jG+j-1)+nSx*nPx*Ny*(k-1)
408 & +nSx*nPx*Ny*nNz*(irecord-1)
409 else
410 iG = 0
411 jG = 0
412 irec=j + sNy*(k-1) + sNy*nNz*(irecord-1)
413 endif
414 if (filePrec .eq. precFloat32) then
415 if (arrType .eq. 'RS') then
416 call MDS_SEG4toRS( j,bi,bj,k,nNz, r4seg, .FALSE., arr )
417 elseif (arrType .eq. 'RL') then
418 call MDS_SEG4toRL( j,bi,bj,k,nNz, r4seg, .FALSE., arr )
419 else
420 write(msgbuf,'(a)')
421 & ' MDSWRITEFIELD: illegal value for arrType'
422 call print_error( msgbuf, mythid )
423 stop 'ABNORMAL END: S/R MDSWRITEFIELD'
424 endif
425 #ifdef _BYTESWAPIO
426 call MDS_BYTESWAPR4( sNx, r4seg )
427 #endif
428 write(dUnit,rec=irec) r4seg
429 elseif (filePrec .eq. precFloat64) then
430 if (arrType .eq. 'RS') then
431 call MDS_SEG8toRS( j,bi,bj,k,nNz, r8seg, .FALSE., arr )
432 elseif (arrType .eq. 'RL') then
433 call MDS_SEG8toRL( j,bi,bj,k,nNz, r8seg, .FALSE., arr )
434 else
435 write(msgbuf,'(a)')
436 & ' MDSWRITEFIELD: illegal value for arrType'
437 call print_error( msgbuf, mythid )
438 stop 'ABNORMAL END: S/R MDSWRITEFIELD'
439 endif
440 #ifdef _BYTESWAPIO
441 call MDS_BYTESWAPR8( sNx, r8seg )
442 #endif
443 write(dUnit,rec=irec) r8seg
444 else
445 write(msgbuf,'(a)')
446 & ' MDSWRITEFIELD: illegal value for filePrec'
447 call print_error( msgbuf, mythid )
448 stop 'ABNORMAL END: S/R MDSWRITEFIELD'
449 endif
450 C End of j loop
451 enddo
452 C End of k loop
453 enddo
454 else
455 write(msgbuf,'(a)')
456 & ' MDSWRITEFIELD: I should never get to this point'
457 call print_error( msgbuf, mythid )
458 stop 'ABNORMAL END: S/R MDSWRITEFIELD'
459 endif
460 C If we were writing to a tiled MDS file then we close it here
461 if (fileIsOpen .AND. (.NOT. globalFile)) then
462 close( dUnit )
463 fileIsOpen = .FALSE.
464 endif
465 C Create meta-file for each tile if we are tiling
466 if (.NOT. globalFile) then
467 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
468 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
469 write(metaFname(1:80),'(2a,i3.3,a,i3.3,a)')
470 & fName(1:IL),'.',iG,'.',jG,'.meta'
471 dimList(1,1)=Nx
472 dimList(2,1)=myXGlobalLo+(bi-1)*sNx
473 dimList(3,1)=myXGlobalLo+bi*sNx-1
474 dimList(1,2)=Ny
475 dimList(2,2)=myYGlobalLo+(bj-1)*sNy
476 dimList(3,2)=myYGlobalLo+bj*sNy-1
477 dimList(1,3)=Nr
478 dimList(2,3)=1
479 dimList(3,3)=Nr
480 ndims=3
481 if (nNz .EQ. 1) ndims=2
482 call MDSWRITEMETA( metaFName, dataFName,
483 & filePrec, ndims, dimList, irecord, myIter, mythid )
484 endif
485 C End of bi,bj loops
486 enddo
487 enddo
488
489 C If global file was opened then close it
490 if (fileIsOpen .AND. globalFile) then
491 close( dUnit )
492 fileIsOpen = .FALSE.
493 endif
494
495 C Create meta-file for the global-file
496 if (globalFile) then
497 C We can't do this operation using threads (yet) because of the
498 C "barrier" at the next step. The barrier could be removed but
499 C at the cost of "safe" distributed I/O.
500 if (nThreads.NE.1) then
501 write(msgbuf,'(a,a)')
502 & ' MDSWRITEFIELD: A threads version of this routine',
503 & ' does not exist.'
504 call print_message( msgbuf, standardmessageunit,
505 & SQUEEZE_RIGHT , mythid)
506 write(msgbuf,'(a)')
507 & ' MDSWRITEFIELD: This needs to be fixed...'
508 call print_message( msgbuf, standardmessageunit,
509 & SQUEEZE_RIGHT , mythid)
510 write(msgbuf,'(a,i3.2)')
511 & ' MDSWRITEFIELD: nThreads = ',nThreads
512 call print_message( msgbuf, standardmessageunit,
513 & SQUEEZE_RIGHT , mythid)
514 write(msgbuf,'(a)')
515 & ' MDSWRITEFIELD: Stopping because you are using threads'
516 call print_error( msgbuf, mythid )
517 stop 'ABNORMAL END: S/R MDSWRITEFIELD'
518 endif
519 C We put a barrier here to ensure that all processes have finished
520 C writing their data before we update the meta-file
521 _BARRIER
522 write(metaFName(1:80),'(2a)') fName(1:IL),'.meta'
523 dimList(1,1)=Nx
524 dimList(2,1)=1
525 dimList(3,1)=Nx
526 dimList(1,2)=Ny
527 dimList(2,2)=1
528 dimList(3,2)=Ny
529 dimList(1,3)=Nr
530 dimList(2,3)=1
531 dimList(3,3)=Nr
532 ndims=3
533 if (nNz .EQ. 1) ndims=2
534 call MDSWRITEMETA( metaFName, dataFName,
535 & filePrec, ndims, dimList, irecord, myIter, mythid )
536 fileIsOpen=.TRUE.
537 endif
538
539 _END_MASTER( myThid )
540
541 C ------------------------------------------------------------------
542 return
543 end
544 C=======================================================================
545
546 C=======================================================================
547 subroutine MDS_SEG4toRS( j,bi,bj,k,nNz, seg, copyTo, arr )
548 C IN:
549 C j,bi,bj,k integer - indices to array "arr"
550 C nNz integer - K dimension of array "arr"
551 C seg Real*4 - 1-D vector of length sNx
552 C OUT:
553 C arr _RS - model tiled array
554 C
555 C Created: 03/20/99 adcroft@mit.edu
556
557 implicit none
558 C Global variables / common blocks
559 #include "SIZE.h"
560
561 C Arguments
562 integer j,bi,bj,k,nNz
563 _RS arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nNz,nSx,nSy)
564 logical copyTo
565 Real*4 seg(sNx)
566 C Local
567 integer ii
568
569 C ------------------------------------------------------------------
570
571 if (copyTo) then
572 do ii=1,sNx
573 arr(ii,j,k,bi,bj)=seg(ii)
574 enddo
575 else
576 do ii=1,sNx
577 seg(ii)=arr(ii,j,k,bi,bj)
578 enddo
579 endif
580
581 C ------------------------------------------------------------------
582 return
583 end
584 C=======================================================================
585
586 C=======================================================================
587 subroutine MDS_SEG4toRL( j,bi,bj,k,nNz, seg, copyTo, arr )
588 C IN:
589 C j,bi,bj,k integer - indices to array "arr"
590 C nNz integer - K dimension of array "arr"
591 C seg Real*4 - 1-D vector of length sNx
592 C OUT:
593 C arr _RL - model tiled array
594 C
595 C Created: 03/20/99 adcroft@mit.edu
596
597 implicit none
598 C Global variables / common blocks
599 #include "SIZE.h"
600
601 C Arguments
602 integer j,bi,bj,k,nNz
603 _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nNz,nSx,nSy)
604 logical copyTo
605 Real*4 seg(sNx)
606 C Local
607 integer ii
608 C ------------------------------------------------------------------
609 if (copyTo) then
610 do ii=1,sNx
611 arr(ii,j,k,bi,bj)=seg(ii)
612 enddo
613 else
614 do ii=1,sNx
615 seg(ii)=arr(ii,j,k,bi,bj)
616 enddo
617 endif
618 C ------------------------------------------------------------------
619 return
620 end
621 C=======================================================================
622
623 C=======================================================================
624 subroutine MDS_SEG8toRS( j,bi,bj,k,nNz, seg, copyTo, arr )
625 C IN:
626 C j,bi,bj,k integer - indices to array "arr"
627 C nNz integer - K dimension of array "arr"
628 C seg Real*8 - 1-D vector of length sNx
629 C OUT:
630 C arr _RS - model tiled array
631 C
632 C Created: 03/20/99 adcroft@mit.edu
633
634 implicit none
635 C Global variables / common blocks
636 #include "SIZE.h"
637
638 C Arguments
639 integer j,bi,bj,k,nNz
640 _RS arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nNz,nSx,nSy)
641 logical copyTo
642 Real*8 seg(sNx)
643 C Local
644 integer ii
645 C ------------------------------------------------------------------
646 if (copyTo) then
647 do ii=1,sNx
648 arr(ii,j,k,bi,bj)=seg(ii)
649 enddo
650 else
651 do ii=1,sNx
652 seg(ii)=arr(ii,j,k,bi,bj)
653 enddo
654 endif
655 C ------------------------------------------------------------------
656 return
657 end
658 C=======================================================================
659
660 C=======================================================================
661 subroutine MDS_SEG8toRL( j,bi,bj,k,nNz, seg, copyTo, arr )
662 C IN:
663 C j,bi,bj,k integer - indices to array "arr"
664 C nNz integer - K dimension of array "arr"
665 C seg Real*8 - 1-D vector of length sNx
666 C OUT:
667 C arr _RL - model tiled array
668 C
669 C Created: 03/20/99 adcroft@mit.edu
670
671 implicit none
672 C Global variables / common blocks
673 #include "SIZE.h"
674
675 C Arguments
676 integer j,bi,bj,k,nNz
677 _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nNz,nSx,nSy)
678 logical copyTo
679 Real*8 seg(sNx)
680 C Local
681 integer ii
682 C ------------------------------------------------------------------
683 if (copyTo) then
684 do ii=1,sNx
685 arr(ii,j,k,bi,bj)=seg(ii)
686 enddo
687 else
688 do ii=1,sNx
689 seg(ii)=arr(ii,j,k,bi,bj)
690 enddo
691 endif
692 C ------------------------------------------------------------------
693 return
694 end
695 C=======================================================================
696
697 C=======================================================================
698 subroutine MDSWRITEMETA(
699 I mFileName,
700 I dFileName,
701 I filePrec,
702 I ndims,
703 I dimList,
704 I nrecords,
705 I myIter,
706 I mythid )
707
708 C IN:
709 C mFileName string - complete name of meta-file
710 C dFileName string - complete name of data-file
711 C ndims integer - number of dimensions
712 C dimList integer - array of dimensions, etc.
713 C nrecords integer - record number
714 C myIter integer - time-step number
715 C mythid integer - thread id
716 C OUT:
717 C
718 C Created: 03/20/99 adcroft@mit.edu
719
720 implicit none
721 C Arguments
722 character*(*) mFileName
723 character*(*) dFileName
724 integer filePrec
725 integer ndims
726 integer dimList(3,ndims)
727 integer nrecords
728 integer myIter
729 integer mythid
730
731 C Global variables / common blocks
732 #include "SIZE.h"
733 #include "EEPARAMS.h"
734 #include "PARAMS.h"
735
736 C Functions
737 integer ILNBLNK
738 C Local
739 integer i,ii,mUnit
740 logical ex
741 character*(max_len_mbuf) msgbuf
742 C ------------------------------------------------------------------
743
744 C We should *read* the met-file if it exists to check
745 C that the information we are writing is consistent
746 C with the current contents
747 inquire( file=mFileName, exist=ex )
748 C However, it is bloody difficult to parse files
749 C in fortran so someone else can do this.
750 C For now, we will assume everything is ok
751 C and that the last record is written to the
752 C last consecutive record in the file.
753
754 C Assign a free unit number as the I/O channel for this subroutine
755 call MDSFINDUNIT( mUnit, mythid )
756
757 C Open meta-file
758 open( mUnit, file=mFileName, status='unknown',
759 & form='formatted' )
760
761 C Write the number of dimensions
762 write(mUnit,'(x,a,i3,a)') 'nDims = [ ',ndims,' ];'
763
764 C For each dimension, write the following:
765 C 1 global size (ie. the size of the global dimension of all files)
766 C 2 global start (ie. the global position of the start of this file)
767 C 3 global end (ie. the global position of the end of this file)
768
769 write(mUnit,'(x,a)') 'dimList = ['
770 do ii=1,ndims
771 if (ii.lt.ndims) then
772 write(mUnit,'(10x,3(i5,","))') (dimList(i,ii),i=1,3)
773 else
774 write(mUnit,'(10x,i5,",",i5,",",i5)') (dimList(i,ii),i=1,3)
775 endif
776 enddo
777 write(mUnit,'(10x,a)') '];'
778
779 C Record the precision of the file
780 if (filePrec .EQ. precFloat32) then
781 write(mUnit,'(x,a)') "format = [ 'float32' ];"
782 elseif (filePrec .EQ. precFloat64) then
783 write(mUnit,'(x,a)') "format = [ 'float64' ];"
784 else
785 write(msgbuf,'(a)')
786 & ' MDSWRITEMETA: invalid filePrec'
787 call print_error( msgbuf, mythid )
788 stop 'ABNORMAL END: S/R MDSWRITEMETA'
789 endif
790
791 C Record the current record number
792 C This is a proxy for the actual number of records in the file.
793 C If we could read the file then we could do this properly.
794 write(mUnit,'(x,a,i5,a)') 'nrecords = [ ',nrecords,' ];'
795
796 C Record the file-name for the binary data
797 Cveto ii=ILNBLNK( dFileName )
798 Cveto write(mUnit,'(x,3a)') 'binarydatafile = [ ',dFileName(1:ii),' ];'
799
800 C Write the integer time (integer iteration number) for later record
801 C keeping. If the timestep number is less than 0 then we assume
802 C that the information is superfluous and do not write it.
803 if (myIter .ge. 0)
804 & write(mUnit,'(x,a,i8,a)') 'timeStepNumber = [ ',myIter,' ];'
805
806 C Close meta-file
807 close(mUnit)
808
809 C ------------------------------------------------------------------
810 return
811 end
812 C=======================================================================
813
814 C=======================================================================
815 subroutine MDSFINDUNIT( iounit, mythid )
816 C OUT:
817 C iounit integer - unit number
818 C
819 C MDSFINDUNIT returns a valid, unused unit number for f77 I/O
820 C The routine stops the program is an error occurs in the process
821 C of searching the I/O channels.
822 C
823 C Created: 03/20/99 adcroft@mit.edu
824
825 implicit none
826
827 #include "EEPARAMS.h"
828
829 C Arguments
830 integer iounit
831 integer mythid
832 C Local
833 integer ii
834 logical op
835 integer ios
836 character*(max_len_mbuf) msgbuf
837 C ------------------------------------------------------------------
838
839 C Sweep through a valid range of unit numbers
840 iounit=-1
841 do ii=9,99
842 if (iounit.eq.-1) then
843 inquire(unit=ii,iostat=ios,opened=op)
844 if (ios.ne.0) then
845 write(msgbuf,'(a,i2.2)')
846 & ' MDSFINDUNIT: inquiring unit number = ',ii
847 call print_message( msgbuf, standardmessageunit,
848 & SQUEEZE_RIGHT , mythid)
849 write(msgbuf,'(a)')
850 & ' MDSFINDUNIT: inquire statement failed!'
851 call print_error( msgbuf, mythid )
852 stop 'ABNORMAL END: S/R MDSFINDUNIT'
853 endif
854 if (.NOT. op) then
855 iounit=ii
856 endif
857 endif
858 enddo
859
860 C Was there an available unit number
861 if (iounit.eq.-1) then
862 write(msgbuf,'(a)')
863 & ' MDSFINDUNIT: could not find an available unit number!'
864 call print_error( msgbuf, mythid )
865 stop 'ABNORMAL END: S/R MDSFINDUNIT'
866 endif
867
868 C ------------------------------------------------------------------
869 return
870 end
871 C=======================================================================
872
873 C=======================================================================
874 integer function MDS_RECLEN( filePrec, nnn, mythid )
875 C IN:
876 C filePrec integer - precision of file in bits
877 C nnn integer - number of elements in record
878 C OUT:
879 C MDS_RECLEN integer - appropriate length of record in bytes or words
880 C
881 C Created: 03/29/99 eckert@mit.edu + adcroft@mit.edu
882
883 implicit none
884 C Arguments
885 integer filePrec
886 integer nnn
887 integer mythid
888 C Global variables
889 #include "SIZE.h"
890 #include "EEPARAMS.h"
891 #include "PARAMS.h"
892 C Local
893 character*(max_len_mbuf) msgbuf
894 C ------------------------------------------------------------------
895
896 if (filePrec .EQ. precFloat32) then
897 MDS_RECLEN=nnn*WORDLENGTH
898 elseif (filePrec .EQ. precFloat64) then
899 MDS_RECLEN=nnn*WORDLENGTH*2
900 else
901 write(msgbuf,'(a,i2.2)')
902 & ' MDS_RECLEN: filePrec = ',filePrec
903 call print_message( msgbuf, standardmessageunit,
904 & SQUEEZE_RIGHT , mythid)
905 write(msgbuf,'(a)')
906 & ' MDS_RECLEN: illegal value for filePrec'
907 call print_error( msgbuf, mythid )
908 stop 'ABNORMAL END: S/R MDS_RECLEN'
909 endif
910
911 C ------------------------------------------------------------------
912 return
913 end
914 C=======================================================================
915
916 C=======================================================================
917 SUBROUTINE MDSREADVECTOR(
918 I fName,
919 I filePrec,
920 I arrType,
921 I narr,
922 O arr,
923 I bi,
924 I bj,
925 I irecord,
926 I myThid )
927 C
928 C Arguments:
929 C
930 C fName string base name for file to read
931 C filePrec integer number of bits per word in file (32 or 64)
932 C arrType char(2) declaration of "arr": either "RS" or "RL"
933 C narr integer size of third dimension: normally either 1 or Nr
934 C arr RS/RL array to read into, arr(narr)
935 ce bi integer x tile index
936 ce bj integer y tile index
937 C irecord integer record number to read
938 C myThid integer thread identifier
939 C
940 C Created: 03/26/99 eckert@mit.edu
941 C Modified: 03/29/99 adcroft@mit.edu + eckert@mit.edu
942 C Fixed to work work with _RS and _RL declarations
943 C Modified: 07/27/99 eckert@mit.edu
944 C Customized for state estimation (--> active_file_control.F)
945
946 implicit none
947 C Global variables / common blocks
948 #include "SIZE.h"
949 #include "EEPARAMS.h"
950 #include "PARAMS.h"
951
952 C Routine arguments
953 character*(*) fName
954 integer filePrec
955 character*(2) arrType
956 integer narr
957 Real arr(narr)
958 integer irecord
959 integer myThid
960 ce
961 integer bi,bj
962 ce
963
964 C Functions
965 integer ILNBLNK
966 integer MDS_RECLEN
967 C Local variables
968 character*(80) dataFName
969 integer iG,jG,irec,dUnit,IL
970 logical exst
971 logical globalFile,fileIsOpen
972 integer length_of_rec
973 character*(max_len_mbuf) msgbuf
974 C ------------------------------------------------------------------
975
976 C Only do I/O if I am the master thread
977 _BEGIN_MASTER( myThid )
978
979 C Record number must be >= 1
980 if (irecord .LT. 1) then
981 write(msgbuf,'(a,i9.8)')
982 & ' MDSREADVECTOR: argument irecord = ',irecord
983 call print_message( msgbuf, standardmessageunit,
984 & SQUEEZE_RIGHT , mythid)
985 write(msgbuf,'(a)')
986 & ' MDSREADVECTOR: invalid value for irecord'
987 call print_error( msgbuf, mythid )
988 stop 'ABNORMAL END: S/R MDSREADVECTOR'
989 endif
990
991 C Assume nothing
992 globalFile = .FALSE.
993 fileIsOpen = .FALSE.
994 IL=ILNBLNK( fName )
995
996 C Assign a free unit number as the I/O channel for this routine
997 call MDSFINDUNIT( dUnit, mythid )
998
999 C Check first for global file with simple name (ie. fName)
1000 dataFName = fName
1001 inquire( file=dataFname, exist=exst )
1002 if (exst) then
1003 write(msgbuf,'(a,a)')
1004 & ' MDSREADVECTOR: opening global file: ',dataFName
1005 call print_message( msgbuf, standardmessageunit,
1006 & SQUEEZE_RIGHT , mythid)
1007 globalFile = .TRUE.
1008 endif
1009
1010 C If negative check for global file with MDS name (ie. fName.data)
1011 if (.NOT. globalFile) then
1012 write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
1013 inquire( file=dataFname, exist=exst )
1014 if (exst) then
1015 write(msgbuf,'(a,a)')
1016 & ' MDSREADVECTOR: opening global file: ',dataFName
1017 call print_message( msgbuf, standardmessageunit,
1018 & SQUEEZE_RIGHT , mythid)
1019 globalFile = .TRUE.
1020 endif
1021 endif
1022
1023 C If we are reading from a global file then we open it here
1024 if (globalFile) then
1025 length_of_rec=MDS_RECLEN( filePrec, narr, mythid )
1026 open( dUnit, file=dataFName, status='old',
1027 & access='direct', recl=length_of_rec )
1028 fileIsOpen=.TRUE.
1029 endif
1030
1031 C Loop over all tiles
1032 ce do bj=1,nSy
1033 ce do bi=1,nSx
1034 C If we are reading from a tiled MDS file then we open each one here
1035 if (.NOT. globalFile) then
1036 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
1037 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
1038 write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
1039 & fName(1:IL),'.',iG,'.',jG,'.data'
1040 inquire( file=dataFname, exist=exst )
1041 C Of course, we only open the file if the tile is "active"
1042 C (This is a place-holder for the active/passive mechanism)
1043 if (exst) then
1044 write(msgbuf,'(a,a)')
1045 & ' MDSREADVECTOR: opening file: ',dataFName
1046 call print_message( msgbuf, standardmessageunit,
1047 & SQUEEZE_RIGHT , mythid)
1048 length_of_rec=MDS_RECLEN( filePrec, narr, mythid )
1049 open( dUnit, file=dataFName, status='old',
1050 & access='direct', recl=length_of_rec )
1051 fileIsOpen=.TRUE.
1052 else
1053 fileIsOpen=.FALSE.
1054 write(msgbuf,'(a)')
1055 & ' MDSREADVECTOR: un-active tiles not implemented yet'
1056 call print_error( msgbuf, mythid )
1057 stop 'ABNORMAL END: S/R MDSREADVECTOR'
1058 endif
1059 endif
1060 if (fileIsOpen) then
1061 if (globalFile) then
1062 iG = myXGlobalLo-1+(bi-1)*sNx
1063 jG = myYGlobalLo-1+(bj-1)*sNy
1064 irec = 1 + int(iG/sNx) + (jG/sNy)*nSx*nPx +
1065 & (irecord-1)*nSx*nPx*nSy*nPy
1066 else
1067 iG = 0
1068 jG = 0
1069 irec = irecord
1070 endif
1071 if (filePrec .eq. precFloat32) then
1072 call MDS_READ_RS_VEC( dUnit, irec, narr, arr )
1073 elseif (filePrec .eq. precFloat64) then
1074 call MDS_READ_RL_VEC( dUnit, irec, narr, arr )
1075 else
1076 write(msgbuf,'(a)')
1077 & ' MDSREADVECTOR: illegal value for filePrec'
1078 call print_error( msgbuf, mythid )
1079 stop 'ABNORMAL END: S/R MDSREADVECTOR'
1080 endif
1081 if (.NOT. globalFile) then
1082 close( dUnit )
1083 fileIsOpen = .FALSE.
1084 endif
1085 endif
1086 C End of bi,bj loops
1087 ce enddo
1088 ce enddo
1089
1090 C If global file was opened then close it
1091 if (fileIsOpen .AND. globalFile) then
1092 close( dUnit )
1093 fileIsOpen = .FALSE.
1094 endif
1095
1096 _END_MASTER( myThid )
1097
1098 C ------------------------------------------------------------------
1099 return
1100 end
1101 C=======================================================================
1102
1103 C=======================================================================
1104 SUBROUTINE MDSWRITEVECTOR(
1105 I fName,
1106 I filePrec,
1107 I globalfile,
1108 I arrType,
1109 I narr,
1110 I arr,
1111 I bi,
1112 I bj,
1113 I irecord,
1114 I myIter,
1115 I myThid )
1116 C Arguments:
1117 C
1118 C fName string base name for file to written
1119 C filePrec integer number of bits per word in file (32 or 64)
1120 C globalFile logical selects between writing a global or tiled file
1121 C arrType char(2) declaration of "arr": either "RS" or "RL"
1122 C narr integer size of third dimension: normally either 1 or Nr
1123 C arr RS/RL array to write, arr(narr)
1124 ce bi integer x tile index
1125 ce bj integer y tile index
1126 C irecord integer record number to read
1127 C myIter integer time step number
1128 C myThid integer thread identifier
1129 C
1130 C Created: 03/26/99 eckert@mit.edu
1131 C Modified: 03/29/99 adcroft@mit.edu + eckert@mit.edu
1132 C Fixed to work work with _RS and _RL declarations
1133 C Modified: 07/27/99 eckert@mit.edu
1134 C Customized for state estimation (--> active_file_control.F)
1135
1136 implicit none
1137 C Global variables / common blocks
1138 #include "SIZE.h"
1139 #include "EEPARAMS.h"
1140 #include "PARAMS.h"
1141
1142 C Routine arguments
1143 character*(*) fName
1144 integer filePrec
1145 logical globalfile
1146 character*(2) arrType
1147 integer narr
1148 Real arr(narr)
1149 integer irecord
1150 integer myIter
1151 integer myThid
1152 ce
1153 integer bi,bj
1154 ce
1155
1156 C Functions
1157 integer ILNBLNK
1158 integer MDS_RECLEN
1159 C Local variables
1160 character*(80) dataFName,metaFName
1161 integer iG,jG,irec,dUnit,IL
1162 logical fileIsOpen
1163 integer dimList(3,3),ndims
1164 integer length_of_rec
1165 character*(max_len_mbuf) msgbuf
1166 C ------------------------------------------------------------------
1167
1168 C Only do I/O if I am the master thread
1169 _BEGIN_MASTER( myThid )
1170
1171 C Record number must be >= 1
1172 if (irecord .LT. 1) then
1173 write(msgbuf,'(a,i9.8)')
1174 & ' MDSWRITEVECTOR: argument irecord = ',irecord
1175 call print_message( msgbuf, standardmessageunit,
1176 & SQUEEZE_RIGHT , mythid)
1177 write(msgbuf,'(a)')
1178 & ' MDSWRITEVECTOR: invalid value for irecord'
1179 call print_error( msgbuf, mythid )
1180 stop 'ABNORMAL END: S/R MDSWRITEVECTOR'
1181 endif
1182
1183 C Assume nothing
1184 fileIsOpen = .FALSE.
1185 IL=ILNBLNK( fName )
1186
1187 C Assign a free unit number as the I/O channel for this routine
1188 call MDSFINDUNIT( dUnit, mythid )
1189
1190 C If we are writing to a global file then we open it here
1191 if (globalFile) then
1192 write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
1193 if (irecord .EQ. 1) then
1194 length_of_rec = MDS_RECLEN( filePrec, narr, mythid )
1195 open( dUnit, file=dataFName, status=_NEW_STATUS,
1196 & access='direct', recl=length_of_rec )
1197 fileIsOpen=.TRUE.
1198 else
1199 length_of_rec = MDS_RECLEN( filePrec, narr, mythid )
1200 open( dUnit, file=dataFName, status='old',
1201 & access='direct', recl=length_of_rec )
1202 fileIsOpen=.TRUE.
1203 endif
1204 endif
1205
1206 C Loop over all tiles
1207 ce do bj=1,nSy
1208 ce do bi=1,nSx
1209 C If we are writing to a tiled MDS file then we open each one here
1210 if (.NOT. globalFile) then
1211 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
1212 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
1213 write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
1214 & fName(1:IL),'.',iG,'.',jG,'.data'
1215 if (irecord .EQ. 1) then
1216 length_of_rec = MDS_RECLEN( filePrec, narr, mythid )
1217 open( dUnit, file=dataFName, status=_NEW_STATUS,
1218 & access='direct', recl=length_of_rec )
1219 fileIsOpen=.TRUE.
1220 else
1221 length_of_rec = MDS_RECLEN( filePrec, narr, mythid )
1222 open( dUnit, file=dataFName, status='old',
1223 & access='direct', recl=length_of_rec )
1224 fileIsOpen=.TRUE.
1225 endif
1226 endif
1227 if (fileIsOpen) then
1228 if (globalFile) then
1229 iG = myXGlobalLo-1+(bi-1)*sNx
1230 jG = myYGlobalLo-1+(bj-1)*sNy
1231 irec = 1 + int(iG/sNx) + (jG/sNy)*nSx*nPx +
1232 & (irecord-1)*nSx*nPx*nSy*nPy
1233 else
1234 iG = 0
1235 jG = 0
1236 irec = irecord
1237 endif
1238 if (filePrec .eq. precFloat32) then
1239 call MDS_WRITE_RS_VEC( dUnit, irec, narr, arr )
1240 elseif (filePrec .eq. precFloat64) then
1241 call MDS_WRITE_RL_VEC( dUnit, irec, narr, arr )
1242 else
1243 write(msgbuf,'(a)')
1244 & ' MDSWRITEVECTOR: illegal value for filePrec'
1245 call print_error( msgbuf, mythid )
1246 stop 'ABNORMAL END: S/R MDSWRITEVECTOR'
1247 endif
1248 else
1249 write(msgbuf,'(a)')
1250 & ' MDSWRITEVECTOR: I should never get to this point'
1251 call print_error( msgbuf, mythid )
1252 stop 'ABNORMAL END: S/R MDSWRITEVECTOR'
1253 endif
1254 C If we were writing to a tiled MDS file then we close it here
1255 if (fileIsOpen .AND. (.NOT. globalFile)) then
1256 close( dUnit )
1257 fileIsOpen = .FALSE.
1258 endif
1259 C Create meta-file for each tile file
1260 if (.NOT. globalFile) then
1261 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
1262 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
1263 write(metaFname(1:80),'(2a,i3.3,a,i3.3,a)')
1264 & fName(1:IL),'.',iG,'.',jG,'.meta'
1265 dimList(1,1) = nPx*nSx*narr
1266 dimList(2,1) = ((myXGlobalLo-1)/sNx + (bi-1))*narr + 1
1267 dimList(3,1) = ((myXGlobalLo-1)/sNx + bi )*narr
1268 dimList(1,2) = nPy*nSy
1269 dimList(2,2) = (myYGlobalLo-1)/sNy + bj
1270 dimList(3,2) = (myYGlobalLo-1)/sNy + bj
1271 dimList(1,3) = 1
1272 dimList(2,3) = 1
1273 dimList(3,3) = 1
1274 ndims=1
1275 call MDSWRITEMETA( metaFName, dataFName,
1276 & filePrec, ndims, dimList, irecord, myIter, mythid )
1277 endif
1278 C End of bi,bj loops
1279 ce enddo
1280 ce enddo
1281
1282 C If global file was opened then close it
1283 if (fileIsOpen .AND. globalFile) then
1284 close( dUnit )
1285 fileIsOpen = .FALSE.
1286 endif
1287
1288 C Create meta-file for global file
1289 if (globalFile) then
1290 write(metaFName(1:80),'(2a)') fName(1:IL),'.meta'
1291 dimList(1,1) = nPx*nSx*narr
1292 dimList(2,1) = 1
1293 dimList(3,1) = nPx*nSx*narr
1294 dimList(1,2) = nPy*nSy
1295 dimList(2,2) = 1
1296 dimList(3,2) = nPy*nSy
1297 dimList(1,3) = 1
1298 dimList(2,3) = 1
1299 dimList(3,3) = 1
1300 ndims=1
1301 call MDSWRITEMETA( metaFName, dataFName,
1302 & filePrec, ndims, dimList, irecord, myIter, mythid )
1303 endif
1304
1305 _END_MASTER( myThid )
1306 C ------------------------------------------------------------------
1307 return
1308 end
1309 C=======================================================================
1310
1311 C=======================================================================
1312 subroutine MDS_WRITE_RS_VEC( dUnit, irec, narr, arr, mythid )
1313 C IN:
1314 C dunit integer - 'Opened' I/O channel
1315 C irec integer - record number to write
1316 C narr integer - dimension off array "arr"
1317 C arr _RS - model tiled vector
1318 C mythid integer - thread id
1319 C
1320 C Created: 03/29/99 eckert@mit.edu + adcroft@mit.edu
1321
1322 implicit none
1323
1324 #include "EEPARAMS.h"
1325
1326 C Arguments
1327 integer dUnit
1328 integer irec
1329 integer narr
1330 integer mythid
1331 _RS arr(narr)
1332 C Local
1333 character*(max_len_mbuf) msgbuf
1334 C ------------------------------------------------------------------
1335 write(msgbuf,'(a,i9.8,2x,i9.8)')
1336 & ' MDS_WRITE_RS_VEC: irec = ',irec,narr
1337 call print_message( msgbuf, standardmessageunit,
1338 & SQUEEZE_RIGHT , mythid)
1339 write(dUnit,rec=irec) arr
1340 C ------------------------------------------------------------------
1341 return
1342 end
1343 C=======================================================================
1344
1345 C=======================================================================
1346 subroutine MDS_WRITE_RL_VEC( dUnit, irec, narr, arr, mythid )
1347 C IN:
1348 C dunit integer - 'Opened' I/O channel
1349 C irec integer - record number to write
1350 C narr integer - dimension off array "arr"
1351 C arr _RL - model tiled vector
1352 C mythid integer - thread id
1353 C
1354 C Created: 03/29/99 eckert@mit.edu + adcroft@mit.edu
1355
1356 implicit none
1357
1358 #include "EEPARAMS.h"
1359
1360 C Arguments
1361 integer dUnit
1362 integer irec
1363 integer narr
1364 integer mythid
1365 _RL arr(narr)
1366 C Local
1367 character*(max_len_mbuf) msgbuf
1368 C ------------------------------------------------------------------
1369 write(msgbuf,'(a,i9.8,2x,i9.8)')
1370 & ' MDS_WRITE_RL_VEC: irec = ',irec,narr
1371 call print_message( msgbuf, standardmessageunit,
1372 & SQUEEZE_RIGHT , mythid)
1373 write(dUnit,rec=irec) arr
1374 C ------------------------------------------------------------------
1375 return
1376 end
1377 C=======================================================================
1378
1379 C=======================================================================
1380 subroutine MDS_READ_RS_VEC( dUnit, irec, narr, arr, mythid )
1381 C IN:
1382 C dunit integer - 'Opened' I/O channel
1383 C irec integer - record number to write
1384 C narr integer - dimension off array "arr"
1385 C mythid integer - thread id
1386 C OUT:
1387 C arr _RS - model tiled vector
1388 C
1389 C Created: 03/29/99 eckert@mit.edu + adcroft@mit.edu
1390
1391 implicit none
1392
1393 #include "EEPARAMS.h"
1394
1395 C Arguments
1396 integer dUnit
1397 integer irec
1398 integer narr
1399 _RS arr(narr)
1400 integer mythid
1401 C Local
1402 character*(max_len_mbuf) msgbuf
1403 C ------------------------------------------------------------------
1404 write(msgbuf,'(a,i9.8,2x,i9.8)')
1405 & ' MDS_READ_RS_VEC: irec = ',irec,narr
1406 call print_message( msgbuf, standardmessageunit,
1407 & SQUEEZE_RIGHT , mythid)
1408 read(dUnit,rec=irec) arr
1409 C ------------------------------------------------------------------
1410 return
1411 end
1412 C=======================================================================
1413
1414 C=======================================================================
1415 subroutine MDS_READ_RL_VEC( dUnit, irec, narr, arr, mythid )
1416 C IN:
1417 C dunit integer - 'Opened' I/O channel
1418 C irec integer - record number to write
1419 C narr integer - dimension off array "arr"
1420 C mythid integer - thread id
1421 C OUT:
1422 C arr _RL - model tiled vector
1423 C
1424 C Created: 03/29/99 eckert@mit.edu + adcroft@mit.edu
1425
1426 implicit none
1427
1428 #include "EEPARAMS.h"
1429
1430 C Arguments
1431 integer dUnit
1432 integer irec
1433 integer narr
1434 _RL arr(narr)
1435 integer mythid
1436 C Local
1437 character*(max_len_mbuf) msgbuf
1438 C ------------------------------------------------------------------
1439 write(msgbuf,'(a,i9.8,2x,i9.8)')
1440 & ' MDS_READ_RL_VEC: irec = ',irec,narr
1441 call print_message( msgbuf, standardmessageunit,
1442 & SQUEEZE_RIGHT , mythid)
1443 read(dUnit,rec=irec) arr
1444 C ------------------------------------------------------------------
1445 return
1446 end
1447 C=======================================================================
1448
1449 #ifdef _BYTESWAPIO
1450 C=======================================================================
1451 subroutine MDS_BYTESWAPR4( n, arr )
1452 C IN:
1453 C n integer - Number of 4-byte words in arr
1454 C IN/OUT:
1455 C arr real*4 - Array declared as real*4(n)
1456 C
1457 C Created: 05/05/99 adcroft@mit.edu (This is an unfortunate hack!!)
1458
1459 implicit none
1460 C Arguments
1461 integer n
1462 character*(*) arr
1463 C Local
1464 integer i
1465 character*(1) cc
1466 C ------------------------------------------------------------------
1467 do i=1,4*n,4
1468 cc=arr(i:i)
1469 arr(i:i)=arr(i+3:i+3)
1470 arr(i+3:i+3)=cc
1471 cc=arr(i+1:i+1)
1472 arr(i+1:i+1)=arr(i+2:i+2)
1473 arr(i+2:i+2)=cc
1474 enddo
1475 C ------------------------------------------------------------------
1476 return
1477 end
1478 C=======================================================================
1479
1480 C=======================================================================
1481 subroutine MDS_BYTESWAPR8( n, arr )
1482 C IN:
1483 C n integer - Number of 8-byte words in arr
1484 C IN/OUT:
1485 C arr real*8 - Array declared as real*4(n)
1486 C
1487 C Created: 05/05/99 adcroft@mit.edu (This is an unfortunate hack!!)
1488
1489 implicit none
1490 C Arguments
1491 integer n
1492 character*(*) arr
1493 C Local
1494 integer i
1495 character*(1) cc
1496 C ------------------------------------------------------------------
1497 do i=1,8*n,8
1498 cc=arr(i:i)
1499 arr(i:i)=arr(i+7:i+7)
1500 arr(i+7:i+7)=cc
1501 cc=arr(i+1:i+1)
1502 arr(i+1:i+1)=arr(i+6:i+6)
1503 arr(i+6:i+6)=cc
1504 cc=arr(i+2:i+2)
1505 arr(i+2:i+2)=arr(i+5:i+5)
1506 arr(i+5:i+5)=cc
1507 cc=arr(i+3:i+3)
1508 arr(i+3:i+3)=arr(i+4:i+4)
1509 arr(i+4:i+4)=cc
1510 enddo
1511 C ------------------------------------------------------------------
1512 return
1513 end
1514 C=======================================================================
1515 #endif
1516

  ViewVC Help
Powered by ViewVC 1.1.22