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

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

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


Revision 1.3 - (hide annotations) (download)
Wed Apr 6 18:45:48 2005 UTC (19 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57g_post, checkpoint57g_pre, checkpoint57f_post, checkpoint57h_pre, checkpoint57h_post
Changes since 1.2: +7 -7 lines
use baseTime as time origin ; DIFF_BASE_MULTIPLE replaces DIFFERENT_MULTIPLE

1 jmc 1.3 C $Header: /u/gcmpack/MITgcm/pkg/ptracers/ptracers_write_timeave.F,v 1.2 2004/12/18 02:18:56 edhill Exp $
2 mlosch 1.1 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.h"
24     #include "PTRACERS_STATV.h"
25     C Functions
26 jmc 1.3 LOGICAL DIFF_BASE_MULTIPLE
27     EXTERNAL DIFF_BASE_MULTIPLE
28 mlosch 1.1 INTEGER IO_ERRCOUNT
29     EXTERNAL IO_ERRCOUNT
30    
31     C !INPUT PARAMETERS:
32     C myThid :: Thread number for this instance of the routine.
33     C myIter :: Iteration number
34     C myTime :: Current time of simulation ( s )
35     INTEGER myThid
36     INTEGER myIter
37     _RL myTime
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     INTEGER prevPrec
46     CHARACTER*(MAX_LEN_FNAM) suff
47     _RL DDTT
48     INTEGER bi,bj,k, iTracer
49     INTEGER beginIOErrCount
50     INTEGER endIOErrCount
51     CHARACTER*(MAX_LEN_MBUF) msgBuf
52     #ifdef ALLOW_MNC
53     INTEGER ii,jj, ilnb
54     CHARACTER*(MAX_LEN_FNAM) name
55     C Functions
56     INTEGER ILNBLNK
57     #endif /* ALLOW_MNC */
58    
59     C Final Time Averages and Dump Files if needed
60 jmc 1.3 c IF ( myIter.NE.nIter0 .AND. DIFF_BASE_MULTIPLE
61     c & (baseTime,PTRACERS_taveFreq, myTime, deltaTClock) ) THEN
62     IF ( DIFF_BASE_MULTIPLE
63     & (baseTime,PTRACERS_taveFreq, myTime, deltaTClock) ) THEN
64 mlosch 1.1
65     CML WRITE(*,*) 'EH3: myIter = ', myIter
66    
67     DO bj = myByLo(myThid), myByHi(myThid)
68     DO bi = myBxLo(myThid), myBxHi(myThid)
69     C Normalize by integrated time
70     DO iTracer=1,PTRACERS_numInUse
71     CALL TIMEAVE_NORMALIZ(
72     & ptracerFluxtave(1-Olx,1-Oly, 1,1,iTracer),
73     & ptracer_full, 1,bi,bj,myThid)
74     CALL TIMEAVE_NORMALIZ(
75     & ptracertave (1-Olx,1-Oly,1,1,1,iTracer),
76     & ptracer_half,Nr,bi,bj,myThid)
77     ENDDO
78     ENDDO
79     ENDDO
80    
81     C Write to files
82     _BARRIER
83     _BEGIN_MASTER( myThid )
84    
85     #ifdef ALLOW_MNC
86     IF (useMNC .AND. PTRACERS_write_mnc) THEN
87     CALL MNC_CW_SET_UDIM('ptr_tave', -1, myThid)
88 edhill 1.2 CALL MNC_CW_I_W_S('I','ptr_tave',0,0,'T',myIter,myThid)
89 mlosch 1.1 CALL MNC_CW_SET_UDIM('ptr_tave', 0, myThid)
90     CALL MNC_CW_SET_UDIM('ptr_flux_tave', -1, myThid)
91 edhill 1.2 CALL MNC_CW_I_W_S('I','ptr_flux_tave',0,0,'T',myIter,
92 mlosch 1.1 & myThid)
93     CALL MNC_CW_SET_UDIM('ptr_flux_tave', 0, myThid)
94     DO ii = 1,PTRACERS_numInUse
95     CALL MNC_CW_RL_W('D','ptr_tave',0,0,PTRACERS_names(ii),
96     & ptracertave(1-OLx,1-OLy,1,1,1,ii),myThid)
97     DO jj = 1,MAX_LEN_FNAM
98     name(jj:jj) = ' '
99     ENDDO
100     ilnb = ILNBLNK(PTRACERS_names(ii))
101     WRITE(name,'(a,a)') 'surf_',PTRACERS_names(ii)(1:ilnb)
102     CALL MNC_CW_RL_W('D','ptr_flux_tave',0,0,name,
103     & ptracerFluxtave(1-OLx,1-OLy,1,1,ii),myThid)
104     ENDDO
105     ENDIF
106     #endif /* ALLOW_MNC */
107    
108     IF (PTRACERS_write_mdsio) THEN
109    
110     C Set IO "context" for writing state
111     #ifdef USE_DFILE
112     CALL DFILE_SET_RW
113     CALL DFILE_SET_CONT_ON_ERROR
114     #endif
115     C Read IO error counter
116     beginIOErrCount = IO_ERRCOUNT(myThid)
117     c prevPrec = writeBinaryPrec
118     c writeBinaryPrec = precFloat32
119    
120     do iTracer=1,PTRACERS_numInUse
121     WRITE(suff,'(A7,I2.2,A1,I10.10)') 'PtrFluxtave',
122     & iTracer,'.',myIter
123     CALL WRITE_FLD_XY_RL (suff,' ',
124     & ptracerFluxtave(1-Olx,1-Oly, 1,1,iTracer),
125     & myIter,myThid)
126     WRITE(suff,'(A7,I2.2,A1,I10.10)') 'PTRtave',
127     & iTracer,'.',myIter
128     CALL WRITE_FLD_XYZ_RL(suff,' ',
129     & ptracertave (1-Olx,1-Oly,1,1,1,iTracer),
130     & myIter,myThid)
131     enddo
132    
133     c writeBinaryPrec = prevPrec
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     WRITE(msgBuf,'(A)') 'S/R PTRACERS_WRITE_TIMEAVE'
140     CALL PRINT_ERROR( msgBuf, 1 )
141     WRITE(msgBuf,'(A)') 'Error writing out data'
142     CALL PRINT_ERROR( msgBuf, 1 )
143     WRITE(msgBuf,'(A,I10)') 'Timestep ',myIter
144     CALL PRINT_ERROR( msgBuf, 1 )
145     ELSE
146     WRITE(msgBuf,'(A,I10)')
147     & '// PTRACER time-average data written, t-step', myIter
148     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
149     & SQUEEZE_RIGHT, 1 )
150     WRITE(msgBuf,'(A)') ' '
151     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
152     & SQUEEZE_RIGHT, 1 )
153     ENDIF
154    
155     ENDIF
156    
157     _END_MASTER( myThid )
158     _BARRIER
159    
160     DO bj = myByLo(myThid), myByHi(myThid)
161     DO bi = myBxLo(myThid), myBxHi(myThid)
162    
163     C Like before the 1rst iteration,
164     C ==> call TIMEAVE_STATVARS with myIter=nIter0 :
165     C 1) Reset the averages to zero ;
166     C 2) Start to cumulate state-variables with Half time step.
167    
168     CALL PTRACERS_STATVARS(myTime, nIter0, bi, bj, myThid)
169    
170     ENDDO
171     ENDDO
172    
173     ENDIF
174    
175     #endif /* ALLOW_PTRACERS and ALLOW_TIMEAVE */
176    
177     RETURN
178     END

  ViewVC Help
Powered by ViewVC 1.1.22