/[MITgcm]/MITgcm/pkg/flt/flt_up.F
ViewVC logotype

Contents of /MITgcm/pkg/flt/flt_up.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_up.F,v 1.8 2009/02/13 04:22:22 jmc Exp $
2 C $Name: $
3
4 #include "FLT_OPTIONS.h"
5
6 SUBROUTINE FLT_UP (
7 I myTime, myIter, myThid )
8
9 C ==================================================================
10 C SUBROUTINE FLT_UP
11 C ==================================================================
12 C o This routine moves particles vertical from the target depth to
13 C the surface and samples the model state over the full water
14 C column at horizontal float position every flt_int_prof time steps
15 C and writes output.
16 C ==================================================================
17
18 C !USES:
19 IMPLICIT NONE
20
21 C == global variables ==
22 #include "SIZE.h"
23 #include "EEPARAMS.h"
24 #include "PARAMS.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 FLT_MAP_K2R
35 EXTERNAL ILNBLNK
36 EXTERNAL FLT_MAP_K2R
37
38 C == local variables ==
39 INTEGER bi, bj
40 INTEGER imax
41 PARAMETER (imax=(9+4*Nr))
42 INTEGER ip, k, ii
43 _RL ix, jy, i0x, j0y, xx, yy, zz
44 _RL uu,vv,tt,ss, pp
45 INTEGER ioUnit, irecord
46 _RL tmp(imax)
47 _RL npart_read, npart_times
48 _RS dummyRS(1)
49 CHARACTER*(MAX_LEN_FNAM) fn
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_profiles'
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 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_prof
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 ioUnit = -1
99 CALL MDS_WRITEVEC_LOC( fn, precFloat64, ioUnit,
100 & 'RL', imax, tmp, dummyRS,
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 C Move float to the surface
108 IF ( myTime.GE.tstart(ip,bi,bj) .AND.
109 & (tend(ip,bi,bj).EQ.-1..OR.myTime.LE.tend(ip,bi,bj))
110 & .AND.
111 & kpart(ip,bi,bj).EQ.kfloat(ip,bi,bj) .AND.
112 & iup(ip,bi,bj).GT.0.
113 & ) THEN
114
115 IF ( MOD(myTime,iup(ip,bi,bj)).EQ.0.)
116 & kpart(ip,bi,bj) = flt_surf
117
118 ENDIF
119
120 C If float has died move to level 0
121 IF ( tend(ip,bi,bj).NE.-1..AND.myTime.GT.tend(ip,bi,bj)
122 & ) THEN
123 kpart(ip,bi,bj) = 0.
124 ENDIF
125
126 C Convert to coordinates
127 ix = ipart(ip,bi,bj)
128 jy = jpart(ip,bi,bj)
129 CALL FLT_MAP_IJLOCAL2XY( xx, yy,
130 I ix, jy, bi,bj, myThid )
131 zz = FLT_MAP_K2R( kpart(ip,bi,bj),bi,bj,myThid )
132
133 tmp(1) = npart(ip,bi,bj)
134 tmp(2) = myTime
135 tmp(3) = xx
136 tmp(4) = yy
137 tmp(5) = zz
138 tmp(6) = ix + i0x
139 tmp(7) = jy + j0y
140 tmp(8) = kpart(ip,bi,bj)
141
142 IF ( myTime.GE.tstart(ip,bi,bj) .AND.
143 & (tend(ip,bi,bj).EQ.-1..OR.myTime.LE.tend(ip,bi,bj))
144 & ) THEN
145
146 CALL FLT_BILINEAR2D(ix,jy,pp,etaN,0,bi,bj,myThid)
147 tmp(9) = pp
148 DO k=1,Nr
149 CALL FLT_BILINEAR (ix,jy,uu,uVel, k,1,bi,bj,myThid)
150 CALL FLT_BILINEAR (ix,jy,vv,vVel, k,2,bi,bj,myThid)
151 CALL FLT_BILINEAR (ix,jy,tt,theta, k,0,bi,bj,myThid)
152 CALL FLT_BILINEAR (ix,jy,ss,salt, k,0,bi,bj,myThid)
153 tmp(9+k) = uu
154 tmp(9+1*Nr+k) = vv
155 tmp(9+2*Nr+k) = tt
156 tmp(9+3*Nr+k) = ss
157 ENDDO
158
159 ELSE
160 DO ii=9,imax
161 tmp(ii) = flt_nan
162 ENDDO
163 ENDIF
164
165 C (3) write float positions into file
166 irecord = npart_read+ip+1
167 IF ( ip.NE.npart_tile(bi,bj) ) irecord = -irecord
168 CALL MDS_WRITEVEC_LOC( fn, precFloat64, ioUnit,
169 & 'RL', imax, tmp, dummyRS,
170 & bi,bj,irecord, myIter, myThid )
171
172 ENDDO
173 CLOSE( ioUnit )
174
175 ENDDO
176 ENDDO
177
178 RETURN
179 END

  ViewVC Help
Powered by ViewVC 1.1.22