/[MITgcm]/MITgcm/pkg/diagnostics/diagnostics_readparms.F
ViewVC logotype

Diff of /MITgcm/pkg/diagnostics/diagnostics_readparms.F

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

revision 1.26 by jmc, Fri Jan 15 18:57:36 2010 UTC revision 1.27 by jmc, Sun Dec 19 23:50:57 2010 UTC
# Line 35  C     timePhase :: phase (in s) within t Line 35  C     timePhase :: phase (in s) within t
35  C     averagingFreq  :: frequency (in s) for periodic averaging interval  C     averagingFreq  :: frequency (in s) for periodic averaging interval
36  C     averagingPhase :: phase     (in s) for periodic averaging interval  C     averagingPhase :: phase     (in s) for periodic averaging interval
37  C     repeatCycle    :: number of averaging intervals in 1 cycle  C     repeatCycle    :: number of averaging intervals in 1 cycle
38  C     mising_value     :: missing value for floats   in output  C     missing_value  :: missing value for real-type fields in output file
39  C     mising_value_int :: missing value for integers in output  C     missing_value_int :: missing value for integers in output
40  C     levels    :: List Output Levels  C     levels    :: List Output Levels
41  C     fields    :: List Output Fields  C     fields    :: List Output Fields
42  C     filename  :: List Output Filename  C     fileName  :: List Output Filename
43  C--   for regional-statistics  C--   for regional-statistics
44  C     set_regMask(n) :: region-mask set-index that define the region "n"  C     set_regMask(n) :: region-mask set-index that define the region "n"
45  C     val_regMask(n) :: corresponding mask value of region "n" in the region-mask  C     val_regMask(n) :: corresponding mask value of region "n" in the region-mask
# Line 48  C     stat_freq   :: Frequency (in s) of Line 48  C     stat_freq   :: Frequency (in s) of
48  C     stat_phase  :: phase (in s) to write statistics output  C     stat_phase  :: phase (in s) to write statistics output
49  C     stat_region :: List of statistics output Regions  C     stat_region :: List of statistics output Regions
50  C     stat_fields :: List of statistics output Fields  C     stat_fields :: List of statistics output Fields
51  C     stat_fname  :: List of statistics output Filename  C     stat_fName  :: List of statistics output Filename
52        INTEGER     ldimLoc, kdimLoc, fdimLoc, rdimLoc        INTEGER     ldimLoc, kdimLoc, fdimLoc, rdimLoc
53        PARAMETER ( ldimLoc = 2*numlists )        PARAMETER ( ldimLoc = 2*numlists )
54        PARAMETER ( kdimLoc = 2*numLevels )        PARAMETER ( kdimLoc = 2*numLevels )
# Line 63  C     stat_fname  :: List of statistics Line 63  C     stat_fname  :: List of statistics
63        _RL         stat_freq(ldimLoc), stat_phase(ldimLoc)        _RL         stat_freq(ldimLoc), stat_phase(ldimLoc)
64        CHARACTER*8 fields(fdimLoc,ldimLoc)        CHARACTER*8 fields(fdimLoc,ldimLoc)
65        CHARACTER*8 stat_fields(fdimLoc,ldimLoc)        CHARACTER*8 stat_fields(fdimLoc,ldimLoc)
66        CHARACTER*80 filename(ldimLoc), blkFilName        CHARACTER*80 fileName(ldimLoc), blkFilName
67        CHARACTER*80 stat_fname(ldimLoc)        CHARACTER*80 stat_fname(ldimLoc)
68        CHARACTER*8 fileflags(ldimLoc)        CHARACTER*8 fileFlags(ldimLoc)
69        CHARACTER*8 blk8c        CHARACTER*8 blk8c
70        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
71        CHARACTER*12 suffix        CHARACTER*12 suffix
# Line 83  C--   full level output: Line 83  C--   full level output:
83       &     frequency, timePhase,       &     frequency, timePhase,
84       &     averagingFreq, averagingPhase, repeatCycle,       &     averagingFreq, averagingPhase, repeatCycle,
85       &     missing_value, missing_value_int,       &     missing_value, missing_value_int,
86       &     levels, fields, filename, fileflags,       &     levels, fields, fileName, fileFlags,
87       &     dumpAtLast, diag_mnc,       &     dumpAtLast, diag_mnc,
88       &     diag_pickup_read,     diag_pickup_write,       &     diag_pickup_read,     diag_pickup_write,
89       &     diag_pickup_read_mnc, diag_pickup_write_mnc       &     diag_pickup_read_mnc, diag_pickup_write_mnc
# Line 109  C     Initialize and Read Diagnostics Na Line 109  C     Initialize and Read Diagnostics Na
109          averagingFreq(l) = 0.          averagingFreq(l) = 0.
110          averagingPhase(l)= 0.          averagingPhase(l)= 0.
111          repeatCycle(l)   = 0          repeatCycle(l)   = 0
112          filename(l)   = blkFilName          fileName(l)   = blkFilName
113          missing_value(l)     = UNSET_RL          missing_value(l)     = UNSET_RL
114          missing_value_int(l) = UNSET_I          missing_value_int(l) = UNSET_I
115          fileflags(l)  = blk8c          fileFlags(l)  = blk8c
116          DO k = 1,kdimLoc          DO k = 1,kdimLoc
117            levels(k,l) = UNSET_RL            levels(k,l) = UNSET_RL
118          ENDDO          ENDDO
# Line 221  C     Fill Diagnostics Common Block with Line 221  C     Fill Diagnostics Common Block with
221        diagSt_ascii = (.NOT. diagSt_mnc) .OR. outputTypesInclusive        diagSt_ascii = (.NOT. diagSt_mnc) .OR. outputTypesInclusive
222    
223        DO l = 1,ldimLoc        DO l = 1,ldimLoc
224         iLen = ILNBLNK(filename(l))         iLen = ILNBLNK(fileName(l))
225  C-     Only lists with non-empty file name (iLen>0) are considered  C-     Only lists with non-empty file name (iLen>0) are considered
226         IF ( iLen.GE.1 .AND. nlists.LT.numlists ) THEN         IF ( iLen.GE.1 .AND. nlists.LT.numlists ) THEN
227           n = nlists + 1           n = nlists + 1
# Line 241  C-     Only lists with non-empty file na Line 241  C-     Only lists with non-empty file na
241       &       averagingFreq(l), repeatCycle(l)       &       averagingFreq(l), repeatCycle(l)
242             CALL PRINT_ERROR( msgBuf , myThid )             CALL PRINT_ERROR( msgBuf , myThid )
243             WRITE(msgBuf,'(2A,I4,2A)') 'DIAGNOSTICS_READPARMS: ',             WRITE(msgBuf,'(2A,I4,2A)') 'DIAGNOSTICS_READPARMS: ',
244       &         ' for list l=', l, ', filename: ', filename(l)       &         ' for list l=', l, ', fileName: ', fileName(l)
245             CALL PRINT_ERROR( msgBuf , myThid )             CALL PRINT_ERROR( msgBuf , myThid )
246             STOP 'ABNORMAL END: S/R DIAGNOSTICS_READPARMS'             STOP 'ABNORMAL END: S/R DIAGNOSTICS_READPARMS'
247           ELSEIF ( frequency(l) .EQ. 0. ) THEN           ELSEIF ( frequency(l) .EQ. 0. ) THEN
# Line 255  C-     Only lists with non-empty file na Line 255  C-     Only lists with non-empty file na
255       &        misvalFlt(n) = missing_value(l)       &        misvalFlt(n) = missing_value(l)
256           IF ( missing_value_int(l) .NE. UNSET_I )           IF ( missing_value_int(l) .NE. UNSET_I )
257       &        misvalInt(n) = missing_value_int(l)       &        misvalInt(n) = missing_value_int(l)
258           fnames(n)  = filename (l)           fnames(n)  = fileName (l)
259           fflags(n)  = fileflags(l)           fflags(n)  = fileFlags(l)
260           nlevels(n) = 0           nlevels(n) = 0
261           IF ( levels(1,l).NE.UNSET_RL ) THEN           IF ( levels(1,l).NE.UNSET_RL ) THEN
262             DO k=1,kdimLoc             DO k=1,kdimLoc
# Line 272  C-     Only lists with non-empty file na Line 272  C-     Only lists with non-empty file na
272       &         'when trying to add level(k=', k, ' )=', levels(k,l)       &         'when trying to add level(k=', k, ' )=', levels(k,l)
273                CALL PRINT_ERROR( msgBuf , myThid )                CALL PRINT_ERROR( msgBuf , myThid )
274                WRITE(msgBuf,'(2A,I4,2A)') 'DIAGNOSTICS_READPARMS: ',                WRITE(msgBuf,'(2A,I4,2A)') 'DIAGNOSTICS_READPARMS: ',
275       &         ' for list l=', l, ', filename: ', filename(l)       &         ' for list l=', l, ', fileName: ', fileName(l)
276                CALL PRINT_ERROR( msgBuf , myThid )                CALL PRINT_ERROR( msgBuf , myThid )
277                STOP 'ABNORMAL END: S/R DIAGNOSTICS_READPARMS'                STOP 'ABNORMAL END: S/R DIAGNOSTICS_READPARMS'
278               ENDIF               ENDIF
# Line 295  C-       will set levels later, once the Line 295  C-       will set levels later, once the
295       &        'when trying to add field (m=', m, ' ): ',fields(m,l)       &        'when trying to add field (m=', m, ' ): ',fields(m,l)
296               CALL PRINT_ERROR( msgBuf , myThid )               CALL PRINT_ERROR( msgBuf , myThid )
297               WRITE(msgBuf,'(2A,I4,2A)') 'DIAGNOSTICS_READPARMS: ',               WRITE(msgBuf,'(2A,I4,2A)') 'DIAGNOSTICS_READPARMS: ',
298       &        ' in list l=', l, ', filename: ', filename(l)       &        ' in list l=', l, ', fileName: ', fileName(l)
299               CALL PRINT_ERROR( msgBuf , myThid )               CALL PRINT_ERROR( msgBuf , myThid )
300               STOP 'ABNORMAL END: S/R DIAGNOSTICS_READPARMS'               STOP 'ABNORMAL END: S/R DIAGNOSTICS_READPARMS'
301             ENDIF             ENDIF
# Line 310  c        write(6,*) 'list summary:',n,nf Line 310  c        write(6,*) 'list summary:',n,nf
310       &    'when trying to add list l=', l       &    'when trying to add list l=', l
311           CALL PRINT_ERROR( msgBuf , myThid )           CALL PRINT_ERROR( msgBuf , myThid )
312           WRITE(msgBuf,'(2A,F18.6,2A)') 'DIAGNOSTICS_READPARMS: ',           WRITE(msgBuf,'(2A,F18.6,2A)') 'DIAGNOSTICS_READPARMS: ',
313       &    ' Frq=', frequency(l), ', filename: ', filename(l)       &    ' Frq=', frequency(l), ', fileName: ', fileName(l)
314           CALL PRINT_ERROR( msgBuf , myThid )           CALL PRINT_ERROR( msgBuf , myThid )
315           STOP 'ABNORMAL END: S/R DIAGNOSTICS_READPARMS'           STOP 'ABNORMAL END: S/R DIAGNOSTICS_READPARMS'
316         ENDIF         ENDIF

Legend:
Removed from v.1.26  
changed lines
  Added in v.1.27

  ViewVC Help
Powered by ViewVC 1.1.22