/[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.5 - (show annotations) (download)
Tue Feb 3 23:05:46 2009 UTC (15 years, 4 months ago) by jmc
Branch: MAIN
Changes since 1.4: +14 -11 lines
more efficient I/O, using new options of mdsio_writevec_loc S/R:
 open & close & write-meta done only once (instead of 1 for each float)

1 C $Header: /u/gcmpack/MITgcm/pkg/flt/flt_traj.F,v 1.4 2009/02/01 21:10:51 jmc Exp $
2 C $Name: $
3
4 #include "FLT_OPTIONS.h"
5
6
7 SUBROUTINE FLT_TRAJ (
8 I myTime, myIter, myThid )
9
10 C ==================================================================
11 C SUBROUTINE FLT_TRAJ
12 C ==================================================================
13 C o This routine samples the model state at float position every
14 C flt_int_traj time steps and writes output.
15 C ==================================================================
16
17 C !USES:
18 IMPLICIT NONE
19
20 C == global variables ==
21 #include "SIZE.h"
22 #include "EEPARAMS.h"
23 #include "PARAMS.h"
24 #include "GRID.h"
25 #include "DYNVARS.h"
26 #include "FLT.h"
27
28 C == routine arguments ==
29 _RL myTime
30 INTEGER myIter, myThid
31
32 C === Functions ==
33 INTEGER ILNBLNK
34 _RL global2local_i
35 _RL global2local_j
36
37 C == local variables ==
38 INTEGER bi, bj, imax
39 PARAMETER (imax=10)
40 INTEGER ip, kp, ii
41 _RL xx, yy
42 _RL uu,vv,tt,ss, pp
43
44 INTEGER ioUnit, irecord
45 _RL tmp(imax)
46 _RL npart_read,npart_times
47 CHARACTER*(MAX_LEN_FNAM) fn
48 CHARACTER*(MAX_LEN_MBUF) msgBuf
49 CHARACTER*(80) dataFName
50 INTEGER iG,jG,IL
51 LOGICAL exst
52 LOGICAL globalFile
53
54 C == end of interface ==
55
56 fn = 'float_trajectories'
57
58 DO bj=myByLo(myThid),myByHi(myThid)
59 DO bi=myBxLo(myThid),myBxHi(myThid)
60
61 C (1) read actual number floats from file (if exists)
62 IL=ILNBLNK( fn )
63 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
64 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
65 WRITE(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
66 & fn(1:IL),'.',iG,'.',jG,'.data'
67 INQUIRE( file=dataFname, exist=exst )
68 IF (exst) THEN
69 CALL FLT_MDSREADVECTOR(fn,globalFile,precFloat64,'RL',
70 & imax,tmp,bi,bj,1,myThid)
71 npart_read = tmp(1)
72 npart_times = tmp(5)
73 ELSE
74 npart_read = 0.
75 npart_times = 0.
76 tmp(2) = myTime
77 ENDIF
78
79 C the standard routine mds_writevec_loc can be used here
80 C (2) WRITE new actual number floats and time axis into file
81 C
82 C total number of records in this file
83 tmp(1) = DBLE(npart_tile(bi,bj))+npart_read
84 C first time of writing floats (do not change when written)
85 c tmp(2) = tmp(2)
86 C current time
87 tmp(3) = myTime
88 C timestep
89 tmp(4) = flt_int_traj
90 C total number of timesteps
91 tmp(5) = npart_times + 1.
92 C total number of floats
93 tmp(6) = max_npart
94 DO ip=7,imax
95 tmp(ip) = 0.
96 ENDDO
97
98 ioUnit = -1
99 CALL MDS_WRITEVEC_LOC( fn, precFloat64, ioUnit,
100 & 'RL', imax, tmp,
101 & bi,bj,-1, myIter, myThid )
102
103 DO ip=1,npart_tile(bi,bj)
104
105 xx=global2local_i(xpart(ip,bi,bj),bi,bj,myThid)
106 yy=global2local_j(ypart(ip,bi,bj),bi,bj,myThid)
107 kp = NINT(kpart(ip,bi,bj))
108 tmp(1) = npart(ip,bi,bj)
109 tmp(2) = myTime
110 tmp(3) = xpart(ip,bi,bj)
111 tmp(4) = ypart(ip,bi,bj)
112 tmp(5) = kpart(ip,bi,bj)
113
114 IF ( ( myTime.GE.tstart(ip,bi,bj)) .AND.
115 & ( tend(ip,bi,bj).EQ.-1. .OR. myTime.LE.tend(ip,bi,bj))
116 & ) THEN
117
118 IF ( kp.LT.1 .OR. kp.GT.Nr ) THEN
119 WRITE(msgBuf,'(2A,I8)') '** WARNING ** FLT_TRAJ: ',
120 & ' illegal value for kp=',kp
121 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
122 & SQUEEZE_RIGHT, myThid )
123 WRITE(msgBuf,'(A,1P5E20.13)')
124 & ' FLT_TRAJ: ', (tmp(ii),ii=1,5)
125 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
126 & SQUEEZE_RIGHT, myThid )
127 c CALL PRINT_ERROR( msgBuf, myThid )
128 c STOP 'ABNORMAL END: S/R FLT_TRAJ'
129 C-- jmc: not sure if this is right but added to avoid Pb in FLT_BILINEAR:
130 kp = MIN( MAX(kp,1), Nr)
131 ENDIF
132
133 CALL FLT_BILINEAR (xx,yy,uu,uVel, kp,1,bi,bj,myThid)
134 CALL FLT_BILINEAR (xx,yy,vv,vVel, kp,2,bi,bj,myThid)
135 CALL FLT_BILINEAR2D(xx,yy,pp,etaN, 0,bi,bj,myThid)
136 CALL FLT_BILINEAR (xx,yy,tt,theta, kp,0,bi,bj,myThid)
137 CALL FLT_BILINEAR (xx,yy,ss,salt, kp,0,bi,bj,myThid)
138
139 tmp(6) = uu
140 tmp(7) = vv
141 tmp(8) = tt
142 tmp(9) = ss
143 tmp(10) = pp
144 ELSE
145 tmp(6) = flt_nan
146 tmp(7) = flt_nan
147 tmp(8) = flt_nan
148 tmp(9) = flt_nan
149 tmp(10) = flt_nan
150 ENDIF
151
152 C (3) WRITE float positions into file
153 irecord = npart_read+ip+1
154 IF ( ip.NE.npart_tile(bi,bj) ) irecord = -irecord
155 CALL MDS_WRITEVEC_LOC( fn, precFloat64, ioUnit,
156 & 'RL', imax, tmp,
157 & bi,bj,irecord, myIter, myThid )
158
159 ENDDO
160 CLOSE( ioUnit )
161
162 ENDDO
163 ENDDO
164
165 RETURN
166 END

  ViewVC Help
Powered by ViewVC 1.1.22