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

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

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


Revision 1.3 - (hide annotations) (download)
Mon Nov 29 03:36:12 2004 UTC (19 years, 7 months ago) by mlosch
Branch: MAIN
Changes since 1.2: +1 -5 lines
o remove more comments

1 mlosch 1.3 C $Header: /u/gcmpack/MITgcm/pkg/ptracers/ptracers_monitor.F,v 1.2 2004/11/29 00:38:37 mlosch Exp $
2 mlosch 1.1 C $Name: $
3    
4     #include "PTRACERS_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: PTRACERS_MONITOR
8    
9     C !INTERFACE: ==========================================================
10     SUBROUTINE PTRACERS_MONITOR(
11     I myIter, myTime, myThid )
12    
13     C !DESCRIPTION:
14     C writes out ptracer statistics
15    
16     C !USES: ===============================================================
17     IMPLICIT NONE
18     #include "SIZE.h"
19     #include "EEPARAMS.h"
20     #include "PARAMS.h"
21     #include "DYNVARS.h"
22     #include "GRID.h"
23     #include "PTRACERS_SIZE.h"
24     #include "PTRACERS.h"
25     #ifdef ALLOW_MONITOR
26     #include "MONITOR.h"
27     #endif
28    
29     C !INPUT PARAMETERS: ===================================================
30     C myThid :: thread number
31     C myIter :: current timestep
32     C myTime :: current time
33     INTEGER myIter
34     _RL myTime
35     INTEGER myThid
36    
37     C === Functions ====
38     LOGICAL DIFFERENT_MULTIPLE
39     EXTERNAL DIFFERENT_MULTIPLE
40    
41     #ifdef ALLOW_PTRACERS
42     #ifdef ALLOW_MONITOR
43    
44     C !LOCAL VARIABLES: ====================================================
45     C i,j :: loop indices
46     C ip :: ptracer number
47     CHARACTER*(MAX_LEN_MBUF) msgBuf
48     CHARACTER*(MAX_LEN_MBUF) suff
49     _RL dT
50     INTEGER time_as_int
51     integer ip
52     CEOP
53    
54     dT=deltaTclock
55    
56     IF (myIter.LE.nIter0+1.OR.DIFFERENT_MULTIPLE(
57     & PTRACERS_monitorFreq,myTime,myTime-dT)) THEN
58    
59     C Ptracers field monitor start
60     _BEGIN_MASTER(myThid)
61     #ifdef ALLOW_USE_MPI
62     IF ( .NOT. useSingleCPUIO .OR. mpiMyId .EQ. 0 ) THEN
63     #endif /* ALLOW_USE_MPI */
64    
65     IF (monitor_stdio) THEN
66     WRITE(msgBuf,'(2A)') '// ==========================',
67     & '============================='
68     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
69     WRITE(msgBuf,'(A)')
70     & '// Begin MONITOR ptracer field statistics'
71     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit,
72     & SQUEEZE_RIGHT , 1)
73     WRITE(msgBuf,'(2A)') '// ==========================',
74     & '============================='
75     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
76     mon_write_stdout = .TRUE.
77     ENDIF
78    
79     #ifdef ALLOW_USE_MPI
80     ENDIF
81     #endif /* ALLOW_USE_MPI */
82     _END_MASTER(myThid)
83    
84     IF ( PTRACERS_monitorFreq .NE. monitorFreq ) THEN
85     C repeat printing of time to make grepping easier, default is not
86     C to do this, because the default is to use the same monitorFreq
87     C for ptracers than for the dynamics variables.
88     CALL MON_SET_PREF('trctime',myThid)
89     CALL MON_OUT_I( '_tsnumber', myIter,mon_string_none,myThid)
90     CALL MON_OUT_RL('_secondsf', myTime,mon_string_none,myThid)
91     ENDIF
92     C Print the basic statistics of ptracer variables
93     CALL MON_SET_PREF('trcstat_',myThid)
94     DO ip = 1, PTRACERS_numInUse
95     WRITE(suff,'(A7,I2.2)') 'ptracer',ip
96     CALL MON_PRINTSTATS_RL(
97     & Nr, ptracer(1-Olx,1-Oly,1,1,1,ip),
98     & suff, maskC,hFacC,rA ,drF,myThid)
99     ENDDO
100    
101     IF (mon_write_stdout) THEN
102     C Ptracers field monitor finish
103     _BEGIN_MASTER(myThid)
104     #ifdef ALLOW_USE_MPI
105     IF ( .NOT. useSingleCPUIO .OR. mpiMyId .EQ. 0 ) THEN
106     #endif /* ALLOW_USE_MPI */
107     WRITE(msgBuf,'(2A)') '// ==========================',
108     & '============================='
109     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
110     WRITE(msgBuf,'(A)')
111     & '// End MONITOR ptracers field statistics'
112     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit,
113     & SQUEEZE_RIGHT , 1)
114     WRITE(msgBuf,'(2A)') '// ==========================',
115     & '============================='
116     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
117     #ifdef ALLOW_USE_MPI
118     ENDIF
119     #endif /* ALLOW_USE_MPI */
120    
121     mon_write_stdout = .FALSE.
122    
123     _END_MASTER(myThid)
124     ENDIF
125     C endif different multiple
126     ENDIF
127    
128     #endif /* ALLOW_MONITOR */
129     #endif /* ALLOW_PTRACERS */
130    
131     RETURN
132     END

  ViewVC Help
Powered by ViewVC 1.1.22