/[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.1 - (hide annotations) (download)
Sun Nov 28 23:50:59 2004 UTC (19 years, 6 months ago) by mlosch
Branch: MAIN
o PTRACERS:
  - rename GCHEM_MONITOR to PTRACERS_MONITOR and call it from MONITOR, so
    that ALL experiments with ptracers enable can be checked. This makes
    GCHEM_MONITOR obsolete.
  - include a runtime parameter PTRACERS_monitorFreq that defaults to
    monitorFreq
  - set default PTRACERS_write_mdsio to false if PTRACERS_write_mnc is true

1 mlosch 1.1 C $Header: $
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 "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     CML Do we need a copy of the 6D-array to the 5D-array?
101     CML DO bj = myByLo(myThid), myByHi(myThid)
102     CML DO bi = myBxLo(myThid), myBxHi(myThid)
103     CML DO k=1,Nr
104     CML DO j=1-Oly,sNy+OLy
105     CML DO i=1-Olx,sNx+Olx
106     CML tmp(i,j,k,bi,bj)=ptracer(i,j,k,bi,bj,ip)
107     CML ENDDO
108     CML ENDDO
109     CML ENDDO
110     CML ENDDO
111     CML ENDDO
112     CML CALL MON_PRINTSTATS_RL(Nr,tmp,suff,
113     CML & maskC,hFacC,rA ,drF,myThid)
114     CML It would be nice to avoid the copies. The code below works on
115     CML muliple tiles on one processor, that is, it gives the same results
116     CML as the above code which I leave for now in case something unexpected
117     CML happens on multiple processors.
118     CALL MON_PRINTSTATS_RL(
119     & Nr, ptracer(1-Olx,1-Oly,1,1,1,ip),
120     & suff, maskC,hFacC,rA ,drF,myThid)
121     ENDDO
122    
123     IF (mon_write_stdout) THEN
124     C Ptracers field monitor finish
125     _BEGIN_MASTER(myThid)
126     #ifdef ALLOW_USE_MPI
127     IF ( .NOT. useSingleCPUIO .OR. mpiMyId .EQ. 0 ) THEN
128     #endif /* ALLOW_USE_MPI */
129     WRITE(msgBuf,'(2A)') '// ==========================',
130     & '============================='
131     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
132     WRITE(msgBuf,'(A)')
133     & '// End MONITOR ptracers field statistics'
134     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit,
135     & SQUEEZE_RIGHT , 1)
136     WRITE(msgBuf,'(2A)') '// ==========================',
137     & '============================='
138     CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
139     #ifdef ALLOW_USE_MPI
140     ENDIF
141     #endif /* ALLOW_USE_MPI */
142    
143     mon_write_stdout = .FALSE.
144    
145     _END_MASTER(myThid)
146     ENDIF
147     C endif different multiple
148     ENDIF
149    
150     #endif /* ALLOW_MONITOR */
151     #endif /* ALLOW_PTRACERS */
152    
153     RETURN
154     END

  ViewVC Help
Powered by ViewVC 1.1.22