/[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.8 - (hide annotations) (download)
Thu Oct 26 00:29:34 2006 UTC (17 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58u_post, checkpoint58w_post, checkpoint58r_post, checkpoint58x_post, checkpoint58t_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59i, checkpoint59h, checkpoint59, checkpoint58y_post, checkpoint58v_post, checkpoint58s_post
Changes since 1.7: +30 -34 lines
- call pkg/rw S/R (rather than directly MDSIO)
- all threads call I/0 S/R (needed for singleCPUIO to work in multi-threaded)

1 jmc 1.8 C $Header: /u/gcmpack/MITgcm/pkg/ptracers/ptracers_write_timeave.F,v 1.7 2005/09/29 12:19:52 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.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 jmc 1.8 C myTime :: Current time of simulation ( s )
33     C myIter :: Iteration number
34 mlosch 1.1 C myThid :: Thread number for this instance of the routine.
35 jmc 1.8 _RL myTime
36     INTEGER myIter
37 mlosch 1.1 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 jmc 1.8 INTEGER bi,bj, iTracer
47 mlosch 1.1 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 edhill 1.7 CHARACTER*(1) pf
55 mlosch 1.1 #endif /* ALLOW_MNC */
56    
57     C Final Time Averages and Dump Files if needed
58 jmc 1.4 IF ( DIFFERENT_MULTIPLE( PTRACERS_taveFreq, myTime, deltaTClock )
59     & ) THEN
60 jmc 1.8
61 mlosch 1.1 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 edhill 1.6 IF ( PTRACERS_timeave_mnc ) THEN
80 edhill 1.7 IF ( writeBinaryPrec .EQ. precFloat64 ) THEN
81     pf(1:1) = 'D'
82     ELSE
83     pf(1:1) = 'R'
84     ENDIF
85 mlosch 1.1 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 edhill 1.7 CALL MNC_CW_RL_W(pf,'ptr_tave',0,0,PTRACERS_names(ii),
99 mlosch 1.1 & ptracertave(1-OLx,1-OLy,1,1,1,ii),myThid)
100     DO jj = 1,MAX_LEN_FNAM
101 jmc 1.8 suff(jj:jj) = ' '
102 mlosch 1.1 ENDDO
103     ilnb = ILNBLNK(PTRACERS_names(ii))
104 jmc 1.8 WRITE(suff,'(a,a)') 'surf_',PTRACERS_names(ii)(1:ilnb)
105     CALL MNC_CW_RL_W(pf,'ptr_flux_tave',0,0,suff,
106 mlosch 1.1 & ptracerFluxtave(1-OLx,1-OLy,1,1,ii),myThid)
107     ENDDO
108     ENDIF
109     #endif /* ALLOW_MNC */
110    
111 edhill 1.6 IF ( PTRACERS_timeave_mdsio ) THEN
112 jmc 1.8
113 mlosch 1.1 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 jmc 1.8
121     DO iTracer=1,PTRACERS_numInUse
122 mlosch 1.1 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 jmc 1.8 ENDDO
133 mlosch 1.1
134     C Reread IO error counter
135     endIOErrCount = IO_ERRCOUNT(myThid)
136 jmc 1.8
137 mlosch 1.1 C Check for IO errors
138     IF ( endIOErrCount .NE. beginIOErrCount ) THEN
139 jmc 1.8 C- any thread that detects an error should report
140 mlosch 1.1 WRITE(msgBuf,'(A)') 'S/R PTRACERS_WRITE_TIMEAVE'
141 jmc 1.8 CALL PRINT_ERROR( msgBuf, myThid )
142 mlosch 1.1 WRITE(msgBuf,'(A)') 'Error writing out data'
143 jmc 1.8 CALL PRINT_ERROR( msgBuf, myThid )
144 mlosch 1.1 WRITE(msgBuf,'(A,I10)') 'Timestep ',myIter
145 jmc 1.8 CALL PRINT_ERROR( msgBuf, myThid )
146 mlosch 1.1 ELSE
147 jmc 1.8 C- normal case: 1 message is enough
148     _BEGIN_MASTER( myThid )
149     WRITE(msgBuf,'(A,I10)')
150 mlosch 1.1 & '// PTRACER time-average data written, t-step', myIter
151 jmc 1.8 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
152     & SQUEEZE_RIGHT, myThid )
153 mlosch 1.1 WRITE(msgBuf,'(A)') ' '
154 jmc 1.8 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
155     & SQUEEZE_RIGHT, myThid )
156     _END_MASTER( myThid )
157 mlosch 1.1 ENDIF
158 jmc 1.8
159 mlosch 1.1 ENDIF
160    
161     _BARRIER
162 jmc 1.8
163 mlosch 1.1 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 jmc 1.8
178 mlosch 1.1 #endif /* ALLOW_PTRACERS and ALLOW_TIMEAVE */
179    
180     RETURN
181     END

  ViewVC Help
Powered by ViewVC 1.1.22