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

Annotation of /MITgcm/eesupp/src/dfile.F

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


Revision 1.9 - (hide annotations) (download)
Mon May 24 14:31:23 1999 UTC (25 years, 1 month ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint23, checkpoint24
Changes since 1.8: +15 -4 lines
Added IMPLICIT NONEs (Again! Is someone deleting them?)
Changed instances of NAME= to FILE= in OPEN statements.

1 adcroft 1.9 C $Header: /u/gcmpack/models/MITgcmUV/eesupp/src/dfile.F,v 1.8 1998/10/28 03:11:33 cnh Exp $
2 cnh 1.1
3     #include "CPP_EEOPTIONS.h"
4    
5     C-- File dfile.F: Routines that handle actual I/O
6     C-- to model "dump" files.
7     C-- These low-level routines could be replaced
8     C-- by platform/environment specific C or
9     C-- MPI-2 routines one day! In some situations the
10     C-- functionality of these low-level routines is
11     C-- encompassed by the data handling package. For
12     C-- example netCDF provides primitive that are
13     C-- higher level
14     C-- Contents
15     C-- DFILE_CLOSE - Closes dump file
16     C-- DFILE_INIT - Initialisation procedure for subsequent DFILE
17     C data-structures. Only called once per run.
18     C-- DFILE_OPEN - Opens dump file
19     C-- DFILE_READ_R8 - Reads from a dump file
20     C-- DFILE_READ_R4 - Reads from a dump file
21     C-- DFILE_SET_RO - Sets new connections to be read-only
22     C-- DFILE_SET_RW - Sets new connections to be read-write
23     C-- DFILE_SET_STOP_ON_ERROR - Sets new connections to STOP on error
24     C-- DFILE_SET_CONT_ON_ERROR - Sets new connections to continue
25     C on error
26     C-- DFILE_WRITE_R4 - Writes to a dump file
27     C-- DFILE_WRITE_R8 - Writes to a dump file
28     C
29     C Notes:
30     C ======
31     C The default behaviour is for the model to stop if an
32     C input errors occur but to continue if output errors occur.
33     C However, this policy is not enforced in these low-level routines.
34     C Instead these routines are coded to allow either continue
35     C on error or stop on error. Which action is taken
36     C is controlled via a mode flag which is set from the higher
37     C level calls to these routines. A mode flag is also used to
38     C control whether the DFILE_OPEN routine opens a file in
39     C read-write or read-only mode. On some systems this is necessary
40     C as the default is read-write and will fail for read-only files or
41 cnh 1.8 C file systems. Other systems do not support the OPEN(...='READ_ONLY')
42 cnh 1.1 C so this feature may need to be switched on or off as appropriate.
43     C The DFILE_SET routines provide this mechanism. They work by setting
44     C a "context" flag which is applied to IO ahndles when the DFILE_OPEN
45     C call is made. IO handles that are already open are not affected by
46     C subsequent calls to DFILE_SET routines.
47    
48     SUBROUTINE DFILE_CLOSE(
49     I fileHandle, myThid)
50     C /==========================================================\
51     C | SUBROUTINE DFILE_CLOSE |
52     C | o Close model "dump" file. |
53     C |==========================================================|
54     C | Controlling routine for doing actual I/O operations. |
55     C | Close the file referred to by handle fielHandle. |
56     C \==========================================================/
57 adcroft 1.9 IMPLICIT NONE
58 cnh 1.1
59     C == Global variables ==
60     #include "SIZE.h"
61     #include "EEPARAMS.h"
62     #include "EESUPPORT.h"
63     #include "DFILE.h"
64    
65     C == Routine arguments ==
66     INTEGER myThid
67     INTEGER fileHandle
68    
69     C == Local variables ==
70     C msgBuf - Error message buffer
71     C I - Work variables
72     C dUnit Data unit
73     C mUnit Meta data unit
74     C eMode Error mode
75     CHARACTER*(MAX_LEN_MBUF) msgBuf
76     INTEGER I
77     INTEGER dUnit
78     INTEGER mUnit
79     INTEGER eMode
80    
81     I = fileHandle
82    
83     C-- Check that the fileHandle passed in is open
84     IF ( unitStatus(I,myThid) .NE. busyUnit ) GOTO 1000
85    
86     unitStatus(I,myThid) = freeUnit
87     dUnit = dUnitNumber(I,myThid)
88     mUnit = mUnitNumber(I,myThid)
89     eMode = errorMode(I,myThid)
90     CLOSE(dUnit,ERR=999)
91     CLOSE(mUnit,ERR=999)
92    
93     1000 CONTINUE
94     RETURN
95     999 CONTINUE
96     WRITE(msgBuf,'(A)') ' S/R DFILE_CLOSE'
97     CALL PRINT_ERROR( msgBuf , 1)
98     WRITE(msgBuf,'(A,A)') ' Thread ', myThid,' Close file failed'
99     CALL PRINT_ERROR( msgBuf , 1)
100     IF ( eMode .EQ. errorModeSTOP ) THEN
101     STOP 'ABNORMAL END: S/R DFILE_CLOSE'
102     ENDIF
103     ioErrorCount(myThid) = ioErrorCount(myThid)+1
104     GOTO 1000
105    
106     END
107    
108     SUBROUTINE DFILE_INIT
109     C /==========================================================\
110     C | SUBROUTINE DFILE_INIT |
111     C | o Model "dump" file initialisation procedure |
112     C |==========================================================|
113     C | Initalises data structures used by MITgcmUV "dump file" |
114     C | procedures. |
115     C | As coded this routine sets the unit number used for |
116     C | dump file IO. Two numbers are used one for data and one |
117     C | for meta data. It is possible to use more unit numbers |
118     C | and/or have different unit numbers per thread. This is |
119     C | not done here. |
120     C \==========================================================/
121 adcroft 1.9 IMPLICIT NONE
122 cnh 1.1
123     C == Global variables ==
124     #include "SIZE.h"
125     #include "EEPARAMS.h"
126     #include "DFILE.h"
127    
128     C == Local variables ==
129     C I, J - Loop counters
130     INTEGER I, J
131    
132     DO j=1,MAX_NO_THREADS
133     DO i=1,ioUnitsPerThread
134     mUnitNumber(i,j) = 20+i*2-1
135     dUnitNumber(i,j) = 20+i*2
136     unitStatus (i,j) = freeUnit
137     metaDataStatus(i,j) = metaDataNotWritten
138     ENDDO
139     ENDDO
140    
141     C-- Set initial access and error modes
142     CALL DFILE_SET_RW
143     CALL DFILE_SET_STOP_ON_ERROR
144    
145     RETURN
146     END
147    
148     SUBROUTINE DFILE_OPEN(
149     I fNam, fNamMeta, myThid,
150     O fileHandle)
151     C /==========================================================\
152     C | SUBROUTINE DFILE_OPEN |
153     C | o Open model "dump" file. |
154     C |==========================================================|
155     C | Controlling routine for doing actual I/O operations. |
156     C | Routine returns a handle to the caller that can be used |
157     C | in subsequent read and write operations. |
158     C \==========================================================/
159 adcroft 1.9 IMPLICIT NONE
160 cnh 1.1
161     C == Global variables ==
162     #include "SIZE.h"
163     #include "EEPARAMS.h"
164     #include "EESUPPORT.h"
165     #include "DFILE.h"
166    
167     INTEGER IFNBLNK
168     EXTERNAL IFNBLNK
169     INTEGER ILNBLNK
170     EXTERNAL ILNBLNK
171    
172     C == Routine arguments ==
173     CHARACTER*(*) fNam
174     CHARACTER*(*) fNamMeta
175     INTEGER myThid
176     INTEGER fileHandle
177    
178     C == Local variables ==
179     C msgBuf - Error message buffer
180     C dUnit - Unit number for data
181     C mUnit - Unit number for meta data
182     C eMode - Error mode
183     C aMode - Access mode
184     C I - Loop counters
185     INTEGER dUnit
186     INTEGER mUnit
187     INTEGER eMode
188     INTEGER aMode
189     CHARACTER*(MAX_LEN_MBUF) msgBuf
190     INTEGER I
191     INTEGER i1Lo, i1Hi, i2Lo, i2Hi
192    
193     C-- Get statistics on names
194     i1Lo = IFNBLNK(fNam)
195     i1Hi = ILNBLNK(fNam)
196     i2Lo = IFNBLNK(fNamMeta)
197     i2Hi = ILNBLNK(fNamMeta)
198    
199     C-- Choose a free I/O unit
200     fileHandle = -1
201     dUnit = 0
202     DO I=1, ioUnitsPerThread
203     IF ( unitStatus(I,myThid) .EQ. freeUnit ) THEN
204     dUnit = dUnitNumber(I,myThid)
205     mUnit = mUnitNumber(I,myThid)
206     unitStatus(I,myThid) = busyUnit
207     errorMode(I,myThid) = theErrorMode
208     accessMode(I,myThid) = theAccessMode
209     eMode = theErrorMode
210     aMode = theAccessMode
211     fileHandle = I
212     GOTO 10
213     ENDIF
214     ENDDO
215     10 CONTINUE
216     IF ( dUnit .EQ. 0 ) GOTO 999
217    
218     C-- Remove previous meta information if there was any
219     metaDataStatus(fileHandle,myThid) = metaDataWritten
220     IF ( fNamMeta .NE. ' ' ) THEN
221     IF ( aMode .EQ. accessModeRW ) THEN
222 adcroft 1.9 OPEN(UNIT=mUnit,FILE=fNamMeta(i2Lo:i2Hi),
223 cnh 1.8 & STATUS='UNKNOWN',ERR=899)
224 cnh 1.1 CLOSE(mUnit,ERR=899)
225 adcroft 1.9 OPEN(UNIT=mUnit,FILE=fNamMeta(i2Lo:i2Hi),
226 cnh 1.8 & STATUS='UNKNOWN',ERR=899)
227 cnh 1.6 metaDataStatus(fileHandle,myThid) = metaDataNotWritten
228     nameOfMFile(fileHandle,myThid) = fNamMeta(i2Lo:i2Hi)
229 cnh 1.1 ENDIF
230     ENDIF
231    
232     C-- Open data file
233     nameOfDFile(fileHandle,myThid) = fNam(i1Lo:i1Hi)
234 adcroft 1.9 OPEN(UNIT=dUnit,FILE=fNam(i1Lo:i1Hi),STATUS='UNKNOWN', ERR=799,
235 cnh 1.1 & FORM='UNFORMATTED',ACCESS='SEQUENTIAL')
236    
237    
238     1000 CONTINUE
239     RETURN
240    
241     999 CONTINUE
242     WRITE(msgBuf,'(A)') ' S/R DFILE_OPEN '
243     CALL PRINT_ERROR( msgBuf , 1)
244     WRITE(msgBuf,'(A,A)') ' Too many open files '
245     CALL PRINT_ERROR( msgBuf , 1)
246 cnh 1.8 WRITE(msgBuf,'(A,I4,A,A)') ' Thread ', myThid,' trying to open ',
247 cnh 1.1 & fNam(i1Lo:i1Hi)
248     CALL PRINT_ERROR( msgBuf , 1)
249     IF ( eMode .EQ. errorModeSTOP ) THEN
250     STOP 'ABNORMAL END: S/R DFILE_OPEN '
251     ENDIF
252     ioErrorCount(myThid) = ioErrorCount(myThid) + 1
253     GOTO 1000
254    
255     899 CONTINUE
256     WRITE(msgBuf,'(A)') ' S/R DFILE_OPEN '
257     CALL PRINT_ERROR( msgBuf , 1)
258 cnh 1.8 WRITE(msgBuf,'(A,I4,A,A)') ' Thread ',myThid,' failed open for ',
259 cnh 1.1 & fNamMeta(i2Lo:i2Hi)
260     CALL PRINT_ERROR( msgBuf , 1)
261     IF ( eMode .EQ. errorModeSTOP ) THEN
262     STOP 'ABNORMAL END: S/R DFILE_OPEN '
263     ENDIF
264     ioErrorCount(myThid) = ioErrorCount(myThid) + 1
265     GOTO 1000
266    
267     799 CONTINUE
268     WRITE(msgBuf,'(A)') ' S/R DFILE_OPEN '
269     CALL PRINT_ERROR( msgBuf , 1)
270 cnh 1.8 WRITE(msgBuf,'(A,I4,A,A)') ' Thread ',myThid,' failed open for ',
271 cnh 1.1 & fNam(i1Lo:i1Hi)
272     CALL PRINT_ERROR( msgBuf , 1)
273     IF ( eMode .EQ. errorModeSTOP ) THEN
274     STOP 'ABNORMAL END: S/R DFILE_OPEN '
275     ENDIF
276     ioErrorCount(myThid) = ioErrorCount(myThid) + 1
277     GOTO 1000
278    
279     END
280    
281     SUBROUTINE DFILE_READ_R4(
282     I lBuffer,
283     I fileHandle, myThid)
284     C /==========================================================\
285     C | SUBROUTINE DFILE_READ_R4 |
286     C | o Read record(s) from model dump file. |
287     C |==========================================================|
288     C | Controlling routine for doing actual I/O operations. |
289     C | Routine reads data from binary files formatted for |
290     C | model input. Could do elaborate reads from netCDF or |
291     C | using regular C I/O primitives. For now we use plain |
292     C | F77. |
293     C \==========================================================/
294 adcroft 1.9 IMPLICIT NONE
295 cnh 1.1
296     C == Global variables ==
297     #include "SIZE.h"
298     #include "EEPARAMS.h"
299     #include "DFILE.h"
300    
301     INTEGER IFNBLNK
302     EXTERNAL IFNBLNK
303     INTEGER ILNBLNK
304     EXTERNAL ILNBLNK
305    
306     C == Routine arguments ==
307     C lBuffer - Length of buffer data will be read into
308     C fileHandle - Handle of already opened file
309     C myThid - Thread id calling this routine
310     INTEGER lBuffer
311     INTEGER fileHandle
312     INTEGER myThid
313    
314     C == Local variables ==
315     C ioUnit - Unit number associated with fileHandle
316     C I - Loop counter
317     C eMode - fileHandles error mode
318     CHARACTER*(MAX_LEN_FNAM) fNam
319     CHARACTER*(MAX_LEN_MBUF) msgBuf
320     INTEGER ioUnit
321     INTEGER I, iLo, iHi
322     INTEGER eMode
323    
324     C-- Get error mode
325     eMode = errorMode(fileHandle,myThid)
326    
327     C-- Check that file is active
328     IF ( unitStatus(fileHandle,myThid) .NE. busyUnit ) GOTO 999
329    
330     fNam = nameOfDFile(fileHandle,myThid)
331     iLo = IFNBLNK(fNam)
332     iHi = ILNBLNK(fNam)
333     ioUnit = dUnitNumber(fileHandle,myThid)
334 adcroft 1.5 READ(ioUnit,ERR=899) (ioBuf_R4(I),I=1,lBuffer)
335 cnh 1.1
336    
337     1000 CONTINUE
338     RETURN
339    
340     999 CONTINUE
341     WRITE(msgBuf,'(A)') ' S/R DFILE_READ_R4 '
342     CALL PRINT_ERROR( msgBuf , 1)
343     WRITE(msgBuf,'(A,I4,A)') ' Thread ', myThid, ' unit not open '
344     CALL PRINT_ERROR( msgBuf , 1)
345     IF ( eMode .EQ. errorModeSTOP ) THEN
346     STOP 'ABNORMAL END: S/R DFILE_READ_R4'
347     ENDIF
348     ioErrorCount(myThid) = ioErrorCount(myThid) + 1
349     GOTO 1000
350    
351     899 CONTINUE
352     WRITE(msgBuf,'(A)') ' S/R DFILE_READ_R4 '
353     CALL PRINT_ERROR( msgBuf , 1)
354 cnh 1.8 WRITE(msgBuf,'(A,I4,A)') ' Thread ', myThid,' error reading file'
355 cnh 1.3 CALL PRINT_ERROR( msgBuf , 1)
356     WRITE(msgBuf,'(A,A,A)') ' "', fNam(iLo:iHi),'"'
357 cnh 1.1 CALL PRINT_ERROR( msgBuf , 1)
358     IF ( eMode .EQ. errorModeSTOP ) THEN
359     STOP 'ABNORMAL END: S/R DFILE_READ_R4'
360     ENDIF
361     ioErrorCount(myThid) = ioErrorCount(myThid) + 1
362     GOTO 1000
363    
364     END
365     SUBROUTINE DFILE_READ_R8(
366     I lBuffer,
367     I fileHandle, myThid)
368     C /==========================================================\
369     C | SUBROUTINE DFILE_READ_R8 |
370     C | o Read record(s) from model dump file. |
371     C |==========================================================|
372     C | Controlling routine for doing actual I/O operations. |
373     C | Routine reads data from binary files formatted for |
374     C | model input. Could do elaborate reads from netCDF or |
375     C | using regular C I/O primitives. For now we use plain |
376     C | F77. |
377     C \==========================================================/
378 adcroft 1.9 IMPLICIT NONE
379 cnh 1.1
380     C == Global variables ==
381     #include "SIZE.h"
382     #include "EEPARAMS.h"
383     #include "DFILE.h"
384    
385     INTEGER IFNBLNK
386     EXTERNAL IFNBLNK
387     INTEGER ILNBLNK
388     EXTERNAL ILNBLNK
389    
390     C == Routine arguments ==
391     C lBuffer - Length of buffer data will be read into
392     C fileHandle - Handle of already opened file
393     C myThid - Thread id calling this routine
394     INTEGER lBuffer
395     INTEGER fileHandle
396     INTEGER myThid
397    
398     C == Local variables ==
399     C ioUnit - Unit number associated with fileHandle
400     C I - Loop counter
401     C eMode - fileHandles error mode
402     CHARACTER*(MAX_LEN_FNAM) fNam
403     CHARACTER*(MAX_LEN_MBUF) msgBuf
404     INTEGER ioUnit
405     INTEGER I, iLo, iHi
406     INTEGER eMode
407    
408     C-- Get error mode
409     eMode = errorMode(fileHandle,myThid)
410    
411     C-- Check that file is active
412     IF ( unitStatus(fileHandle,myThid) .NE. busyUnit ) GOTO 999
413    
414     fNam = nameOfDFile(fileHandle,myThid)
415     iLo = IFNBLNK(fNam)
416     iHi = ILNBLNK(fNam)
417     ioUnit = dUnitNumber(fileHandle,myThid)
418     READ(ioUnit,ERR=899) (ioBuf_R8(I),I=1,lBuffer)
419    
420    
421     1000 CONTINUE
422     RETURN
423    
424     999 CONTINUE
425     WRITE(msgBuf,'(A)') ' S/R DFILE_READ_R8 '
426     CALL PRINT_ERROR( msgBuf , 1)
427     WRITE(msgBuf,'(A,I4,A)') ' Thread ', myThid, ' unit not open '
428     CALL PRINT_ERROR( msgBuf , 1)
429     IF ( eMode .EQ. errorModeSTOP ) THEN
430     STOP 'ABNORMAL END: S/R DFILE_READ_R8'
431     ENDIF
432     ioErrorCount(myThid) = ioErrorCount(myThid) + 1
433     GOTO 1000
434    
435     899 CONTINUE
436     WRITE(msgBuf,'(A)') ' S/R DFILE_READ_R8 '
437     CALL PRINT_ERROR( msgBuf , 1)
438 cnh 1.8 WRITE(msgBuf,'(A,I4,A)') ' Thread ', myThid,' error reading file'
439 cnh 1.3 CALL PRINT_ERROR( msgBuf , 1)
440     WRITE(msgBuf,'(A,A,A)') ' "', fNam(iLo:iHi),'"'
441 cnh 1.1 CALL PRINT_ERROR( msgBuf , 1)
442     IF ( eMode .EQ. errorModeSTOP ) THEN
443     STOP 'ABNORMAL END: S/R DFILE_READ_R8'
444     ENDIF
445     ioErrorCount(myThid) = ioErrorCount(myThid) + 1
446     GOTO 1000
447    
448     END
449    
450     SUBROUTINE DFILE_SET_RO
451     C /==========================================================\
452     C | SUBROUTINE DFILE_SET_RO |
453     C | o Sets new connections to be read-only. |
454     C \==========================================================/
455 adcroft 1.9 IMPLICIT NONE
456 cnh 1.1
457     C == Global variables ==
458     #include "SIZE.h"
459     #include "EEPARAMS.h"
460     #include "DFILE.h"
461    
462     theAccessMode = accessModeRO
463    
464     RETURN
465     END
466    
467     SUBROUTINE DFILE_SET_RW
468     C /==========================================================\
469     C | SUBROUTINE DFILE_SET_RW |
470     C | o Sets new connections to be read-write |
471     C \==========================================================/
472 adcroft 1.9 IMPLICIT NONE
473 cnh 1.1
474     C == Global variables ==
475     #include "SIZE.h"
476     #include "EEPARAMS.h"
477     #include "DFILE.h"
478    
479     theAccessMode = accessModeRW
480    
481     RETURN
482     END
483    
484     SUBROUTINE DFILE_SET_STOP_ON_ERROR
485     C /==========================================================\
486     C | SUBROUTINE DFILE_SET_STOP_ON_ERROR |
487     C | o Sets new connections to STOP on error |
488     C \==========================================================/
489 adcroft 1.9 IMPLICIT NONE
490 cnh 1.1
491     C == Global variables ==
492     #include "SIZE.h"
493     #include "EEPARAMS.h"
494     #include "DFILE.h"
495    
496     theErrorMode = errorModeSTOP
497    
498     RETURN
499     END
500    
501     SUBROUTINE DFILE_SET_CONT_ON_ERROR
502     C /==========================================================\
503     C | SUBROUTINE DFILE_SET_CONT_ON_ERROR |
504     C | o Sets new connections to continue on error |
505     C \==========================================================/
506 adcroft 1.9 IMPLICIT NONE
507 cnh 1.1
508     C == Global variables ==
509     #include "SIZE.h"
510     #include "EEPARAMS.h"
511     #include "DFILE.h"
512    
513     theErrorMode = errorModeCONT
514    
515     RETURN
516     END
517    
518     SUBROUTINE DFILE_WRITE_R4(
519     I lBuffer,
520     I nDims, dimList,
521     I fileHandle, fileId, myThid )
522     C /==========================================================\
523     C | SUBROUTINE DFILE_WRITE_R4 |
524     C | o Write record(s) to model dump file. |
525     C |==========================================================|
526     C | Controlling routine for doing actual I/O operations. |
527     C | Routine writes data to binary files. |
528     C | Could do elaborate write to netCDF or |
529     C | use C I/O primitives. For now we use plain F77 but the |
530     C | routine does write both data and metadata. Metadata is |
531     C | extra info. which describes the data - in this case it |
532     C | is information indicating the subregion of the global |
533     C | dataset being written out. |
534     C \==========================================================/
535 adcroft 1.9 IMPLICIT NONE
536 cnh 1.1
537     C == Global variables ==
538     #include "SIZE.h"
539     #include "EEPARAMS.h"
540     #include "DFILE.h"
541    
542     C == Routine arguments ==
543     C lBuffer - Amount of data written
544     C nDims - Global and subset dimensionality
545     C dimList - List of global and subset extents
546     C fileHandle - Handle identifying actual IO unit
547     C myThid - Thread number of thread calling this
548     C routine
549     C eMode - error mode for this fileHandle
550     INTEGER lBuffer
551     INTEGER nDims
552     INTEGER dimList(nDims*3)
553     INTEGER fileHandle
554     INTEGER fileId
555     INTEGER myThid
556    
557     C == Local variables ==
558     C ioUnit - Unit number for I/O
559     C msgBuf - Textual printing message buffer
560     C eMode - Error mode for this file handle
561     INTEGER ioUnit
562 cnh 1.2 CHARACTER*(MAX_LEN_MBUF) msgBuf
563     CHARACTER*(MAX_LEN_FNAM) fNam
564 cnh 1.1 INTEGER eMode
565     INTEGER I
566    
567     C-- Set error mode
568     eMode = errorMode(fileHandle,myThid)
569    
570     C-- Check that file is active
571     IF ( unitStatus(fileHandle,myThid) .NE. busyUnit ) GOTO 999
572    
573     C-- Write data
574     ioUnit = dUnitNumber(fileHandle,myThid)
575     fNam = nameOfDFile(fileHandle,myThid)
576     WRITE(ioUnit,ERR=899) (ioBuf_R4(I),I=1,lBuffer)
577    
578     C-- Now write meta information
579 cnh 1.8 IF ( metaDataStatus(fileHandle,myThid) .EQ.
580     & metaDataNotWritten ) THEN
581 cnh 1.1 ioUnit = mUnitNumber(fileHandle,myThid)
582    
583     WRITE(msgBuf,'(A)') '// START OF META DATA'
584     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
585    
586 adcroft 1.5 WRITE(msgBuf,'(A,A)') ' id =[ ','/* Identifier */'
587 cnh 1.1 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
588 cnh 1.8 CALL PRINT_LIST_I( fileId, 1, INDEX_NONE, .FALSE., .TRUE.,
589     & ioUnit )
590 adcroft 1.5 WRITE(msgBuf,'(A)') ' ]; '
591 cnh 1.1 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
592    
593 adcroft 1.5 WRITE(msgBuf,'(A,A)') ' nDims =[ ','/* Number of dimensions */'
594 cnh 1.1 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
595 cnh 1.8 CALL PRINT_LIST_I( nDims, 1, INDEX_NONE, .FALSE., .TRUE.,
596     & ioUnit )
597 adcroft 1.5 WRITE(msgBuf,'(A)') ' ]; '
598 cnh 1.1 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
599    
600 adcroft 1.5 WRITE(msgBuf,'(A,A)') ' dimList =[ ',
601 cnh 1.1 & '/* Global1, local min1, local max1, ... */'
602     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
603     DO I=1,nDims
604 cnh 1.8 CALL PRINT_LIST_I( dimList((I-1)*3+1), 3, INDEX_NONE,
605     & I.NE.nDims, .FALSE., ioUnit )
606 cnh 1.1 ENDDO
607 adcroft 1.5 WRITE(msgBuf,'(A)') ' ]; '
608     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
609    
610     WRITE(msgBuf,'(A,A)') ' format =[ ','/* Field format */'
611     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
612     WRITE(msgBuf,'(16X,A)') '''float32'''
613     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
614     WRITE(msgBuf,'(A)') ' ]; '
615 cnh 1.1 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
616    
617     WRITE(msgBuf,'(A)') '// END OF META DATA'
618     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
619     metaDataStatus(fileHandle,myThid) = metaDataWritten
620     ENDIF
621    
622     1000 CONTINUE
623     RETURN
624    
625     999 CONTINUE
626     WRITE(msgBuf,'(A)') ' S/R DFILE_WRITE_R4 '
627     CALL PRINT_ERROR( msgBuf , 1)
628     WRITE(msgBuf,'(A,A)') ' Thread ', myThid, ' unit not open '
629     CALL PRINT_ERROR( msgBuf , 1)
630     IF ( eMode .EQ. errorModeSTOP ) THEN
631     STOP 'ABNORMAL END: S/R DFILE_WRITE_R4'
632     ENDIF
633     ioErrorCount(myThid) = ioErrorCount(myThid) + 1
634     GOTO 1000
635    
636     899 CONTINUE
637     WRITE(msgBuf,'(A)') ' S/R DFILE_WRITE_R4 '
638     CALL PRINT_ERROR( msgBuf , 1)
639     WRITE(msgBuf,'(A,A)') ' Thread ', myThid, ' write error '
640     CALL PRINT_ERROR( msgBuf , 1)
641     WRITE(msgBuf,'(A,A)') ' File ', fNam
642     CALL PRINT_ERROR( msgBuf , 1)
643     IF ( eMode .EQ. errorModeSTOP ) THEN
644     STOP 'ABNORMAL END: S/R DFILE_WRITE_R4'
645     ENDIF
646     ioErrorCount(myThid) = ioErrorCount(myThid) + 1
647     GOTO 1000
648    
649     END
650    
651     SUBROUTINE DFILE_WRITE_R8(
652     I lBuffer,
653     I nDims, dimList,
654     I fileHandle, fileId, myThid )
655     C /==========================================================\
656     C | SUBROUTINE DFILE_WRITE_R8 |
657     C | o Write record(s) to model dump file. |
658     C |==========================================================|
659     C | Controlling routine for doing actual I/O operations. |
660     C | Routine writes data to binary files. |
661     C | Could do elaborate write to netCDF or |
662     C | use C I/O primitives. For now we use plain F77 but the |
663     C | routine does write both data and metadata. Metadata is |
664     C | extra info. which describes the data - in this case it |
665     C | is information indicating the subregion of the global |
666     C | dataset being written out. |
667     C \==========================================================/
668 adcroft 1.9 IMPLICIT NONE
669 cnh 1.1
670     C == Global variables ==
671     #include "SIZE.h"
672     #include "EEPARAMS.h"
673     #include "DFILE.h"
674    
675     C == Routine arguments ==
676     C buffer - Subset data to write
677     C lBuffer - Amount of data written
678     C nDims - Global and subset dimensionality
679     C dimList - List of global and subset extents
680     C fileHandle - Handle identifying actual IO unit
681     C myThid - Thread number of thread calling this
682     C routine
683     C eMode - error mode for this fileHandle
684     INTEGER lBuffer
685     INTEGER nDims
686     INTEGER dimList(nDims*3)
687     INTEGER fileHandle
688     INTEGER fileId
689     INTEGER myThid
690    
691     C == Local variables ==
692     C ioUnit - Unit number for I/O
693     C msgBuf - Textual printing message buffer
694     C eMode - Error mode for this file handle
695     INTEGER ioUnit
696 cnh 1.2 CHARACTER*(MAX_LEN_MBUF) msgBuf
697     CHARACTER*(MAX_LEN_FNAM) fNam
698 cnh 1.1 INTEGER eMode
699     INTEGER I
700    
701     C-- Set error mode
702     eMode = errorMode(fileHandle,myThid)
703    
704     C-- Check that file is active
705     IF ( unitStatus(fileHandle,myThid) .NE. busyUnit ) GOTO 999
706    
707     C-- Write data
708     ioUnit = dUnitNumber(fileHandle,myThid)
709     fNam = nameOfDFile(fileHandle,myThid)
710     WRITE(ioUnit,ERR=899) (ioBuf_R8(I),I=1,lBuffer)
711    
712     C-- Now write meta information
713 cnh 1.8 IF ( metaDataStatus(fileHandle,myThid) .EQ.
714     & metaDataNotWritten ) THEN
715 cnh 1.1 ioUnit = mUnitNumber(fileHandle,myThid)
716    
717     WRITE(msgBuf,'(A)') '// START OF META DATA'
718     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
719    
720 adcroft 1.5 WRITE(msgBuf,'(A,A)') ' id =[ ','/* Identifier */'
721 cnh 1.1 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
722 cnh 1.8 CALL PRINT_LIST_I( fileId, 1, INDEX_NONE, .FALSE., .TRUE.,
723     & ioUnit )
724 adcroft 1.5 WRITE(msgBuf,'(A)') ' ]; '
725 cnh 1.1 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
726    
727 adcroft 1.5 WRITE(msgBuf,'(A,A)') ' nDims =[ ','/* Number of dimensions */'
728 cnh 1.1 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
729 cnh 1.8 CALL PRINT_LIST_I( nDims, 1, INDEX_NONE, .FALSE., .TRUE.,
730     & ioUnit )
731 adcroft 1.5 WRITE(msgBuf,'(A)') ' ]; '
732 cnh 1.1 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
733    
734 adcroft 1.5 WRITE(msgBuf,'(A,A)') ' dimList =[ ',
735 cnh 1.1 & '/* Global1, local min1, local max1, ... */'
736     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
737     DO I=1,nDims
738 cnh 1.8 CALL PRINT_LIST_I( dimList((I-1)*3+1), 3, INDEX_NONE,
739     & I.NE.nDims, .FALSE., ioUnit )
740 cnh 1.1 ENDDO
741 adcroft 1.5 WRITE(msgBuf,'(A)') ' ]; '
742 cnh 1.1 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
743 adcroft 1.5
744     WRITE(msgBuf,'(A,A)') ' format =[ ','/* Field format */'
745     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
746     WRITE(msgBuf,'(16X,A)') '''float64'''
747     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
748     WRITE(msgBuf,'(A)') ' ]; '
749     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
750    
751 cnh 1.1 WRITE(msgBuf,'(A)') '// END OF META DATA'
752     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
753     metaDataStatus(fileHandle,myThid) = metaDataWritten
754     ENDIF
755    
756     1000 CONTINUE
757     RETURN
758    
759     999 CONTINUE
760     WRITE(msgBuf,'(A)') ' S/R DFILE_WRITE_R8 '
761     CALL PRINT_ERROR( msgBuf , 1)
762     WRITE(msgBuf,'(A,A)') ' Thread ', myThid, ' unit not open '
763     CALL PRINT_ERROR( msgBuf , 1)
764     IF ( eMode .EQ. errorModeSTOP ) THEN
765     STOP 'ABNORMAL END: S/R DFILE_WRITE_R8'
766     ENDIF
767     ioErrorCount(myThid) = ioErrorCount(myThid) + 1
768     GOTO 1000
769    
770     899 CONTINUE
771     WRITE(msgBuf,'(A)') ' S/R DFILE_WRITE_R8 '
772     CALL PRINT_ERROR( msgBuf , 1)
773     WRITE(msgBuf,'(A,A)') ' Thread ', myThid, ' write error '
774     CALL PRINT_ERROR( msgBuf , 1)
775     WRITE(msgBuf,'(A,A)') ' File ', fNam
776     CALL PRINT_ERROR( msgBuf , 1)
777     IF ( eMode .EQ. errorModeSTOP ) THEN
778     STOP 'ABNORMAL END: S/R DFILE_WRITE_R8'
779     ENDIF
780     ioErrorCount(myThid) = ioErrorCount(myThid) + 1
781     GOTO 1000
782    
783     END

  ViewVC Help
Powered by ViewVC 1.1.22