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

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

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


Revision 1.1 - (hide annotations) (download)
Tue Sep 1 19:19:10 2009 UTC (14 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint65, checkpoint62, checkpoint63, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint61v, checkpoint61w, checkpoint61z, checkpoint61x, checkpoint61y, HEAD
old "vertical slice" MDS IO Routines (MDSREAD/WRITEFIELDX/YZ &_LOC):
 disabled (& STOP) if ALLOW_AUTODIFF is undef

1 jmc 1.1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_rw_field.F,v 1.3 2009/08/05 23:17:54 jmc Exp $
2     C $Name: $
3    
4     #include "MDSIO_OPTIONS.h"
5    
6     C-- File mdsio_rw_slice.F: old version of MDS_READ/WRITE_SEC_XZ/YZ S/R with
7     C fewer arguments (kept for backward compatibility): call new MDSIO S/R
8     C with fixed additional arguments
9     C-- Contents
10     C-- o MDSREADFIELDXZ
11     C-- o MDSREADFIELDYZ
12     C-- o MDSREADFIELDXZ_LOC
13     C-- o MDSREADFIELDYZ_LOC
14     C-- o MDSWRITEFIELDXZ
15     C-- o MDSWRITEFIELDYZ
16     C-- o MDSWRITEFIELDXZ_LOC
17     C-- o MDSWRITEFIELDYZ_LOC
18    
19     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
20    
21     SUBROUTINE MDSREADFIELDXZ(
22     I fName,
23     I filePrec,
24     I arrType,
25     I nNz,
26     | arr,
27     I irecord,
28     I myThid )
29    
30     C Arguments:
31     C
32     C fName string :: base name for file to written
33     C filePrec integer :: number of bits per word in file (32 or 64)
34     C arrType char(2) :: declaration of "arr": either "RS" or "RL"
35     C nNz integer :: size of third dimension: normally either 1 or Nr
36     C arr RS/RL :: array to write, arr(:,:,nNz,:,:)
37     C irecord integer :: record number to read
38     C myThid integer :: thread identifier
39     C
40     C Routine now calls MDS_READ_SEC_XZ, just a way to add extra arguments
41     C to the argument list.
42     C The 1rst new argument (useCurrentDir=.FALSE.) allows to read files from
43     C the "mdsioLocalDir" directory (if it is set).
44     C The 2nd new argument avoid argument array of undefined type (RL/RS).
45    
46     IMPLICIT NONE
47     C Global variables / COMMON blocks
48     #include "SIZE.h"
49     c #include "EEPARAMS.h"
50    
51     C Routine arguments
52     CHARACTER*(*) fName
53     INTEGER filePrec
54     CHARACTER*(2) arrType
55     INTEGER nNz
56     _RL arr(*)
57     INTEGER irecord
58     INTEGER myThid
59    
60     #ifdef ALLOW_AUTODIFF
61     C Local variables
62     _RL dummyRL(1)
63     _RS dummyRS(1)
64    
65     IF ( arrType.EQ.'RL' ) THEN
66     CALL MDS_READ_SEC_XZ(
67     I fName, filePrec, .FALSE., arrType, nNz,
68     O arr, dummyRS,
69     I irecord, myThid )
70     ELSE
71     CALL MDS_READ_SEC_XZ(
72     I fName, filePrec, .FALSE., arrType, nNz,
73     O dummyRL, arr,
74     I irecord, myThid )
75     ENDIF
76    
77     #else /* ALLOW_AUTODIFF */
78     STOP 'ABNORMAL END: S/R MDSREADFIELDXZ is retired'
79     #endif /* ALLOW_AUTODIFF */
80    
81     RETURN
82     END
83    
84     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
85    
86     SUBROUTINE MDSREADFIELDYZ(
87     I fName,
88     I filePrec,
89     I arrType,
90     I nNz,
91     | arr,
92     I irecord,
93     I myThid )
94    
95     C Arguments:
96     C
97     C fName string :: base name for file to written
98     C filePrec integer :: number of bits per word in file (32 or 64)
99     C arrType char(2) :: declaration of "arr": either "RS" or "RL"
100     C nNz integer :: size of third dimension: normally either 1 or Nr
101     C arr RS/RL :: array to write, arr(:,:,nNz,:,:)
102     C irecord integer :: record number to read
103     C myThid integer :: thread identifier
104     C
105     C Routine now calls MDS_READ_SEC_YZ, just a way to add extra arguments
106     C to the argument list.
107     C The 1rst new argument (useCurrentDir=.FALSE.) allows to read files from
108     C the "mdsioLocalDir" directory (if it is set).
109     C The 2nd new argument avoid argument array of undefined type (RL/RS).
110    
111     IMPLICIT NONE
112     C Global variables / COMMON blocks
113     #include "SIZE.h"
114     c #include "EEPARAMS.h"
115    
116     C Routine arguments
117     CHARACTER*(*) fName
118     INTEGER filePrec
119     CHARACTER*(2) arrType
120     INTEGER nNz
121     _RL arr(*)
122     INTEGER irecord
123     INTEGER myThid
124    
125     #ifdef ALLOW_AUTODIFF
126     C Local variables
127     _RL dummyRL(1)
128     _RS dummyRS(1)
129    
130     IF ( arrType.EQ.'RL' ) THEN
131     CALL MDS_READ_SEC_YZ(
132     I fName, filePrec, .FALSE., arrType, nNz,
133     O arr, dummyRS,
134     I irecord, myThid )
135     ELSE
136     CALL MDS_READ_SEC_YZ(
137     I fName, filePrec, .FALSE., arrType, nNz,
138     O dummyRL, arr,
139     I irecord, myThid )
140     ENDIF
141    
142     #else /* ALLOW_AUTODIFF */
143     STOP 'ABNORMAL END: S/R MDSREADFIELDYZ is retired'
144     #endif /* ALLOW_AUTODIFF */
145    
146     RETURN
147     END
148    
149     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
150    
151     SUBROUTINE MDSREADFIELDXZ_LOC(
152     I fName,
153     I filePrec,
154     I arrType,
155     I nNz,
156     | arr,
157     I irecord,
158     I myThid )
159    
160     C Arguments:
161     C
162     C fName string :: base name for file to written
163     C filePrec integer :: number of bits per word in file (32 or 64)
164     C arrType char(2) :: declaration of "arr": either "RS" or "RL"
165     C nNz integer :: size of third dimension: normally either 1 or Nr
166     C arr RS/RL :: array to write, arr(:,:,nNz,:,:)
167     C irecord integer :: record number to read
168     C myThid integer :: thread identifier
169     C
170     C Routine now calls MDS_READ_SEC_XZ, just a way to add extra arguments
171     C to the argument list.
172     C The 1rst new argument (useCurrentDir=.TRUE.) forces to ignore the
173     C "mdsioLocalDir" parameter and to always write to the current directory.
174     C The 2nd new argument avoid argument array of undefined type (RL/RS).
175    
176     IMPLICIT NONE
177     C Global variables / COMMON blocks
178     #include "SIZE.h"
179     c #include "EEPARAMS.h"
180    
181     C Routine arguments
182     CHARACTER*(*) fName
183     INTEGER filePrec
184     CHARACTER*(2) arrType
185     INTEGER nNz
186     _RL arr(*)
187     INTEGER irecord
188     INTEGER myThid
189    
190     #ifdef ALLOW_AUTODIFF
191     C Local variables
192     _RL dummyRL(1)
193     _RS dummyRS(1)
194    
195     IF ( arrType.EQ.'RL' ) THEN
196     CALL MDS_READ_SEC_XZ(
197     I fName, filePrec, .TRUE., arrType, nNz,
198     O arr, dummyRS,
199     I irecord, myThid )
200     ELSE
201     CALL MDS_READ_SEC_XZ(
202     I fName, filePrec, .TRUE., arrType, nNz,
203     O dummyRL, arr,
204     I irecord, myThid )
205     ENDIF
206    
207     #else /* ALLOW_AUTODIFF */
208     STOP 'ABNORMAL END: S/R MDSREADFIELDXZ_LOC is empty'
209     #endif /* ALLOW_AUTODIFF */
210    
211     RETURN
212     END
213    
214     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
215    
216     SUBROUTINE MDSREADFIELDYZ_LOC(
217     I fName,
218     I filePrec,
219     I arrType,
220     I nNz,
221     | arr,
222     I irecord,
223     I myThid )
224    
225     C Arguments:
226     C
227     C fName string :: base name for file to written
228     C filePrec integer :: number of bits per word in file (32 or 64)
229     C arrType char(2) :: declaration of "arr": either "RS" or "RL"
230     C nNz integer :: size of third dimension: normally either 1 or Nr
231     C arr RS/RL :: array to write, arr(:,:,nNz,:,:)
232     C irecord integer :: record number to read
233     C myThid integer :: thread identifier
234     C
235     C Routine now calls MDS_READ_SEC_YZ, just a way to add extra arguments
236     C to the argument list.
237     C The 1rst new argument (useCurrentDir=.TRUE.) forces to ignore the
238     C "mdsioLocalDir" parameter and to always write to the current directory.
239     C The 2nd new argument avoid argument array of undefined type (RL/RS).
240    
241     IMPLICIT NONE
242     C Global variables / COMMON blocks
243     #include "SIZE.h"
244     c #include "EEPARAMS.h"
245    
246     C Routine arguments
247     CHARACTER*(*) fName
248     INTEGER filePrec
249     CHARACTER*(2) arrType
250     INTEGER nNz
251     _RL arr(*)
252     INTEGER irecord
253     INTEGER myThid
254    
255     #ifdef ALLOW_AUTODIFF
256     C Local variables
257     _RL dummyRL(1)
258     _RS dummyRS(1)
259    
260     IF ( arrType.EQ.'RL' ) THEN
261     CALL MDS_READ_SEC_YZ(
262     I fName, filePrec, .TRUE., arrType, nNz,
263     O arr, dummyRS,
264     I irecord, myThid )
265     ELSE
266     CALL MDS_READ_SEC_YZ(
267     I fName, filePrec, .TRUE., arrType, nNz,
268     O dummyRL, arr,
269     I irecord, myThid )
270     ENDIF
271    
272     #else /* ALLOW_AUTODIFF */
273     STOP 'ABNORMAL END: S/R MDSREADFIELDYZ_LOC is empty'
274     #endif /* ALLOW_AUTODIFF */
275    
276     RETURN
277     END
278    
279     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
280    
281     SUBROUTINE MDSWRITEFIELDXZ(
282     I fName,
283     I filePrec,
284     I globalFile,
285     I arrType,
286     I nNz,
287     I arr,
288     I irecord,
289     I myIter,
290     I myThid )
291    
292     C Arguments:
293     C
294     C fName string :: base name for file to write
295     C filePrec integer :: number of bits per word in file (32 or 64)
296     C globalFile logical :: selects between writing a global or tiled file
297     C arrType char(2) :: declaration of "arr": either "RS" or "RL"
298     C nNz integer :: size of third dimension: normally either 1 or Nr
299     C arr RS/RL :: array to write, arr(:,:,nNzdim,:,:)
300     C irecord integer :: record number to write
301     C myIter integer :: time step number
302     C myThid integer :: thread identifier
303     C
304     C Routine now calls MDS_WRITE_REC_XZ, just a way to add extra arguments
305     C to the argument list.
306     C The 1rst new argument (useCurrentDir=.FALSE.) allows to write files to
307     C the "mdsioLocalDir" directory (if it is set).
308     C The 2nd new argument avoid argument array of undefined type (RL/RS).
309    
310     IMPLICIT NONE
311     C Global variables / common blocks
312     #include "SIZE.h"
313     c #include "EEPARAMS.h"
314    
315     C Routine arguments
316     CHARACTER*(*) fName
317     INTEGER filePrec
318     LOGICAL globalFile
319     CHARACTER*(2) arrType
320     INTEGER nNz
321     _RL arr(*)
322     INTEGER irecord
323     INTEGER myIter
324     INTEGER myThid
325    
326     #ifdef ALLOW_AUTODIFF
327     C Local variables
328     _RL dummyRL(1)
329     _RS dummyRS(1)
330    
331     IF ( arrType.EQ.'RL' ) THEN
332     CALL MDS_WRITE_SEC_XZ(
333     I fName, filePrec, globalFile, .FALSE.,
334     I arrType, nNz, arr, dummyRS,
335     I irecord, myIter, myThid )
336     ELSE
337     CALL MDS_WRITE_SEC_XZ(
338     I fName, filePrec, globalFile, .FALSE.,
339     I arrType, nNz, dummyRL, arr,
340     I irecord, myIter, myThid )
341     ENDIF
342    
343     #else /* ALLOW_AUTODIFF */
344     STOP 'ABNORMAL END: S/R MDSWRITEFIELDXZ is retired'
345     #endif /* ALLOW_AUTODIFF */
346    
347     RETURN
348     END
349    
350     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
351    
352     SUBROUTINE MDSWRITEFIELDYZ(
353     I fName,
354     I filePrec,
355     I globalFile,
356     I arrType,
357     I nNz,
358     I arr,
359     I irecord,
360     I myIter,
361     I myThid )
362    
363     C Arguments:
364     C
365     C fName string :: base name for file to write
366     C filePrec integer :: number of bits per word in file (32 or 64)
367     C globalFile logical :: selects between writing a global or tiled file
368     C arrType char(2) :: declaration of "arr": either "RS" or "RL"
369     C nNz integer :: size of third dimension: normally either 1 or Nr
370     C arr RS/RL :: array to write, arr(:,:,nNzdim,:,:)
371     C irecord integer :: record number to write
372     C myIter integer :: time step number
373     C myThid integer :: thread identifier
374     C
375     C Routine now calls MDS_WRITE_REC_YZ, just a way to add extra arguments
376     C to the argument list.
377     C The 1rst new argument (useCurrentDir=.FALSE.) allows to write files to
378     C the "mdsioLocalDir" directory (if it is set).
379     C The 2nd new argument avoid argument array of undefined type (RL/RS).
380    
381     IMPLICIT NONE
382     C Global variables / common blocks
383     #include "SIZE.h"
384     c #include "EEPARAMS.h"
385    
386     C Routine arguments
387     CHARACTER*(*) fName
388     INTEGER filePrec
389     LOGICAL globalFile
390     CHARACTER*(2) arrType
391     INTEGER nNz
392     _RL arr(*)
393     INTEGER irecord
394     INTEGER myIter
395     INTEGER myThid
396    
397     #ifdef ALLOW_AUTODIFF
398     C Local variables
399     _RL dummyRL(1)
400     _RS dummyRS(1)
401    
402     IF ( arrType.EQ.'RL' ) THEN
403     CALL MDS_WRITE_SEC_YZ(
404     I fName, filePrec, globalFile, .FALSE.,
405     I arrType, nNz, arr, dummyRS,
406     I irecord, myIter, myThid )
407     ELSE
408     CALL MDS_WRITE_SEC_YZ(
409     I fName, filePrec, globalFile, .FALSE.,
410     I arrType, nNz, dummyRL, arr,
411     I irecord, myIter, myThid )
412     ENDIF
413    
414     #else /* ALLOW_AUTODIFF */
415     STOP 'ABNORMAL END: S/R MDSWRITEFIELDYZ is retired'
416     #endif /* ALLOW_AUTODIFF */
417    
418     RETURN
419     END
420    
421     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
422    
423     SUBROUTINE MDSWRITEFIELDXZ_LOC(
424     I fName,
425     I filePrec,
426     I globalFile,
427     I arrType,
428     I nNz,
429     I arr,
430     I irecord,
431     I myIter,
432     I myThid )
433    
434     C Arguments:
435     C
436     C fName string :: base name for file to write
437     C filePrec integer :: number of bits per word in file (32 or 64)
438     C globalFile logical :: selects between writing a global or tiled file
439     C arrType char(2) :: declaration of "arr": either "RS" or "RL"
440     C nNz integer :: size of third dimension: normally either 1 or Nr
441     C arr RS/RL :: array to write, arr(:,:,nNzdim,:,:)
442     C irecord integer :: record number to write
443     C myIter integer :: time step number
444     C myThid integer :: thread identifier
445     C
446     C Routine now calls MDS_WRITE_REC_XZ, just a way to add extra arguments
447     C to the argument list.
448     C The 1rst new argument (useCurrentDir=.TRUE.) forces to ignore the
449     C "mdsioLocalDir" parameter and to always write to the current directory.
450     C The 2nd new argument avoid argument array of undefined type (RL/RS).
451    
452     IMPLICIT NONE
453     C Global variables / common blocks
454     #include "SIZE.h"
455     c #include "EEPARAMS.h"
456    
457     C Routine arguments
458     CHARACTER*(*) fName
459     INTEGER filePrec
460     LOGICAL globalFile
461     CHARACTER*(2) arrType
462     INTEGER nNz
463     _RL arr(*)
464     INTEGER irecord
465     INTEGER myIter
466     INTEGER myThid
467    
468     #ifdef ALLOW_AUTODIFF
469     C Local variables
470     _RL dummyRL(1)
471     _RS dummyRS(1)
472    
473     IF ( arrType.EQ.'RL' ) THEN
474     CALL MDS_WRITE_SEC_XZ(
475     I fName, filePrec, globalFile, .TRUE.,
476     I arrType, nNz, arr, dummyRS,
477     I irecord, myIter, myThid )
478     ELSE
479     CALL MDS_WRITE_SEC_XZ(
480     I fName, filePrec, globalFile, .TRUE.,
481     I arrType, nNz, dummyRL, arr,
482     I irecord, myIter, myThid )
483     ENDIF
484    
485     #else /* ALLOW_AUTODIFF */
486     STOP 'ABNORMAL END: S/R MDSWRITEFIELDXZ_LOC is empty'
487     #endif /* ALLOW_AUTODIFF */
488    
489     RETURN
490     END
491    
492     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
493    
494     SUBROUTINE MDSWRITEFIELDYZ_LOC(
495     I fName,
496     I filePrec,
497     I globalFile,
498     I arrType,
499     I nNz,
500     I arr,
501     I irecord,
502     I myIter,
503     I myThid )
504    
505     C Arguments:
506     C
507     C fName string :: base name for file to write
508     C filePrec integer :: number of bits per word in file (32 or 64)
509     C globalFile logical :: selects between writing a global or tiled file
510     C arrType char(2) :: declaration of "arr": either "RS" or "RL"
511     C nNz integer :: size of third dimension: normally either 1 or Nr
512     C arr RS/RL :: array to write, arr(:,:,nNzdim,:,:)
513     C irecord integer :: record number to write
514     C myIter integer :: time step number
515     C myThid integer :: thread identifier
516     C
517     C Routine now calls MDS_WRITE_REC_YZ, just a way to add extra arguments
518     C to the argument list.
519     C The 1rst new argument (useCurrentDir=.TRUE.) forces to ignore the
520     C "mdsioLocalDir" parameter and to always write to the current directory.
521     C The 2nd new argument avoid argument array of undefined type (RL/RS).
522    
523     IMPLICIT NONE
524     C Global variables / common blocks
525     #include "SIZE.h"
526     c #include "EEPARAMS.h"
527    
528     C Routine arguments
529     CHARACTER*(*) fName
530     INTEGER filePrec
531     LOGICAL globalFile
532     CHARACTER*(2) arrType
533     INTEGER nNz
534     _RL arr(*)
535     INTEGER irecord
536     INTEGER myIter
537     INTEGER myThid
538    
539     #ifdef ALLOW_AUTODIFF
540     C Local variables
541     _RL dummyRL(1)
542     _RS dummyRS(1)
543    
544     IF ( arrType.EQ.'RL' ) THEN
545     CALL MDS_WRITE_SEC_YZ(
546     I fName, filePrec, globalFile, .TRUE.,
547     I arrType, nNz, arr, dummyRS,
548     I irecord, myIter, myThid )
549     ELSE
550     CALL MDS_WRITE_SEC_YZ(
551     I fName, filePrec, globalFile, .TRUE.,
552     I arrType, nNz, dummyRL, arr,
553     I irecord, myIter, myThid )
554     ENDIF
555    
556     #else /* ALLOW_AUTODIFF */
557     STOP 'ABNORMAL END: S/R MDSWRITEFIELDYZ_LOC is empty'
558     #endif /* ALLOW_AUTODIFF */
559    
560     RETURN
561     END

  ViewVC Help
Powered by ViewVC 1.1.22