/[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.3 - (show annotations) (download)
Sun Jan 4 00:58:23 2009 UTC (15 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61h
Changes since 1.2: +7 -10 lines
- clean-up
- fix restart

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

  ViewVC Help
Powered by ViewVC 1.1.22