/[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.12 by molod, Tue Jun 14 23:06:15 2005 UTC revision 1.13 by jmc, Sun Jun 26 16:51:49 2005 UTC
# Line 35  C     levels    :: List Output Levels Line 35  C     levels    :: List Output Levels
35  C     fields    :: List Output Fields  C     fields    :: List Output Fields
36  C     filename  :: List Output Filename  C     filename  :: List Output Filename
37  C--   per level statistics output:  C--   per level statistics output:
38  C     stat_freq   :: Frequency (in s) of statistics output  C     stat_freq   :: Frequency (in s) of statistics output
39  C     stat_phase  :: phase (in s) to write statistics output  C     stat_phase  :: phase (in s) to write statistics output
40  C     stat_region :: List of statistics output Regions  C     stat_region :: List of statistics output Regions
41  C     stat_fields :: List of statistics output Fields  C     stat_fields :: List of statistics output Fields
# Line 58  C     stat_fname  :: List of statistics Line 58  C     stat_fname  :: List of statistics
58        INTEGER stat_region(rdimLoc,ldimLoc)        INTEGER stat_region(rdimLoc,ldimLoc)
59        INTEGER ku, stdUnit        INTEGER ku, stdUnit
60        INTEGER j,k,l,n,m        INTEGER j,k,l,n,m
61        INTEGER regionCount        INTEGER iLen, regionCount
62        _RL undef, getcon        _RL undef, getcon
63        INTEGER  ILNBLNK        INTEGER  ILNBLNK
64        EXTERNAL ILNBLNK        EXTERNAL ILNBLNK
# Line 72  C--   full level output: Line 72  C--   full level output:
72    
73  C--   per level statistics output:  C--   per level statistics output:
74        NAMELIST / DIAG_STATIS_PARMS /        NAMELIST / DIAG_STATIS_PARMS /
75       &     stat_freq, stat_phase, stat_region, stat_fields,       &     stat_freq, stat_phase, stat_region, stat_fields,
76       &     stat_fname,       &     stat_fname,
77       &     diagSt_mnc       &     diagSt_mnc
78    
79  C     Initialize and Read Diagnostics Namelist  C     Initialize and Read Diagnostics Namelist
80        _BEGIN_MASTER(myThid)        _BEGIN_MASTER(myThid)
# Line 142  C-    set default for statistics output Line 142  C-    set default for statistics output
142       &     ' read namelist "DIAG_STATIS_PARMS": start'       &     ' read namelist "DIAG_STATIS_PARMS": start'
143        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
144       &                    SQUEEZE_RIGHT , 1)       &                    SQUEEZE_RIGHT , 1)
 c     STOP 'before reading namelist: DIAG_STATIS_PARMS'  
145        READ  (ku,NML=DIAG_STATIS_PARMS)        READ  (ku,NML=DIAG_STATIS_PARMS)
146        WRITE(msgBuf,'(2A)') 'S/R DIAGNOSTICS_READPARMS,',        WRITE(msgBuf,'(2A)') 'S/R DIAGNOSTICS_READPARMS,',
147       &     ' read namelist "DIAG_STATIS_PARMS": OK'       &     ' read namelist "DIAG_STATIS_PARMS": OK'
# Line 151  c     STOP 'before reading namelist: DIA Line 150  c     STOP 'before reading namelist: DIA
150    
151        CLOSE (ku)        CLOSE (ku)
152    
153  C     Initialise diag_choices common block  C     Initialise diag_choices common block (except pointers)
154        nlists = 0        nlists = 0
155        DO n = 1,numlists        DO n = 1,numlists
156          freq(n) = 0.          freq(n) = 0.
# Line 164  C     Initialise diag_choices common blo Line 163  C     Initialise diag_choices common blo
163          ENDDO          ENDDO
164          DO m = 1,numperlist          DO m = 1,numperlist
165            flds(m,n) = blk8c            flds(m,n) = blk8c
           jdiag(m,n) = 0  
166          ENDDO          ENDDO
167        ENDDO        ENDDO
168    
# Line 188  C     Fill Diagnostics Common Block with Line 186  C     Fill Diagnostics Common Block with
186        diagSt_ascii = (.NOT. diagSt_mnc) .OR. outputTypesInclusive        diagSt_ascii = (.NOT. diagSt_mnc) .OR. outputTypesInclusive
187    
188        DO l = 1,ldimLoc        DO l = 1,ldimLoc
189         IF ( filename(L).NE.blkFilName .and. nlists.LT.numlists ) THEN         iLen = ILNBLNK(filename(l))
190    C-     Only lists with non-empty file name (iLen>0) are considered
191           IF ( iLen.GE.1 .AND. nlists.LT.numlists ) THEN
192           n = nlists + 1           n = nlists + 1
193           freq(n)    = frequency(l)           freq(n)    = frequency(l)
194           IF ( timePhase(l).NE. UNSET_RL ) THEN           IF ( timePhase(l).NE. UNSET_RL ) THEN
# Line 243  C-       will set levels later, once the Line 243  C-       will set levels later, once the
243           ENDDO           ENDDO
244           nlists = nlists + 1           nlists = nlists + 1
245  c        write(6,*) 'list summary:',n,nfields(n),nlevels(n)  c        write(6,*) 'list summary:',n,nfields(n),nlevels(n)
246         ELSEIF (filename(L).NE.blkFilName) THEN         ELSEIF ( iLen.GE.1 ) THEN
247           WRITE(msgBuf,'(2A,I3)') 'DIAGNOSTICS_READPARMS: ',           WRITE(msgBuf,'(2A,I3)') 'DIAGNOSTICS_READPARMS: ',
248       &            'Exceed Max.Num. of list numlists=', numlists       &            'Exceed Max.Num. of list numlists=', numlists
249           CALL PRINT_ERROR( msgBuf , myThid )           CALL PRINT_ERROR( msgBuf , myThid )
# Line 259  c        write(6,*) 'list summary:',n,nf Line 259  c        write(6,*) 'list summary:',n,nf
259    
260  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
261    
262  C     Initialise DIAG_STATIS common block  C     Initialise DIAG_STATIS common block (except pointers)
263        diagSt_nbLists = 0        diagSt_nbLists = 0
264        DO n = 1,numlists        DO n = 1,numlists
265          diagSt_freq(n) = 0.          diagSt_freq(n) = 0.
# Line 272  C     Initialise DIAG_STATIS common bloc Line 272  C     Initialise DIAG_STATIS common bloc
272          ENDDO          ENDDO
273          DO m = 1,numperlist          DO m = 1,numperlist
274            diagSt_Flds(m,n) = blk8c            diagSt_Flds(m,n) = blk8c
           jSdiag(m,n) = 0  
275          ENDDO          ENDDO
276        ENDDO        ENDDO
277    
# Line 280  C     Fill Diagnostics Common Block with Line 279  C     Fill Diagnostics Common Block with
279        diagSt_ascii = (.NOT. diagSt_mnc) .OR. outputTypesInclusive        diagSt_ascii = (.NOT. diagSt_mnc) .OR. outputTypesInclusive
280    
281        DO l = 1,ldimLoc        DO l = 1,ldimLoc
282         IF(stat_fname(L).NE.blkFilName.AND.         iLen = ILNBLNK(stat_fname(l))
283       .                            diagSt_nbLists.LT.numlists)THEN  C-     Only lists with non-empty file name (iLen>0) are considered
284           IF ( iLen.GE.1 .AND. diagSt_nbLists.LT.numlists)THEN
285           n = diagSt_nbLists + 1           n = diagSt_nbLists + 1
286           diagSt_freq(n) = stat_freq(l)           diagSt_freq(n) = stat_freq(l)
287           IF ( stat_phase(l).NE. UNSET_RL ) THEN           IF ( stat_phase(l).NE. UNSET_RL ) THEN
# Line 323  C-       no region selected => default i Line 323  C-       no region selected => default i
323       &        'Exceed Max.Num. of Fields/list numperlist=', numperlist       &        'Exceed Max.Num. of Fields/list numperlist=', numperlist
324               CALL PRINT_ERROR( msgBuf , myThid )               CALL PRINT_ERROR( msgBuf , myThid )
325               WRITE(msgBuf,'(2A,I3,3A,I3,2A)') 'DIAGNOSTICS_READPARMS: ',               WRITE(msgBuf,'(2A,I3,3A,I3,2A)') 'DIAGNOSTICS_READPARMS: ',
326       &        'when trying to add stat_field (m=', m,       &        'when trying to add stat_field (m=', m,
327       &        ' ): ',stat_fields(m,l)       &        ' ): ',stat_fields(m,l)
328               CALL PRINT_ERROR( msgBuf , myThid )               CALL PRINT_ERROR( msgBuf , myThid )
329               WRITE(msgBuf,'(2A,I3,2A)') 'DIAGNOSTICS_READPARMS: ',               WRITE(msgBuf,'(2A,I3,2A)') 'DIAGNOSTICS_READPARMS: ',
# Line 334  C-       no region selected => default i Line 334  C-       no region selected => default i
334           ENDDO           ENDDO
335           diagSt_nbLists = diagSt_nbLists + 1           diagSt_nbLists = diagSt_nbLists + 1
336  c        write(6,*) 'stat-list summary:',n,diagSt_nbFlds(n),regionCount  c        write(6,*) 'stat-list summary:',n,diagSt_nbFlds(n),regionCount
337         ELSEIF ( stat_fname(L).NE.blkFilName ) THEN         ELSEIF ( iLen.GE.1 ) THEN
338           WRITE(msgBuf,'(2A,I3)') 'DIAGNOSTICS_READPARMS: ',           WRITE(msgBuf,'(2A,I3)') 'DIAGNOSTICS_READPARMS: ',
339       &            'Exceed Max.Num. of list numlists=', numlists       &            'Exceed Max.Num. of list numlists=', numlists
340           CALL PRINT_ERROR( msgBuf , myThid )           CALL PRINT_ERROR( msgBuf , myThid )
# Line 392  C     Echo History List Data Structure Line 392  C     Echo History List Data Structure
392          WRITE(msgBuf,'(2(A,F17.6))') 'Frequency : ',diagSt_freq(n),          WRITE(msgBuf,'(2(A,F17.6))') 'Frequency : ',diagSt_freq(n),
393       &                               ' ; Phase: ', diagSt_phase(n)       &                               ' ; Phase: ', diagSt_phase(n)
394          CALL PRINT_MESSAGE( msgBuf, stdUnit,SQUEEZE_RIGHT, myThid)          CALL PRINT_MESSAGE( msgBuf, stdUnit,SQUEEZE_RIGHT, myThid)
395          WRITE(msgBuf,'(A)') ' Regions : '          WRITE(msgBuf,'(A)') ' Regions : '
396          l = 12          l = 12
397          DO j=0,nRegions          DO j=0,nRegions
398           IF ( diagSt_region(j,n).GE.1 ) THEN           IF ( diagSt_region(j,n).GE.1 ) THEN

Legend:
Removed from v.1.12  
changed lines
  Added in v.1.13

  ViewVC Help
Powered by ViewVC 1.1.22