/[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.8 - (show annotations) (download)
Fri Feb 13 04:22:22 2009 UTC (15 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61n, checkpoint61q, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61i, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p
Changes since 1.7: +1 -2 lines
remove unnecessary lines of code

1 C $Header: /u/gcmpack/MITgcm/pkg/flt/flt_traj.F,v 1.7 2009/02/10 21:30:21 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 "DYNVARS.h"
25 #include "FLT.h"
26
27 C == routine arguments ==
28 _RL myTime
29 INTEGER myIter, myThid
30
31 C === Functions ==
32 INTEGER ILNBLNK
33 _RL FLT_MAP_K2R
34 EXTERNAL ILNBLNK
35 EXTERNAL FLT_MAP_K2R
36
37 C == local variables ==
38 INTEGER bi, bj, imax
39 PARAMETER (imax=13)
40 INTEGER ip, kp, ii
41 _RL ix, jy, i0x, j0y, xx, yy, zz
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 ii=7,imax
95 tmp(ii) = 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 i0x = DFLOAT( myXGlobalLo-1 + (bi-1)*sNx )
104 j0y = DFLOAT( myYGlobalLo-1 + (bj-1)*sNy )
105 DO ip=1,npart_tile(bi,bj)
106
107 ix = ipart(ip,bi,bj)
108 jy = jpart(ip,bi,bj)
109 CALL FLT_MAP_IJLOCAL2XY( xx, yy,
110 I ix, jy, bi,bj, myThid )
111 zz = FLT_MAP_K2R( kpart(ip,bi,bj),bi,bj,myThid )
112 kp = NINT(kpart(ip,bi,bj))
113 tmp(1) = npart(ip,bi,bj)
114 tmp(2) = myTime
115 tmp(3) = xx
116 tmp(4) = yy
117 tmp(5) = zz
118 tmp(6) = ix + i0x
119 tmp(7) = jy + j0y
120 tmp(8) = kpart(ip,bi,bj)
121
122 IF ( ( myTime.GE.tstart(ip,bi,bj)) .AND.
123 & ( tend(ip,bi,bj).EQ.-1. .OR. myTime.LE.tend(ip,bi,bj))
124 & ) THEN
125
126 IF ( kp.LT.1 .OR. kp.GT.Nr ) THEN
127 WRITE(msgBuf,'(2A,I8)') '** WARNING ** FLT_TRAJ: ',
128 & ' illegal value for kp=',kp
129 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
130 & SQUEEZE_RIGHT, myThid )
131 WRITE(msgBuf,'(A,1P5E20.13)')
132 & ' FLT_TRAJ: ', (tmp(ii),ii=1,5)
133 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
134 & SQUEEZE_RIGHT, myThid )
135 c CALL PRINT_ERROR( msgBuf, myThid )
136 c STOP 'ABNORMAL END: S/R FLT_TRAJ'
137 C-- jmc: not sure if this is right but added to avoid Pb in FLT_BILINEAR:
138 kp = MIN( MAX(kp,1), Nr)
139 ENDIF
140
141 CALL FLT_BILINEAR (ix,jy,uu,uVel, kp,1,bi,bj,myThid)
142 CALL FLT_BILINEAR (ix,jy,vv,vVel, kp,2,bi,bj,myThid)
143 CALL FLT_BILINEAR2D(ix,jy,pp,etaN, 0,bi,bj,myThid)
144 CALL FLT_BILINEAR (ix,jy,tt,theta, kp,0,bi,bj,myThid)
145 CALL FLT_BILINEAR (ix,jy,ss,salt, kp,0,bi,bj,myThid)
146
147 tmp( 9) = pp
148 tmp(10) = uu
149 tmp(11) = vv
150 tmp(12) = tt
151 tmp(13) = ss
152 ELSE
153 tmp( 9) = flt_nan
154 tmp(10) = flt_nan
155 tmp(11) = flt_nan
156 tmp(12) = flt_nan
157 tmp(13) = flt_nan
158 ENDIF
159
160 C (3) WRITE float positions into file
161 irecord = npart_read+ip+1
162 IF ( ip.NE.npart_tile(bi,bj) ) irecord = -irecord
163 CALL MDS_WRITEVEC_LOC( fn, precFloat64, ioUnit,
164 & 'RL', imax, tmp,
165 & bi,bj,irecord, myIter, myThid )
166
167 ENDDO
168 CLOSE( ioUnit )
169
170 ENDDO
171 ENDDO
172
173 RETURN
174 END

  ViewVC Help
Powered by ViewVC 1.1.22