/[MITgcm]/MITgcm/pkg/ptracers/ptracers_monitor.F
ViewVC logotype

Diff of /MITgcm/pkg/ptracers/ptracers_monitor.F

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

revision 1.11 by jmc, Fri Jun 23 00:33:42 2006 UTC revision 1.12 by jmc, Tue Aug 8 21:24:31 2006 UTC
# Line 8  C !ROUTINE: PTRACERS_MONITOR Line 8  C !ROUTINE: PTRACERS_MONITOR
8    
9  C !INTERFACE: ==========================================================  C !INTERFACE: ==========================================================
10        SUBROUTINE PTRACERS_MONITOR(        SUBROUTINE PTRACERS_MONITOR(
11       I                myIter, myTime, myThid )       I                    myIter, myTime, myThid )
12    
13  C !DESCRIPTION:  C !DESCRIPTION:
14  C writes out ptracer statistics  C writes out ptracer statistics
# Line 27  C !USES: =============================== Line 27  C !USES: ===============================
27  #endif  #endif
28    
29  C !INPUT PARAMETERS: ===================================================  C !INPUT PARAMETERS: ===================================================
 C  myThid               :: thread number  
 C  myIter               :: current timestep  
30  C  myTime               :: current time  C  myTime               :: current time
31    C  myIter               :: current timestep
32    C  myThid               :: thread number
33          _RL     myTime
34        INTEGER myIter        INTEGER myIter
       _RL myTime  
35        INTEGER myThid        INTEGER myThid
36    
37  C     === Functions ====  C     === Functions ====
# Line 44  C     === Functions ==== Line 44  C     === Functions ====
44  C !LOCAL VARIABLES: ====================================================  C !LOCAL VARIABLES: ====================================================
45  C  i,j                  :: loop indices  C  i,j                  :: loop indices
46  C  ip                   :: ptracer number  C  ip                   :: ptracer number
47        CHARACTER*(MAX_LEN_MBUF) msgBuf          CHARACTER*(MAX_LEN_MBUF) msgBuf
48        CHARACTER*(MAX_LEN_MBUF) suff        CHARACTER*(MAX_LEN_MBUF) suff
49        _RL dT        INTEGER ip
       integer ip  
50  CEOP  CEOP
51    
52        dT=deltaTclock        IF ( DIFFERENT_MULTIPLE( PTRACERS_monitorFreq,myTime,deltaTClock )
53         &   ) THEN
54    
       IF ( DIFFERENT_MULTIPLE( PTRACERS_monitorFreq,myTime,dT ) ) THEN  
55  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
        mon_write_stdout = .FALSE.  
        mon_write_mnc    = .FALSE.  
        _BARRIER  
56    
57  C     Ptracers field monitor start  C--   Ptracers field monitor start
        _BEGIN_MASTER(myThid)  
58  #ifdef ALLOW_USE_MPI  #ifdef ALLOW_USE_MPI
59         IF ( .NOT. useSingleCPUIO .OR. mpiMyId .EQ. 0 ) THEN          IF ( .NOT.useSingleCPUIO .OR. mpiMyId.EQ.0 ) THEN
60  #endif /* ALLOW_USE_MPI */  #endif /* ALLOW_USE_MPI */
61                      _BEGIN_MASTER(myThid)
62          IF (PTRACERS_monitor_stdio) THEN  C-    only the master thread is allowed to switch On/Off mon_write_stdout
63           WRITE(msgBuf,'(2A)') '// ==========================',  C     & mon_write_mnc (since it's the only thread that uses those flags):
64       &        '============================='  
65           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)            IF (monitor_stdio) THEN
66           WRITE(msgBuf,'(A)')              mon_write_stdout = .TRUE.
67       &        '// Begin MONITOR ptracer field statistics'            ELSE
68           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit,              mon_write_stdout = .FALSE.
69       &        SQUEEZE_RIGHT , 1)            ENDIF
70           WRITE(msgBuf,'(2A)') '// ==========================',            mon_write_mnc    = .FALSE.
71       &        '============================='  #ifdef ALLOW_MNC
72           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)            IF (useMNC .AND. PTRACERS_monitor_mnc) THEN
73           mon_write_stdout = .TRUE.              WRITE(mon_fname,'(A)') 'monitor_ptracer'
74          ENDIF              CALL MNC_CW_APPEND_VNAME(
75                 &           'T', '-_-_--__-__t', 0,0, myThid)
76                CALL MNC_CW_SET_UDIM(mon_fname, -1, myThid)
77                CALL MNC_CW_I_W_S(
78         &          'I',mon_fname,1,1,'T', myIter, myThid)
79                CALL MNC_CW_SET_UDIM(mon_fname, 0, myThid)
80                mon_write_mnc = .TRUE.
81              ENDIF
82    #endif /*  ALLOW_MNC  */
83    
84              IF ( mon_write_stdout ) THEN
85                WRITE(msgBuf,'(2A)') '// ==========================',
86         &             '============================='
87                CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
88                WRITE(msgBuf,'(A)')
89         &             '// Begin MONITOR ptracer field statistics'
90                CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
91                WRITE(msgBuf,'(2A)') '// ==========================',
92         &             '============================='
93                CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
94              ENDIF
95    
96            _END_MASTER(myThid)
97  #ifdef ALLOW_USE_MPI  #ifdef ALLOW_USE_MPI
98         ENDIF         ENDIF
99  #endif /* ALLOW_USE_MPI */  #endif /* ALLOW_USE_MPI */
         _END_MASTER(myThid)  
100    
101  #ifdef ALLOW_MNC  C--   Ptracers field monitor : compute stats & write
102          IF (useMNC .AND. PTRACERS_monitor_mnc) mon_write_mnc = .TRUE.         IF ( PTRACERS_monitorFreq .NE. monitorFreq
103  #endif /*  ALLOW_MNC  */       &     .OR. (useMNC.AND.PTRACERS_monitor_mnc) ) THEN
104    C      repeat printing of time to make grepping easier, default is not
105          IF ( PTRACERS_monitorFreq .NE. monitorFreq ) THEN  C      to do this, because the default is to use the same monitorFreq
106  C     repeat printing of time to make grepping easier, default is not  C      for ptracers as for the dynamics variables.
 C     to do this, because the default is to use the same monitorFreq  
 C     for ptracers as for the dynamics variables.  
107           CALL MON_SET_PREF('trctime',myThid)           CALL MON_SET_PREF('trctime',myThid)
108           CALL MON_OUT_I( '_tsnumber', myIter,mon_string_none,myThid)           CALL MON_OUT_I( '_tsnumber', myIter,mon_string_none,myThid)
109           CALL MON_OUT_RL('_secondsf', myTime,mon_string_none,myThid)           CALL MON_OUT_RL('_secondsf', myTime,mon_string_none,myThid)
110          ENDIF         ENDIF
111  C       Print the basic statistics of ptracer variables  C      Print the basic statistics of ptracer variables
112         CALL MON_SET_PREF('trcstat_',myThid)         CALL MON_SET_PREF('trcstat_',myThid)
113         DO ip = 1, PTRACERS_numInUse         DO ip = 1, PTRACERS_numInUse
          _BEGIN_MASTER(myThid)  
114           WRITE(suff,'(A7,I2.2)') 'ptracer',ip           WRITE(suff,'(A7,I2.2)') 'ptracer',ip
115           _END_MASTER(myThid)  c        WRITE(suff,'(A7,I3.3)') 'ptrac_', ip
          _BARRIER  
116           CALL MON_PRINTSTATS_RL(           CALL MON_PRINTSTATS_RL(
117       &        Nr, ptracer(1-Olx,1-Oly,1,1,1,ip),       &        Nr, ptracer(1-Olx,1-Oly,1,1,1,ip),
118       &        suff, maskC,hFacC,rA ,drF,myThid)       &        suff, maskC,hFacC,rA ,drF,myThid)
119         ENDDO         ENDDO
120    
121         IF (PTRACERS_monitor_stdio) THEN  C--   Ptracers field monitor finish
 C     Ptracers field monitor finish  
         _BEGIN_MASTER(myThid)  
122  #ifdef ALLOW_USE_MPI  #ifdef ALLOW_USE_MPI
123          IF ( .NOT. useSingleCPUIO .OR. mpiMyId .EQ. 0 ) THEN         IF ( .NOT. useSingleCPUIO .OR. mpiMyId .EQ. 0 ) THEN
124  #endif /* ALLOW_USE_MPI */  #endif /* ALLOW_USE_MPI */
125            _BEGIN_MASTER(myThid)
126    C-    only the master thread is allowed to switch On/Off mon_write_stdout
127    C     & mon_write_mnc (since it's the only thread that uses those flags):
128    
129            IF ( mon_write_stdout ) THEN
130           WRITE(msgBuf,'(2A)') '// ==========================',           WRITE(msgBuf,'(2A)') '// ==========================',
131       &        '============================='       &        '============================='
132           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
133           WRITE(msgBuf,'(A)')           WRITE(msgBuf,'(A)')
134       &        '// End MONITOR ptracers field statistics'       &        '// End MONITOR ptracers field statistics'
135           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit,           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
      &        SQUEEZE_RIGHT , 1)  
136           WRITE(msgBuf,'(2A)') '// ==========================',           WRITE(msgBuf,'(2A)') '// ==========================',
137       &        '============================='       &        '============================='
138           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
 #ifdef ALLOW_USE_MPI  
139          ENDIF          ENDIF
 #endif /* ALLOW_USE_MPI */  
140    
141          mon_write_stdout = .FALSE.          mon_write_stdout = .FALSE.
142                    mon_write_mnc    = .FALSE.
143    
144          _END_MASTER(myThid)          _END_MASTER(myThid)
145    #ifdef ALLOW_USE_MPI
146         ENDIF         ENDIF
147    #endif /* ALLOW_USE_MPI */
148    
149         mon_write_stdout = .FALSE.  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
        mon_write_mnc    = .FALSE.  
150    
151  C     endif different multiple  C     endif different multiple
152        ENDIF        ENDIF

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

  ViewVC Help
Powered by ViewVC 1.1.22