/[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.14 by edhill, Wed Jul 6 02:13:52 2005 UTC revision 1.15 by jmc, Mon Jan 23 22:24:28 2006 UTC
# Line 20  C     !USES: Line 20  C     !USES:
20  #include "PARAMS.h"  #include "PARAMS.h"
21  #include "DIAGNOSTICS_SIZE.h"  #include "DIAGNOSTICS_SIZE.h"
22  #include "DIAGNOSTICS.h"  #include "DIAGNOSTICS.h"
23    #include "DIAGSTATS_REGIONS.h"
24    
25  C     !INPUT PARAMETERS:  C     !INPUT PARAMETERS:
26        INTEGER myThid        INTEGER myThid
27  CEOP  CEOP
28    
29  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
30  C     ldimLoc :: Max Number of Lists  C     ldimLoc :: Max Number of Lists  (in data.diagnostics)
31  C     kdimLoc :: Max Number of Levels  C     kdimLoc :: Max Number of Levels (in data.diagnostics)
32  C     fdimLoc :: Max Number of Fields  C     fdimLoc :: Max Number of Fields (in data.diagnostics)
33  C     frequency :: Frequency (in s) of Output (ouput every "frequency" second)  C     frequency :: Frequency (in s) of Output (ouput every "frequency" second)
34  C     timePhase :: phase (in s) within the "frequency" period to write output  C     timePhase :: phase (in s) within the "frequency" period to write output
35  C     levels    :: List Output Levels  C     levels    :: List Output Levels
36  C     fields    :: List Output Fields  C     fields    :: List Output Fields
37  C     filename  :: List Output Filename  C     filename  :: List Output Filename
38    C--   for regional-statistics
39    C     lev_regMask(n) :: region-mask levels that define the region "n"
40    C     val_regMask(n) :: corresponding mask value of region "n" in the region-mask
41  C--   per level statistics output:  C--   per level statistics output:
42  C     stat_freq   :: Frequency (in s) of statistics output  C     stat_freq   :: Frequency (in s) of statistics output
43  C     stat_phase  :: phase (in s) to write statistics output  C     stat_phase  :: phase (in s) to write statistics output
# Line 44  C     stat_fname  :: List of statistics Line 48  C     stat_fname  :: List of statistics
48        PARAMETER ( ldimLoc = 2*numlists )        PARAMETER ( ldimLoc = 2*numlists )
49        PARAMETER ( kdimLoc = 2*numLevels )        PARAMETER ( kdimLoc = 2*numLevels )
50        PARAMETER ( fdimLoc = 2*numperlist )        PARAMETER ( fdimLoc = 2*numperlist )
51        PARAMETER ( rdimLoc = 2*nRegions+1 )        PARAMETER ( rdimLoc = nRegions+21 )
52        _RL         frequency(ldimLoc), timePhase(ldimLoc)        _RL         frequency(ldimLoc), timePhase(ldimLoc)
53        _RL         levels(kdimLoc,ldimLoc)        _RL         levels(kdimLoc,ldimLoc)
54        _RL         stat_freq(ldimLoc), stat_phase(ldimLoc)        _RL         stat_freq(ldimLoc), stat_phase(ldimLoc)
# Line 56  C     stat_fname  :: List of statistics Line 60  C     stat_fname  :: List of statistics
60        CHARACTER*8 blk8c        CHARACTER*8 blk8c
61        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
62        INTEGER stat_region(rdimLoc,ldimLoc)        INTEGER stat_region(rdimLoc,ldimLoc)
63          INTEGER lev_regMask(rdimLoc)
64          _RS     val_regMask(rdimLoc)
65        INTEGER ku, stdUnit        INTEGER ku, stdUnit
66        INTEGER j,k,l,n,m        INTEGER j,k,l,n,m
67        INTEGER iLen, regionCount        INTEGER iLen, regionCount
# Line 73  C--   full level output: Line 79  C--   full level output:
79  C--   per level statistics output:  C--   per level statistics output:
80        NAMELIST / DIAG_STATIS_PARMS /        NAMELIST / DIAG_STATIS_PARMS /
81       &     stat_freq, stat_phase, stat_region, stat_fields,       &     stat_freq, stat_phase, stat_region, stat_fields,
82       &     stat_fname,       &     stat_fname, diagSt_mnc,
83       &     diagSt_mnc       &     lev_regMask, val_regMask,
84         &     diagSt_regMaskFile, nLevRegMskFile
85    
86  C     Initialize and Read Diagnostics Namelist  C     Initialize and Read Diagnostics Namelist
87        _BEGIN_MASTER(myThid)        _BEGIN_MASTER(myThid)
# Line 105  C       eight spaces:        12345678 Line 112  C       eight spaces:        12345678
112        diag_pickup_read_mnc  = .FALSE.        diag_pickup_read_mnc  = .FALSE.
113        diag_pickup_write_mnc = .FALSE.        diag_pickup_write_mnc = .FALSE.
114    
115          diagSt_regMaskFile = ' '
116          nLevRegMskFile = 0
117          DO k = 1,rdimLoc
118            lev_regMask(k) = 0
119            val_regMask(k) = 0.
120          ENDDO
121        DO l = 1,ldimLoc        DO l = 1,ldimLoc
122          stat_freq(l)  = 0.          stat_freq(l)  = 0.
123          stat_phase(l) = UNSET_RL          stat_phase(l) = UNSET_RL
# Line 259  c        write(6,*) 'list summary:',n,nf Line 272  c        write(6,*) 'list summary:',n,nf
272    
273  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
274    
275  C     Initialise DIAG_STATIS common block (except pointers)  C-    Initialise DIAG_STATS_REGMASK common block (except the mask)
276          nLevRegMask = 0
277          DO j = 0,nRegions
278            diagSt_kRegMsk(j) = 0
279            diagSt_vRegMsk(j) = 0.
280          ENDDO
281    C     Global statistics (region # 0)
282          diagSt_kRegMsk(0) = 1
283    
284    C-    Initialise DIAG_STATIS common block (except pointers)
285        diagSt_nbLists = 0        diagSt_nbLists = 0
286        DO n = 1,numlists        DO n = 1,numlists
287          diagSt_freq(n) = 0.          diagSt_freq(n) = 0.
# Line 278  C     Initialise DIAG_STATIS common bloc Line 300  C     Initialise DIAG_STATIS common bloc
300  C     Fill Diagnostics Common Block with Namelist Info  C     Fill Diagnostics Common Block with Namelist Info
301        diagSt_ascii = (.NOT. diagSt_mnc) .OR. outputTypesInclusive        diagSt_ascii = (.NOT. diagSt_mnc) .OR. outputTypesInclusive
302    
303    C-    Region mask correspondence table:
304    C     note: this table should be build when regions are defined ;
305    C     for now, simpler just to read it from namelist in data.diagnostics
306          j = 0
307          DO k = 1,rdimLoc
308           IF ( lev_regMask(k).NE.0 .OR. val_regMask(k).NE.0. ) THEN
309             j = j+1
310             IF ( j.LE.nRegions ) THEN
311               diagSt_kRegMsk(j) = lev_regMask(k)
312               diagSt_vRegMsk(j) = val_regMask(k)
313             ENDIF
314           ENDIF
315          ENDDO
316          IF ( j.GT.nRegions ) THEN
317             WRITE(msgBuf,'(2A,I3,A)') 'DIAGNOSTICS_READPARMS: ',
318         &   'lev_regMask & val_regMask lists assume at least',j,' regions'
319             CALL PRINT_ERROR( msgBuf , myThid )
320             WRITE(msgBuf,'(2A)') 'DIAGNOSTICS_READPARMS: ',
321         &   'Need to increase "nRegions" in DIAGNOSTICS_SIZE.h'
322             CALL PRINT_ERROR( msgBuf , myThid )
323             STOP 'ABNORMAL END: S/R DIAGNOSTICS_READPARMS'
324          ENDIF
325    
326        DO l = 1,ldimLoc        DO l = 1,ldimLoc
327         iLen = ILNBLNK(stat_fname(l))         iLen = ILNBLNK(stat_fname(l))
328  C-     Only lists with non-empty file name (iLen>0) are considered  C-     Only lists with non-empty file name (iLen>0) are considered
# Line 294  C-     Only lists with non-empty file na Line 339  C-     Only lists with non-empty file na
339           DO k=1,rdimLoc           DO k=1,rdimLoc
340             j = stat_region(k,l)             j = stat_region(k,l)
341             IF ( j.NE.UNSET_I .AND. j.GE.0 .AND. j.LE.nRegions ) THEN             IF ( j.NE.UNSET_I .AND. j.GE.0 .AND. j.LE.nRegions ) THEN
342                IF ( diagSt_region(j,n).EQ.0 ) THEN
343               diagSt_region(j,n) = 1               diagSt_region(j,n) = 1
344               regionCount = regionCount + 1               regionCount = regionCount + 1
345                ELSE
346                 WRITE(msgBuf,'(2A,I3,2A)')
347         &        'DIAGNOSTICS_READPARMS:',
348         &        ' in list l=', l, ', stat_fname: ', stat_fname(l)
349                 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
350         &                           SQUEEZE_RIGHT , myThid )
351                 WRITE(msgBuf,'(A,I3,A)')
352         &        'DIAGNOSTICS_READPARMS: region=',j,
353         &        ' can only be selected once => ignore 2nd selection'
354                 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
355         &                           SQUEEZE_RIGHT , myThid )
356                ENDIF
357             ELSEIF ( j.NE.UNSET_I ) THEN             ELSEIF ( j.NE.UNSET_I ) THEN
358               WRITE(msgBuf,'(A,I3,A,I3,2A)')               WRITE(msgBuf,'(A,I3,A,I3,2A)')
359       &       'DIAGNOSTICS_READPARMS: region=',j,       &       'DIAGNOSTICS_READPARMS: region=',j,

Legend:
Removed from v.1.14  
changed lines
  Added in v.1.15

  ViewVC Help
Powered by ViewVC 1.1.22