/[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.12 by jmc, Tue Aug 8 21:24:31 2006 UTC revision 1.17 by jmc, Mon Dec 21 00:17:00 2009 UTC
# Line 17  C !USES: =============================== Line 17  C !USES: ===============================
17        IMPLICIT NONE        IMPLICIT NONE
18  #include "SIZE.h"  #include "SIZE.h"
19  #include "EEPARAMS.h"  #include "EEPARAMS.h"
 #include "EESUPPORT.h"  
20  #include "PARAMS.h"  #include "PARAMS.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
# Line 37  C  myThid               :: thread number Line 37  C  myThid               :: thread number
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 47  C  ip                   :: ptracer numbe Line 49  C  ip                   :: ptracer numbe
49        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
50        CHARACTER*(MAX_LEN_MBUF) suff        CHARACTER*(MAX_LEN_MBUF) suff
51        INTEGER ip        INTEGER ip
52          _RL dummyRL(6)
53  CEOP  CEOP
54    
55        IF ( DIFFERENT_MULTIPLE( PTRACERS_monitorFreq,myTime,deltaTClock )        IF ( DIFFERENT_MULTIPLE( PTRACERS_monitorFreq,myTime,deltaTClock )
# Line 55  CEOP Line 58  CEOP
58  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
59    
60  C--   Ptracers field monitor start  C--   Ptracers field monitor start
61  #ifdef ALLOW_USE_MPI          IF ( MASTER_CPU_IO(myThid) ) THEN
62          IF ( .NOT.useSingleCPUIO .OR. mpiMyId.EQ.0 ) THEN  C--   only the master thread is allowed to switch On/Off mon_write_stdout
 #endif /* ALLOW_USE_MPI */  
           _BEGIN_MASTER(myThid)  
 C-    only the master thread is allowed to switch On/Off mon_write_stdout  
63  C     & mon_write_mnc (since it's the only thread that uses those flags):  C     & mon_write_mnc (since it's the only thread that uses those flags):
64    
65            IF (monitor_stdio) THEN            IF (monitor_stdio) THEN
# Line 74  C     & mon_write_mnc (since it's the on Line 74  C     & mon_write_mnc (since it's the on
74              CALL MNC_CW_APPEND_VNAME(              CALL MNC_CW_APPEND_VNAME(
75       &           'T', '-_-_--__-__t', 0,0, myThid)       &           'T', '-_-_--__-__t', 0,0, myThid)
76              CALL MNC_CW_SET_UDIM(mon_fname, -1, myThid)              CALL MNC_CW_SET_UDIM(mon_fname, -1, myThid)
77              CALL MNC_CW_I_W_S(              CALL MNC_CW_RL_W_S(
78       &          'I',mon_fname,1,1,'T', myIter, myThid)       &          'D',mon_fname,1,1,'T', myTime, myThid)
79              CALL MNC_CW_SET_UDIM(mon_fname, 0, myThid)              CALL MNC_CW_SET_UDIM(mon_fname, 0, myThid)
80              mon_write_mnc = .TRUE.              mon_write_mnc = .TRUE.
81            ENDIF            ENDIF
82  #endif /*  ALLOW_MNC  */  #endif /* ALLOW_MNC */
83    
84            IF ( mon_write_stdout ) THEN            IF ( mon_write_stdout ) THEN
85              WRITE(msgBuf,'(2A)') '// ==========================',              WRITE(msgBuf,'(2A)') '// ==========================',
# Line 93  C     & mon_write_mnc (since it's the on Line 93  C     & mon_write_mnc (since it's the on
93              CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)              CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
94            ENDIF            ENDIF
95    
96          _END_MASTER(myThid)  C--   endif master cpu io
 #ifdef ALLOW_USE_MPI  
97         ENDIF         ENDIF
 #endif /* ALLOW_USE_MPI */  
98    
99  C--   Ptracers field monitor : compute stats & write  C--   Ptracers field monitor : compute stats & write
100         IF ( PTRACERS_monitorFreq .NE. monitorFreq         IF ( PTRACERS_monitorFreq .NE. monitorFreq
# Line 111  C      for ptracers as for the dynamics Line 109  C      for ptracers as for the dynamics
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  c        WRITE(suff,'(A7,I3.3)') 'ptrac_', ip  c        WRITE(suff,'(A6,I4.4)') 'ptrac', ip
114           CALL MON_PRINTSTATS_RL(           CALL MON_WRITESTATS_RL(
115       &        Nr, ptracer(1-Olx,1-Oly,1,1,1,ip),       &            Nr, pTracer(1-OLx,1-OLy,1,1,1,ip), suff,
116       &        suff, maskC,hFacC,rA ,drF,myThid)       &            hFacC, maskInC, rA ,drF, dummyRL, myThid )
117         ENDDO         ENDDO
118    
119  C--   Ptracers field monitor finish  C--   Ptracers field monitor finish
120  #ifdef ALLOW_USE_MPI         IF ( MASTER_CPU_IO(myThid) ) THEN
        IF ( .NOT. useSingleCPUIO .OR. mpiMyId .EQ. 0 ) THEN  
 #endif /* ALLOW_USE_MPI */  
         _BEGIN_MASTER(myThid)  
121  C-    only the master thread is allowed to switch On/Off mon_write_stdout  C-    only the master thread is allowed to switch On/Off mon_write_stdout
122  C     & mon_write_mnc (since it's the only thread that uses those flags):  C     & mon_write_mnc (since it's the only thread that uses those flags):
123    
# Line 141  C     & mon_write_mnc (since it's the on Line 136  C     & mon_write_mnc (since it's the on
136          mon_write_stdout = .FALSE.          mon_write_stdout = .FALSE.
137          mon_write_mnc    = .FALSE.          mon_write_mnc    = .FALSE.
138    
139          _END_MASTER(myThid)  C-    endif master cpu io
 #ifdef ALLOW_USE_MPI  
140         ENDIF         ENDIF
 #endif /* ALLOW_USE_MPI */  
141    
142  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
143    
144  C     endif different multiple  C---  endif different multiple
145        ENDIF        ENDIF
146    
147  #endif /* ALLOW_MONITOR */  #endif /* ALLOW_MONITOR */

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

  ViewVC Help
Powered by ViewVC 1.1.22