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

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

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


Revision 1.5 - (show annotations) (download)
Wed Dec 1 21:30:46 2004 UTC (19 years, 6 months ago) by mlosch
Branch: MAIN
Changes since 1.4: +2 -2 lines
o correct the grammar in a comment

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

  ViewVC Help
Powered by ViewVC 1.1.22