/[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.2 by mlosch, Mon Nov 29 00:38:37 2004 UTC revision 1.18 by jmc, Tue Mar 16 00:22:26 2010 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"
 #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_PARAMS.h"
24    #include "PTRACERS_FIELDS.h"
25  #ifdef ALLOW_MONITOR  #ifdef ALLOW_MONITOR
26  #include "MONITOR.h"  #include "MONITOR.h"
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 ====
38        LOGICAL  DIFFERENT_MULTIPLE        LOGICAL  DIFFERENT_MULTIPLE
39        EXTERNAL DIFFERENT_MULTIPLE        EXTERNAL DIFFERENT_MULTIPLE
40          LOGICAL  MASTER_CPU_IO
41          EXTERNAL MASTER_CPU_IO
42    
43  #ifdef ALLOW_PTRACERS  #ifdef ALLOW_PTRACERS
44  #ifdef ALLOW_MONITOR  #ifdef ALLOW_MONITOR
# Line 44  C     === Functions ==== Line 46  C     === Functions ====
46  C !LOCAL VARIABLES: ====================================================  C !LOCAL VARIABLES: ====================================================
47  C  i,j                  :: loop indices  C  i,j                  :: loop indices
48  C  ip                   :: ptracer number  C  ip                   :: ptracer number
49        CHARACTER*(MAX_LEN_MBUF) msgBuf          CHARACTER*(MAX_LEN_MBUF) msgBuf
50        CHARACTER*(MAX_LEN_MBUF) suff        CHARACTER*(MAX_LEN_MBUF) suff
51        _RL dT        INTEGER ip
52        INTEGER time_as_int        _RL dummyRL(6)
       integer ip  
 CML      integer i,j,k,bi,bj  
 CML      _RL tmp(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)  
53  CEOP  CEOP
54    
55        dT=deltaTclock        IF ( DIFFERENT_MULTIPLE( PTRACERS_monitorFreq,myTime,deltaTClock )
56         &   ) THEN
57    
58        IF (myIter.LE.nIter0+1.OR.DIFFERENT_MULTIPLE(  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
      &     PTRACERS_monitorFreq,myTime,myTime-dT)) THEN  
59    
60  CML       mon_write_stdout = .TRUE.  C--   Ptracers field monitor start
61            IF ( MASTER_CPU_IO(myThid) ) THEN
62    C--   only the master thread is allowed to switch On/Off mon_write_stdout
63    C     & mon_write_mnc (since it is the only thread that uses those flags):
64    
65              IF (monitor_stdio) THEN
66                mon_write_stdout = .TRUE.
67              ELSE
68                mon_write_stdout = .FALSE.
69              ENDIF
70              mon_write_mnc    = .FALSE.
71    #ifdef ALLOW_MNC
72              IF (useMNC .AND. PTRACERS_monitor_mnc) THEN
73                WRITE(mon_fname,'(A)') 'monitor_ptracer'
74                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_RL_W_S(
78         &          'D',mon_fname,1,1,'T', myTime, 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  C     Ptracers field monitor start  C--   endif master cpu io
        _BEGIN_MASTER(myThid)  
 #ifdef ALLOW_USE_MPI  
        IF ( .NOT. useSingleCPUIO .OR. mpiMyId .EQ. 0 ) THEN  
 #endif /* ALLOW_USE_MPI */  
           
         IF (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  
97         ENDIF         ENDIF
 #endif /* ALLOW_USE_MPI */  
         _END_MASTER(myThid)  
98    
99          IF ( PTRACERS_monitorFreq .NE. monitorFreq ) THEN  C--   Ptracers field monitor : compute stats & write
100  C     repeat printing of time to make grepping easier, default is not         IF ( PTRACERS_monitorFreq .NE. monitorFreq
101  C     to do this, because the default is to use the same monitorFreq       &     .OR. (useMNC.AND.PTRACERS_monitor_mnc) ) THEN
102  C     for ptracers than for the dynamics variables.  C      repeat printing of time to make grepping easier, default is not
103    C      to do this, because the default is to use the same monitorFreq
104    C      for ptracers as for the dynamics variables.
105           CALL MON_SET_PREF('trctime',myThid)           CALL MON_SET_PREF('trctime',myThid)
106           CALL MON_OUT_I( '_tsnumber', myIter,mon_string_none,myThid)           CALL MON_OUT_I( '_tsnumber', myIter,mon_string_none,myThid)
107           CALL MON_OUT_RL('_secondsf', myTime,mon_string_none,myThid)           CALL MON_OUT_RL('_secondsf', myTime,mon_string_none,myThid)
108          ENDIF         ENDIF
109  C       Print the basic statistics of ptracer variables  C      Print the basic statistics of ptracer variables
110         CALL MON_SET_PREF('trcstat_',myThid)         CALL MON_SET_PREF('trcstat_',myThid)
111         DO ip = 1, PTRACERS_numInUse         DO ip = 1, PTRACERS_numInUse
112           WRITE(suff,'(A7,I2.2)') 'ptracer',ip           WRITE(suff,'(A7,A2)') 'ptracer',PTRACERS_ioLabel(ip)
113           CALL MON_PRINTSTATS_RL(  c        WRITE(suff,'(A6,I4.4)') 'ptrac', ip
114       &        Nr, ptracer(1-Olx,1-Oly,1,1,1,ip),           CALL MON_WRITESTATS_RL(
115       &        suff, maskC,hFacC,rA ,drF,myThid)       &            Nr, pTracer(1-OLx,1-OLy,1,1,1,ip), suff,
116         &            hFacC, maskInC, rA ,drF, dummyRL, myThid )
117         ENDDO         ENDDO
118    
119         IF (mon_write_stdout) THEN  C--   Ptracers field monitor finish
120  C     Ptracers field monitor finish         IF ( MASTER_CPU_IO(myThid) ) THEN
121          _BEGIN_MASTER(myThid)  C-    only the master thread is allowed to switch On/Off mon_write_stdout
122  #ifdef ALLOW_USE_MPI  C     & mon_write_mnc (since it is the only thread that uses those flags):
123          IF ( .NOT. useSingleCPUIO .OR. mpiMyId .EQ. 0 ) THEN  
124  #endif /* ALLOW_USE_MPI */          IF ( mon_write_stdout ) THEN
125           WRITE(msgBuf,'(2A)') '// ==========================',           WRITE(msgBuf,'(2A)') '// ==========================',
126       &        '============================='       &        '============================='
127           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
128           WRITE(msgBuf,'(A)')           WRITE(msgBuf,'(A)')
129       &        '// End MONITOR ptracers field statistics'       &        '// End MONITOR ptracers field statistics'
130           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit,           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
      &        SQUEEZE_RIGHT , 1)  
131           WRITE(msgBuf,'(2A)') '// ==========================',           WRITE(msgBuf,'(2A)') '// ==========================',
132       &        '============================='       &        '============================='
133           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
 #ifdef ALLOW_USE_MPI  
134          ENDIF          ENDIF
 #endif /* ALLOW_USE_MPI */  
135    
136          mon_write_stdout = .FALSE.          mon_write_stdout = .FALSE.
137                    mon_write_mnc    = .FALSE.
138          _END_MASTER(myThid)  
139    C-    endif master cpu io
140         ENDIF         ENDIF
141  C     endif different multiple  
142    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
143    
144    C---  endif different multiple
145        ENDIF        ENDIF
146    
147  #endif /* ALLOW_MONITOR */  #endif /* ALLOW_MONITOR */

Legend:
Removed from v.1.2  
changed lines
  Added in v.1.18

  ViewVC Help
Powered by ViewVC 1.1.22