/[MITgcm]/MITgcm/pkg/flt/flt_traj.F
ViewVC logotype

Contents of /MITgcm/pkg/flt/flt_traj.F

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


Revision 1.14 - (show annotations) (download)
Fri Mar 30 18:25:03 2012 UTC (12 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint64, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint65o, checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, HEAD
Changes since 1.13: +4 -4 lines
change call to ALL_PROC_DIE when within BEGIN/END_MASTER section

1 C $Header: /u/gcmpack/MITgcm/pkg/flt/flt_traj.F,v 1.13 2011/08/31 21:41:55 jmc Exp $
2 C $Name: $
3
4 #include "FLT_OPTIONS.h"
5
6 CBOP 0
7 C !ROUTINE: FLT_TRAJ
8
9 C !INTERFACE:
10 SUBROUTINE FLT_TRAJ (
11 I myTime, myIter, myThid )
12
13 C !DESCRIPTION:
14 C *==========================================================*
15 C | SUBROUTINE FLT_TRAJ
16 C | o This routine samples the model state at float position
17 C | every flt_int_traj time steps and writes output.
18 C *==========================================================*
19
20 C !USES:
21 IMPLICIT NONE
22 C == global variables ==
23 #include "SIZE.h"
24 #include "EEPARAMS.h"
25 #include "PARAMS.h"
26 #include "DYNVARS.h"
27 #include "FLT_SIZE.h"
28 #include "FLT.h"
29 #include "FLT_BUFF.h"
30 #ifdef ALLOW_EXCH2
31 #include "W2_EXCH2_SIZE.h"
32 #include "W2_EXCH2_TOPOLOGY.h"
33 #endif
34
35 C !INPUT PARAMETERS:
36 C myTime :: current time in simulation
37 C myIter :: current iteration number
38 C myThid :: my Thread Id number
39 _RL myTime
40 INTEGER myIter, myThid
41
42 C !FUNCTIONS:
43 _RL FLT_MAP_K2R
44 EXTERNAL FLT_MAP_K2R
45
46 C !LOCAL VARIABLES:
47 INTEGER bi, bj, nFlds
48 INTEGER ip, kp, ii
49 _RL ix, jy, i0x, j0y, xx, yy, zz
50 _RL uu, vv, tt, ss, pp
51
52 INTEGER imax
53 PARAMETER (imax=13)
54 _RL tmp(imax)
55 _RL npart_read, npart_times
56 _RS dummyRS(1)
57 INTEGER fp, ioUnit, irecord
58 CHARACTER*(MAX_LEN_FNAM) fn
59 CHARACTER*(MAX_LEN_MBUF) msgBuf
60 #ifdef ALLOW_EXCH2
61 INTEGER nT
62 #endif
63 CEOP
64
65 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
66
67 C-- set number of fields to write
68 nFlds = 0
69 IF ( flt_selectTrajOutp.GE.1 ) nFlds = nFlds + 8
70 IF ( flt_selectTrajOutp.GE.2 ) nFlds = nFlds + 5
71
72 C-- check buffer size
73 IF ( nFlds.GT.fltBufDim ) THEN
74 _BEGIN_MASTER(myThid)
75 WRITE(msgBuf,'(3(A,I4))') ' FLT_TRAJ: fltBufDim=', fltBufDim,
76 & ' too small (<', nFlds, ' )'
77 CALL PRINT_ERROR( msgBuf, myThid )
78 WRITE(msgBuf,'(2A)') ' FLT_TRAJ: => increase fltBufDim',
79 & ' in "FLT_SIZE.h" & recompile'
80 CALL PRINT_ERROR( msgBuf, myThid )
81 _END_MASTER(myThid)
82 CALL ALL_PROC_DIE( myThid )
83 STOP 'ABNORMAL END: S/R FLT_TRAJ'
84 ENDIF
85
86 IF ( myIter.EQ.nIter0 .OR. flt_selectTrajOutp.LE.0 ) RETURN
87
88 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
89 C-- Calculate position + other fields at float position and fill up IO-buffer
90
91 DO bj=myByLo(myThid),myByHi(myThid)
92 DO bi=myBxLo(myThid),myBxHi(myThid)
93
94 #ifdef ALLOW_EXCH2
95 nT = W2_myTileList(bi,bj)
96 i0x = DFLOAT( exch2_txGlobalo(nT) - 1 )
97 j0y = DFLOAT( exch2_tyGlobalo(nT) - 1 )
98 #else
99 i0x = DFLOAT( myXGlobalLo-1 + (bi-1)*sNx )
100 j0y = DFLOAT( myYGlobalLo-1 + (bj-1)*sNy )
101 #endif
102 DO ip=1,npart_tile(bi,bj)
103
104 ix = ipart(ip,bi,bj)
105 jy = jpart(ip,bi,bj)
106 CALL FLT_MAP_IJLOCAL2XY( xx, yy,
107 I ix, jy, bi,bj, myThid )
108 zz = FLT_MAP_K2R( kpart(ip,bi,bj),bi,bj,myThid )
109 kp = NINT(kpart(ip,bi,bj))
110 tmp(1) = npart(ip,bi,bj)
111 tmp(2) = myTime
112 tmp(3) = xx
113 tmp(4) = yy
114 tmp(5) = zz
115 tmp(6) = ix + i0x
116 tmp(7) = jy + j0y
117 tmp(8) = kpart(ip,bi,bj)
118
119 IF ( ( flt_selectTrajOutp.GE.2 ) .AND.
120 & ( myTime.GE.tstart(ip,bi,bj)) .AND.
121 & ( tend(ip,bi,bj).EQ.-1. .OR. myTime.LE.tend(ip,bi,bj))
122 & ) THEN
123 IF ( kp.LT.1 .OR. kp.GT.Nr ) THEN
124 WRITE(msgBuf,'(2A,I8)') '** WARNING ** FLT_TRAJ: ',
125 & ' illegal value for kp=',kp
126 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
127 & SQUEEZE_RIGHT, myThid )
128 WRITE(msgBuf,'(A,1P5E20.13)')
129 & ' FLT_TRAJ: ', (flt_io_buff(ii,ip,bi,bj),ii=1,5)
130 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
131 & SQUEEZE_RIGHT, myThid )
132 c CALL PRINT_ERROR( msgBuf, myThid )
133 c STOP 'ABNORMAL END: S/R FLT_TRAJ'
134 C-- jmc: not sure if this is right but added to avoid Pb in FLT_BILINEAR:
135 kp = MIN( MAX(kp,1), Nr)
136 ENDIF
137 CALL FLT_BILINEAR (ix,jy,uu,uVel, kp,1,bi,bj,myThid)
138 CALL FLT_BILINEAR (ix,jy,vv,vVel, kp,2,bi,bj,myThid)
139 CALL FLT_BILINEAR2D(ix,jy,pp,etaN, 0,bi,bj,myThid)
140 CALL FLT_BILINEAR (ix,jy,tt,theta, kp,0,bi,bj,myThid)
141 CALL FLT_BILINEAR (ix,jy,ss,salt, kp,0,bi,bj,myThid)
142 tmp( 9) = pp
143 tmp(10) = uu
144 tmp(11) = vv
145 tmp(12) = tt
146 tmp(13) = ss
147 ELSEIF ( flt_selectTrajOutp.GE.2 ) THEN
148 tmp( 9) = flt_nan
149 tmp(10) = flt_nan
150 tmp(11) = flt_nan
151 tmp(12) = flt_nan
152 tmp(13) = flt_nan
153 ENDIF
154
155 DO ii=1,nFlds
156 flt_io_buff(ii,ip,bi,bj) = tmp(ii)
157 ENDDO
158
159 ENDDO
160
161 ENDDO
162 ENDDO
163
164 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
165
166 C-- Write shared buffer to file
167
168 _BARRIER
169 _BEGIN_MASTER(myThid)
170
171 fn = 'float_trajectories'
172 fp = writeBinaryPrec
173
174 DO bj=1,nSy
175 DO bi=1,nSx
176
177 C (1) read actual number floats from file (if exists)
178 ioUnit = -2
179 CALL MDS_READVEC_LOC( fn, fp, ioUnit, 'RL', nFlds,
180 O tmp, dummyRS,
181 I bi, bj, 1, myThid )
182 IF ( ioUnit.GT. 0 ) THEN
183 npart_read = tmp(1)
184 npart_times = tmp(5)
185 ii = NINT(tmp(7))
186 C- for backward compatibility with old trajectory files:
187 IF ( ii.EQ.0 ) ii = 13
188 IF ( ii.NE.nFlds ) THEN
189 WRITE(msgBuf,'(A,I4,A)')
190 & 'FLT_TRAJ: nFlds=', nFlds,' different from'
191 CALL PRINT_ERROR( msgBuf, myThid )
192 WRITE(msgBuf,'(3A,I4,A)')
193 & 'previous file (',fn(1:18),') value =',ii
194 CALL PRINT_ERROR( msgBuf, myThid )
195 CALL ALL_PROC_DIE( 0 )
196 STOP 'ABNORMAL END: S/R FLT_TRAJ'
197 ENDIF
198 C- close the read-unit (safer to use a different unit for writing)
199 CLOSE( ioUnit )
200 ELSE
201 npart_read = 0.
202 npart_times = 0.
203 tmp(2) = myTime
204 ENDIF
205
206 C (2) write new actual number floats and time axis into file
207 C- the standard routine mds_writevec_loc can be used here
208
209 C total number of records in this file
210 tmp(1) = DBLE(npart_tile(bi,bj))+npart_read
211 C first time of writing floats (do not change when written)
212 c tmp(2) = tmp(2)
213 C current time
214 tmp(3) = myTime
215 C timestep
216 tmp(4) = flt_int_traj
217 C total number of timesteps
218 tmp(5) = npart_times + 1.
219 C total number of floats
220 tmp(6) = max_npart
221 C total number of fields
222 tmp(7) = nFlds
223 DO ii=8,nFlds
224 tmp(ii) = 0.
225 ENDDO
226 ioUnit = -1
227 CALL MDS_WRITEVEC_LOC( fn, fp, ioUnit, 'RL', nFlds,
228 & tmp, dummyRS,
229 & bi, bj, -1, myIter, myThid )
230
231 DO ip=1,npart_tile(bi,bj)
232 C (3) write float positions into file
233 irecord = npart_read+ip+1
234 IF ( ip.NE.npart_tile(bi,bj) ) irecord = -irecord
235 CALL MDS_WRITEVEC_LOC( fn, fp, ioUnit, 'RL', nFlds,
236 I flt_io_buff(1,ip,bi,bj), dummyRS,
237 I bi, bj, irecord, myIter, myThid )
238 ENDDO
239 CLOSE( ioUnit )
240
241 ENDDO
242 ENDDO
243
244 _END_MASTER(myThid)
245 _BARRIER
246
247 RETURN
248 END

  ViewVC Help
Powered by ViewVC 1.1.22