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

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

  ViewVC Help
Powered by ViewVC 1.1.22