/[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.9 - (show annotations) (download)
Tue Sep 1 19:32:27 2009 UTC (14 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62c, checkpoint62p, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62, checkpoint62b, checkpoint61v, checkpoint61w, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.8: +4 -3 lines
updated after changing MDS_WRITEVEC_LOC S/R interface

1 C $Header: /u/gcmpack/MITgcm/pkg/flt/flt_traj.F,v 1.8 2009/02/13 04:22:22 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 _RS dummyRS(1)
48 CHARACTER*(MAX_LEN_FNAM) fn
49 CHARACTER*(MAX_LEN_MBUF) msgBuf
50 CHARACTER*(80) dataFName
51 INTEGER iG,jG,IL
52 LOGICAL exst
53 LOGICAL globalFile
54
55 C == end of interface ==
56
57 fn = 'float_trajectories'
58
59 DO bj=myByLo(myThid),myByHi(myThid)
60 DO bi=myBxLo(myThid),myBxHi(myThid)
61
62 C (1) read actual number floats from file (if exists)
63 IL=ILNBLNK( fn )
64 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
65 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
66 WRITE(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
67 & fn(1:IL),'.',iG,'.',jG,'.data'
68 INQUIRE( file=dataFname, exist=exst )
69 IF (exst) THEN
70 CALL FLT_MDSREADVECTOR(fn,globalFile,precFloat64,'RL',
71 & imax,tmp,bi,bj,1,myThid)
72 npart_read = tmp(1)
73 npart_times = tmp(5)
74 ELSE
75 npart_read = 0.
76 npart_times = 0.
77 tmp(2) = myTime
78 ENDIF
79
80 C the standard routine mds_writevec_loc can be used here
81 C (2) WRITE new actual number floats and time axis into file
82 C
83 C total number of records in this file
84 tmp(1) = DBLE(npart_tile(bi,bj))+npart_read
85 C first time of writing floats (do not change when written)
86 c tmp(2) = tmp(2)
87 C current time
88 tmp(3) = myTime
89 C timestep
90 tmp(4) = flt_int_traj
91 C total number of timesteps
92 tmp(5) = npart_times + 1.
93 C total number of floats
94 tmp(6) = max_npart
95 DO ii=7,imax
96 tmp(ii) = 0.
97 ENDDO
98
99 ioUnit = -1
100 CALL MDS_WRITEVEC_LOC( fn, precFloat64, ioUnit,
101 & 'RL', imax, tmp, dummyRS,
102 & bi,bj,-1, myIter, myThid )
103
104 i0x = DFLOAT( myXGlobalLo-1 + (bi-1)*sNx )
105 j0y = DFLOAT( myYGlobalLo-1 + (bj-1)*sNy )
106 DO ip=1,npart_tile(bi,bj)
107
108 ix = ipart(ip,bi,bj)
109 jy = jpart(ip,bi,bj)
110 CALL FLT_MAP_IJLOCAL2XY( xx, yy,
111 I ix, jy, 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) = xx
117 tmp(4) = yy
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, dummyRS,
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