/[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.1 by mlosch, Sun Nov 28 23:50:59 2004 UTC revision 1.16 by dfer, Thu Feb 19 01:42:15 2009 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
       INTEGER time_as_int  
       integer ip  
 CML      integer i,j,k,bi,bj  
 CML      _RL tmp(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)  
52  CEOP  CEOP
53    
54        dT=deltaTclock        IF ( DIFFERENT_MULTIPLE( PTRACERS_monitorFreq,myTime,deltaTClock )
55         &   ) THEN
56    
57        IF (myIter.LE.nIter0+1.OR.DIFFERENT_MULTIPLE(  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
      &     PTRACERS_monitorFreq,myTime,myTime-dT)) THEN  
58    
59  CML       mon_write_stdout = .TRUE.  C--   Ptracers field monitor start
60            IF ( MASTER_CPU_IO(myThid) ) THEN
61    C--   only the master thread is allowed to switch On/Off mon_write_stdout
62    C     & mon_write_mnc (since it's the only thread that uses those flags):
63    
64              IF (monitor_stdio) THEN
65                mon_write_stdout = .TRUE.
66              ELSE
67                mon_write_stdout = .FALSE.
68              ENDIF
69              mon_write_mnc    = .FALSE.
70    #ifdef ALLOW_MNC
71              IF (useMNC .AND. PTRACERS_monitor_mnc) THEN
72                WRITE(mon_fname,'(A)') 'monitor_ptracer'
73                CALL MNC_CW_APPEND_VNAME(
74         &           'T', '-_-_--__-__t', 0,0, myThid)
75                CALL MNC_CW_SET_UDIM(mon_fname, -1, myThid)
76                CALL MNC_CW_RL_W_S(
77         &          'D',mon_fname,1,1,'T', myTime, myThid)
78                CALL MNC_CW_SET_UDIM(mon_fname, 0, myThid)
79                mon_write_mnc = .TRUE.
80              ENDIF
81    #endif /* ALLOW_MNC */
82    
83              IF ( mon_write_stdout ) THEN
84                WRITE(msgBuf,'(2A)') '// ==========================',
85         &             '============================='
86                CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
87                WRITE(msgBuf,'(A)')
88         &             '// Begin MONITOR ptracer field statistics'
89                CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
90                WRITE(msgBuf,'(2A)') '// ==========================',
91         &             '============================='
92                CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
93              ENDIF
94    
95  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  
96         ENDIF         ENDIF
 #endif /* ALLOW_USE_MPI */  
         _END_MASTER(myThid)  
97    
98          IF ( PTRACERS_monitorFreq .NE. monitorFreq ) THEN  C--   Ptracers field monitor : compute stats & write
99  C     repeat printing of time to make grepping easier, default is not         IF ( PTRACERS_monitorFreq .NE. monitorFreq
100  C     to do this, because the default is to use the same monitorFreq       &     .OR. (useMNC.AND.PTRACERS_monitor_mnc) ) THEN
101  C     for ptracers than for the dynamics variables.  C      repeat printing of time to make grepping easier, default is not
102    C      to do this, because the default is to use the same monitorFreq
103    C      for ptracers as for the dynamics variables.
104           CALL MON_SET_PREF('trctime',myThid)           CALL MON_SET_PREF('trctime',myThid)
105           CALL MON_OUT_I( '_tsnumber', myIter,mon_string_none,myThid)           CALL MON_OUT_I( '_tsnumber', myIter,mon_string_none,myThid)
106           CALL MON_OUT_RL('_secondsf', myTime,mon_string_none,myThid)           CALL MON_OUT_RL('_secondsf', myTime,mon_string_none,myThid)
107          ENDIF         ENDIF
108  C       Print the basic statistics of ptracer variables  C      Print the basic statistics of ptracer variables
109         CALL MON_SET_PREF('trcstat_',myThid)         CALL MON_SET_PREF('trcstat_',myThid)
110         DO ip = 1, PTRACERS_numInUse         DO ip = 1, PTRACERS_numInUse
111           WRITE(suff,'(A7,I2.2)') 'ptracer',ip           WRITE(suff,'(A7,A2)') 'ptracer',PTRACERS_ioLabel(ip)
112  CML   Do we need a copy of the 6D-array to the 5D-array?  c        WRITE(suff,'(A6,I4.4)') 'ptrac', ip
 CML         DO bj = myByLo(myThid), myByHi(myThid)  
 CML          DO bi = myBxLo(myThid), myBxHi(myThid)  
 CML           DO k=1,Nr  
 CML            DO j=1-Oly,sNy+OLy  
 CML             DO i=1-Olx,sNx+Olx  
 CML              tmp(i,j,k,bi,bj)=ptracer(i,j,k,bi,bj,ip)  
 CML             ENDDO  
 CML            ENDDO  
 CML           ENDDO  
 CML          ENDDO  
 CML         ENDDO  
 CML         CALL MON_PRINTSTATS_RL(Nr,tmp,suff,  
 CML     &                 maskC,hFacC,rA ,drF,myThid)  
 CML   It would be nice to avoid the copies. The code below works on  
 CML   muliple tiles on one processor, that is, it gives the same results  
 CML   as the above code which I leave for now in case something unexpected  
 CML   happens on multiple processors.  
113           CALL MON_PRINTSTATS_RL(           CALL MON_PRINTSTATS_RL(
114       &        Nr, ptracer(1-Olx,1-Oly,1,1,1,ip),       &        Nr, pTracer(1-Olx,1-Oly,1,1,1,ip),
115       &        suff, maskC,hFacC,rA ,drF,myThid)       &        suff, maskC,hFacC,rA ,drF,myThid)
116         ENDDO         ENDDO
117    
118         IF (mon_write_stdout) THEN  C--   Ptracers field monitor finish
119  C     Ptracers field monitor finish         IF ( MASTER_CPU_IO(myThid) ) THEN
120          _BEGIN_MASTER(myThid)  C-    only the master thread is allowed to switch On/Off mon_write_stdout
121  #ifdef ALLOW_USE_MPI  C     & mon_write_mnc (since it's the only thread that uses those flags):
122          IF ( .NOT. useSingleCPUIO .OR. mpiMyId .EQ. 0 ) THEN  
123  #endif /* ALLOW_USE_MPI */          IF ( mon_write_stdout ) THEN
124           WRITE(msgBuf,'(2A)') '// ==========================',           WRITE(msgBuf,'(2A)') '// ==========================',
125       &        '============================='       &        '============================='
126           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
127           WRITE(msgBuf,'(A)')           WRITE(msgBuf,'(A)')
128       &        '// End MONITOR ptracers field statistics'       &        '// End MONITOR ptracers field statistics'
129           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit,           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
      &        SQUEEZE_RIGHT , 1)  
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)
 #ifdef ALLOW_USE_MPI  
133          ENDIF          ENDIF
 #endif /* ALLOW_USE_MPI */  
134    
135          mon_write_stdout = .FALSE.          mon_write_stdout = .FALSE.
136                    mon_write_mnc    = .FALSE.
137          _END_MASTER(myThid)  
138    C-    endif master cpu io
139         ENDIF         ENDIF
140  C     endif different multiple  
141    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
142    
143    C---  endif different multiple
144        ENDIF        ENDIF
145    
146  #endif /* ALLOW_MONITOR */  #endif /* ALLOW_MONITOR */

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.16

  ViewVC Help
Powered by ViewVC 1.1.22