/[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.6 - (hide annotations) (download)
Thu Oct 14 18:43:39 2004 UTC (19 years, 8 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint57m_post, checkpoint57g_pre, checkpoint57b_post, checkpoint57g_post, checkpoint56b_post, checkpoint57d_post, checkpoint57i_post, checkpoint57, checkpoint56, checkpoint57n_post, checkpoint55i_post, checkpoint57l_post, checkpoint57f_post, checkpoint57a_post, checkpoint57h_pre, checkpoint57h_post, checkpoint57c_post, checkpoint57c_pre, checkpoint55j_post, checkpoint55h_post, checkpoint57e_post, checkpoint57p_post, eckpoint57e_pre, checkpoint56a_post, checkpoint57h_done, checkpoint57j_post, checkpoint57f_pre, checkpoint56c_post, checkpoint57a_pre, checkpoint57o_post, checkpoint57k_post
Changes since 1.5: +1 -5 lines
Remove STOP in _GL for adxx, weights, etc.

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

  ViewVC Help
Powered by ViewVC 1.1.22