/[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.6 - (show annotations) (download)
Thu Feb 5 01:01:48 2009 UTC (15 years, 3 months ago) by jmc
Branch: MAIN
Changes since 1.5: +34 -25 lines
add depth & horiz. indices i,j to output files

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

  ViewVC Help
Powered by ViewVC 1.1.22