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

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

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


Revision 1.7 - (hide annotations) (download)
Fri Aug 19 18:01:29 2005 UTC (18 years, 9 months ago) by heimbach
Branch: MAIN
Changes since 1.6: +474 -6 lines
Fixed [data,meta]FName initialization.

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

  ViewVC Help
Powered by ViewVC 1.1.22