/[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.5 - (hide annotations) (download)
Wed May 25 04:03:10 2005 UTC (19 years ago) by edhill
Branch: MAIN
CVS Tags: checkpoint57m_post, checkpoint57k_post, checkpoint57i_post, checkpoint57n_post, checkpoint57j_post, checkpoint57l_post
Changes since 1.4: +8 -3 lines
 o for mnc output, fill the 'T' coordinate var with myTime and create a
   separate 'iter' variable for iteration count

1 edhill 1.5 C $Header: /u/gcmpack/MITgcm/pkg/ptracers/ptracers_write_timeave.F,v 1.4 2005/05/15 03:06:01 jmc 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.4 LOGICAL DIFFERENT_MULTIPLE
27     EXTERNAL DIFFERENT_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.4 IF ( DIFFERENT_MULTIPLE( PTRACERS_taveFreq, myTime, deltaTClock )
61     & ) THEN
62 mlosch 1.1
63     CML WRITE(*,*) 'EH3: myIter = ', myIter
64    
65     DO bj = myByLo(myThid), myByHi(myThid)
66     DO bi = myBxLo(myThid), myBxHi(myThid)
67     C Normalize by integrated time
68     DO iTracer=1,PTRACERS_numInUse
69     CALL TIMEAVE_NORMALIZ(
70     & ptracerFluxtave(1-Olx,1-Oly, 1,1,iTracer),
71     & ptracer_full, 1,bi,bj,myThid)
72     CALL TIMEAVE_NORMALIZ(
73     & ptracertave (1-Olx,1-Oly,1,1,1,iTracer),
74     & ptracer_half,Nr,bi,bj,myThid)
75     ENDDO
76     ENDDO
77     ENDDO
78    
79     C Write to files
80     _BARRIER
81     _BEGIN_MASTER( myThid )
82    
83     #ifdef ALLOW_MNC
84     IF (useMNC .AND. PTRACERS_write_mnc) THEN
85     CALL MNC_CW_SET_UDIM('ptr_tave', -1, myThid)
86 edhill 1.5 CALL MNC_CW_RL_W_S('D','ptr_tave',0,0,'T',myTime,myThid)
87 mlosch 1.1 CALL MNC_CW_SET_UDIM('ptr_tave', 0, myThid)
88 edhill 1.5 CALL MNC_CW_I_W_S('I','ptr_tave',0,0,'iter',myIter,myThid)
89    
90 mlosch 1.1 CALL MNC_CW_SET_UDIM('ptr_flux_tave', -1, myThid)
91 edhill 1.5 CALL MNC_CW_RL_W_S('D','ptr_flux_tave',0,0,'T',myTime,
92 mlosch 1.1 & myThid)
93     CALL MNC_CW_SET_UDIM('ptr_flux_tave', 0, myThid)
94 edhill 1.5 CALL MNC_CW_I_W_S('I','ptr_flux_tave',0,0,'iter',myIter,
95     & myThid)
96    
97 mlosch 1.1 DO ii = 1,PTRACERS_numInUse
98     CALL MNC_CW_RL_W('D','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     name(jj:jj) = ' '
102     ENDDO
103     ilnb = ILNBLNK(PTRACERS_names(ii))
104     WRITE(name,'(a,a)') 'surf_',PTRACERS_names(ii)(1:ilnb)
105     CALL MNC_CW_RL_W('D','ptr_flux_tave',0,0,name,
106     & ptracerFluxtave(1-OLx,1-OLy,1,1,ii),myThid)
107     ENDDO
108     ENDIF
109     #endif /* ALLOW_MNC */
110    
111     IF (PTRACERS_write_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     c prevPrec = writeBinaryPrec
121     c writeBinaryPrec = precFloat32
122    
123     do iTracer=1,PTRACERS_numInUse
124     WRITE(suff,'(A7,I2.2,A1,I10.10)') 'PtrFluxtave',
125     & iTracer,'.',myIter
126     CALL WRITE_FLD_XY_RL (suff,' ',
127     & ptracerFluxtave(1-Olx,1-Oly, 1,1,iTracer),
128     & myIter,myThid)
129     WRITE(suff,'(A7,I2.2,A1,I10.10)') 'PTRtave',
130     & iTracer,'.',myIter
131     CALL WRITE_FLD_XYZ_RL(suff,' ',
132     & ptracertave (1-Olx,1-Oly,1,1,1,iTracer),
133     & myIter,myThid)
134     enddo
135    
136     c writeBinaryPrec = prevPrec
137     C Reread IO error counter
138     endIOErrCount = IO_ERRCOUNT(myThid)
139    
140     C Check for IO errors
141     IF ( endIOErrCount .NE. beginIOErrCount ) THEN
142     WRITE(msgBuf,'(A)') 'S/R PTRACERS_WRITE_TIMEAVE'
143     CALL PRINT_ERROR( msgBuf, 1 )
144     WRITE(msgBuf,'(A)') 'Error writing out data'
145     CALL PRINT_ERROR( msgBuf, 1 )
146     WRITE(msgBuf,'(A,I10)') 'Timestep ',myIter
147     CALL PRINT_ERROR( msgBuf, 1 )
148     ELSE
149     WRITE(msgBuf,'(A,I10)')
150     & '// PTRACER time-average data written, t-step', myIter
151     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
152     & SQUEEZE_RIGHT, 1 )
153     WRITE(msgBuf,'(A)') ' '
154     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
155     & SQUEEZE_RIGHT, 1 )
156     ENDIF
157    
158     ENDIF
159    
160     _END_MASTER( myThid )
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