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

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

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


Revision 1.9 - (show annotations) (download)
Mon Nov 5 18:48:04 2007 UTC (16 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint62, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59k, checkpoint59j, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.8: +2 -2 lines
split PTRACERS.h in 2 header files: PTRACERS_FIELDS.h & PTRACERS_PARAMS.h

1 C $Header: /u/gcmpack/MITgcm/pkg/ptracers/ptracers_write_timeave.F,v 1.8 2006/10/26 00:29:34 jmc Exp $
2 C $Name: $
3
4 #include "PTRACERS_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 CBOP 1
8 C !ROUTINE: PTRACERS_WRITE_TIMEAVE
9
10 C !INTERFACE:
11 SUBROUTINE PTRACERS_WRITE_TIMEAVE(myTime, myIter, myThid)
12
13 C !DESCRIPTION:
14 C At the end of average period, write the time-average
15 C state-variables on file; then reset for next period
16
17 C !USES:
18 IMPLICIT NONE
19 #include "SIZE.h"
20 #include "EEPARAMS.h"
21 #include "PARAMS.h"
22 #include "PTRACERS_SIZE.h"
23 #include "PTRACERS_PARAMS.h"
24 #include "PTRACERS_STATV.h"
25 C Functions
26 LOGICAL DIFFERENT_MULTIPLE
27 EXTERNAL DIFFERENT_MULTIPLE
28 INTEGER IO_ERRCOUNT
29 EXTERNAL IO_ERRCOUNT
30
31 C !INPUT PARAMETERS:
32 C myTime :: Current time of simulation ( s )
33 C myIter :: Iteration number
34 C myThid :: Thread number for this instance of the routine.
35 _RL myTime
36 INTEGER myIter
37 INTEGER myThid
38 CEOP
39
40 #if ( defined ALLOW_PTRACERS && defined ALLOW_TIMEAVE )
41
42 C !LOCAL VARIABLES:
43 C suff :: Hold suffix part of a filename
44 C TimeAve :: total time over average
45 CHARACTER*(MAX_LEN_FNAM) suff
46 INTEGER bi,bj, iTracer
47 INTEGER beginIOErrCount
48 INTEGER endIOErrCount
49 CHARACTER*(MAX_LEN_MBUF) msgBuf
50 #ifdef ALLOW_MNC
51 INTEGER ii,jj, ilnb
52 C Functions
53 INTEGER ILNBLNK
54 CHARACTER*(1) pf
55 #endif /* ALLOW_MNC */
56
57 C Final Time Averages and Dump Files if needed
58 IF ( DIFFERENT_MULTIPLE( PTRACERS_taveFreq, myTime, deltaTClock )
59 & ) THEN
60
61 DO bj = myByLo(myThid), myByHi(myThid)
62 DO bi = myBxLo(myThid), myBxHi(myThid)
63 C Normalize by integrated time
64 DO iTracer=1,PTRACERS_numInUse
65 CALL TIMEAVE_NORMALIZ(
66 & ptracerFluxtave(1-Olx,1-Oly, 1,1,iTracer),
67 & ptracer_full, 1,bi,bj,myThid)
68 CALL TIMEAVE_NORMALIZ(
69 & ptracertave (1-Olx,1-Oly,1,1,1,iTracer),
70 & ptracer_half,Nr,bi,bj,myThid)
71 ENDDO
72 ENDDO
73 ENDDO
74
75 C Write to files
76 _BARRIER
77
78 #ifdef ALLOW_MNC
79 IF ( PTRACERS_timeave_mnc ) THEN
80 IF ( writeBinaryPrec .EQ. precFloat64 ) THEN
81 pf(1:1) = 'D'
82 ELSE
83 pf(1:1) = 'R'
84 ENDIF
85 CALL MNC_CW_SET_UDIM('ptr_tave', -1, myThid)
86 CALL MNC_CW_RL_W_S('D','ptr_tave',0,0,'T',myTime,myThid)
87 CALL MNC_CW_SET_UDIM('ptr_tave', 0, myThid)
88 CALL MNC_CW_I_W_S('I','ptr_tave',0,0,'iter',myIter,myThid)
89
90 CALL MNC_CW_SET_UDIM('ptr_flux_tave', -1, myThid)
91 CALL MNC_CW_RL_W_S('D','ptr_flux_tave',0,0,'T',myTime,
92 & myThid)
93 CALL MNC_CW_SET_UDIM('ptr_flux_tave', 0, myThid)
94 CALL MNC_CW_I_W_S('I','ptr_flux_tave',0,0,'iter',myIter,
95 & myThid)
96
97 DO ii = 1,PTRACERS_numInUse
98 CALL MNC_CW_RL_W(pf,'ptr_tave',0,0,PTRACERS_names(ii),
99 & ptracertave(1-OLx,1-OLy,1,1,1,ii),myThid)
100 DO jj = 1,MAX_LEN_FNAM
101 suff(jj:jj) = ' '
102 ENDDO
103 ilnb = ILNBLNK(PTRACERS_names(ii))
104 WRITE(suff,'(a,a)') 'surf_',PTRACERS_names(ii)(1:ilnb)
105 CALL MNC_CW_RL_W(pf,'ptr_flux_tave',0,0,suff,
106 & ptracerFluxtave(1-OLx,1-OLy,1,1,ii),myThid)
107 ENDDO
108 ENDIF
109 #endif /* ALLOW_MNC */
110
111 IF ( PTRACERS_timeave_mdsio ) THEN
112
113 C Set IO "context" for writing state
114 #ifdef USE_DFILE
115 CALL DFILE_SET_RW
116 CALL DFILE_SET_CONT_ON_ERROR
117 #endif
118 C Read IO error counter
119 beginIOErrCount = IO_ERRCOUNT(myThid)
120
121 DO iTracer=1,PTRACERS_numInUse
122 WRITE(suff,'(A7,I2.2,A1,I10.10)') 'PtrFluxtave',
123 & iTracer,'.',myIter
124 CALL WRITE_FLD_XY_RL (suff,' ',
125 & ptracerFluxtave(1-Olx,1-Oly, 1,1,iTracer),
126 & myIter,myThid)
127 WRITE(suff,'(A7,I2.2,A1,I10.10)') 'PTRtave',
128 & iTracer,'.',myIter
129 CALL WRITE_FLD_XYZ_RL(suff,' ',
130 & ptracertave (1-Olx,1-Oly,1,1,1,iTracer),
131 & myIter,myThid)
132 ENDDO
133
134 C Reread IO error counter
135 endIOErrCount = IO_ERRCOUNT(myThid)
136
137 C Check for IO errors
138 IF ( endIOErrCount .NE. beginIOErrCount ) THEN
139 C- any thread that detects an error should report
140 WRITE(msgBuf,'(A)') 'S/R PTRACERS_WRITE_TIMEAVE'
141 CALL PRINT_ERROR( msgBuf, myThid )
142 WRITE(msgBuf,'(A)') 'Error writing out data'
143 CALL PRINT_ERROR( msgBuf, myThid )
144 WRITE(msgBuf,'(A,I10)') 'Timestep ',myIter
145 CALL PRINT_ERROR( msgBuf, myThid )
146 ELSE
147 C- normal case: 1 message is enough
148 _BEGIN_MASTER( myThid )
149 WRITE(msgBuf,'(A,I10)')
150 & '// PTRACER time-average data written, t-step', myIter
151 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
152 & SQUEEZE_RIGHT, myThid )
153 WRITE(msgBuf,'(A)') ' '
154 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
155 & SQUEEZE_RIGHT, myThid )
156 _END_MASTER( myThid )
157 ENDIF
158
159 ENDIF
160
161 _BARRIER
162
163 DO bj = myByLo(myThid), myByHi(myThid)
164 DO bi = myBxLo(myThid), myBxHi(myThid)
165
166 C Like before the 1rst iteration,
167 C ==> call TIMEAVE_STATVARS with myIter=nIter0 :
168 C 1) Reset the averages to zero ;
169 C 2) Start to cumulate state-variables with Half time step.
170
171 CALL PTRACERS_STATVARS(myTime, nIter0, bi, bj, myThid)
172
173 ENDDO
174 ENDDO
175
176 ENDIF
177
178 #endif /* ALLOW_PTRACERS and ALLOW_TIMEAVE */
179
180 RETURN
181 END

  ViewVC Help
Powered by ViewVC 1.1.22