/[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.2 - (hide annotations) (download)
Mon Nov 29 00:38:37 2004 UTC (19 years, 7 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint56a_post
Changes since 1.1: +1 -19 lines
o remove superfluous comments by someone with the initials ML

1 mlosch 1.2 C $Header: /u/gcmpack/MITgcm/pkg/ptracers/ptracers_monitor.F,v 1.1 2004/11/28 23:50:59 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     CML integer i,j,k,bi,bj
53     CML _RL tmp(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
54     CEOP
55    
56     dT=deltaTclock
57    
58     IF (myIter.LE.nIter0+1.OR.DIFFERENT_MULTIPLE(
59     & PTRACERS_monitorFreq,myTime,myTime-dT)) THEN
60    
61     CML mon_write_stdout = .TRUE.
62    
63     C Ptracers field monitor start
64     _BEGIN_MASTER(myThid)
65     #ifdef ALLOW_USE_MPI
66     IF ( .NOT. useSingleCPUIO .OR. mpiMyId .EQ. 0 ) THEN
67     #endif /* ALLOW_USE_MPI */
68    
69     IF (monitor_stdio) THEN
70     WRITE(msgBuf,'(2A)') '// ==========================',
71     & '============================='
72     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
73     WRITE(msgBuf,'(A)')
74     & '// Begin MONITOR ptracer field statistics'
75     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit,
76     & SQUEEZE_RIGHT , 1)
77     WRITE(msgBuf,'(2A)') '// ==========================',
78     & '============================='
79     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
80     mon_write_stdout = .TRUE.
81     ENDIF
82    
83     #ifdef ALLOW_USE_MPI
84     ENDIF
85     #endif /* ALLOW_USE_MPI */
86     _END_MASTER(myThid)
87    
88     IF ( PTRACERS_monitorFreq .NE. monitorFreq ) THEN
89     C repeat printing of time to make grepping easier, default is not
90     C to do this, because the default is to use the same monitorFreq
91     C for ptracers than for the dynamics variables.
92     CALL MON_SET_PREF('trctime',myThid)
93     CALL MON_OUT_I( '_tsnumber', myIter,mon_string_none,myThid)
94     CALL MON_OUT_RL('_secondsf', myTime,mon_string_none,myThid)
95     ENDIF
96     C Print the basic statistics of ptracer variables
97     CALL MON_SET_PREF('trcstat_',myThid)
98     DO ip = 1, PTRACERS_numInUse
99     WRITE(suff,'(A7,I2.2)') 'ptracer',ip
100     CALL MON_PRINTSTATS_RL(
101     & Nr, ptracer(1-Olx,1-Oly,1,1,1,ip),
102     & suff, maskC,hFacC,rA ,drF,myThid)
103     ENDDO
104    
105     IF (mon_write_stdout) THEN
106     C Ptracers field monitor finish
107     _BEGIN_MASTER(myThid)
108     #ifdef ALLOW_USE_MPI
109     IF ( .NOT. useSingleCPUIO .OR. mpiMyId .EQ. 0 ) THEN
110     #endif /* ALLOW_USE_MPI */
111     WRITE(msgBuf,'(2A)') '// ==========================',
112     & '============================='
113     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
114     WRITE(msgBuf,'(A)')
115     & '// End MONITOR ptracers field statistics'
116     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit,
117     & SQUEEZE_RIGHT , 1)
118     WRITE(msgBuf,'(2A)') '// ==========================',
119     & '============================='
120     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
121     #ifdef ALLOW_USE_MPI
122     ENDIF
123     #endif /* ALLOW_USE_MPI */
124    
125     mon_write_stdout = .FALSE.
126    
127     _END_MASTER(myThid)
128     ENDIF
129     C endif different multiple
130     ENDIF
131    
132     #endif /* ALLOW_MONITOR */
133     #endif /* ALLOW_PTRACERS */
134    
135     RETURN
136     END

  ViewVC Help
Powered by ViewVC 1.1.22