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

Contents of /MITgcm/pkg/flt/flt_runga2.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.6 - (show annotations) (download)
Tue Mar 1 16:52:27 2005 UTC (19 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57m_post, checkpoint57g_pre, checkpoint57s_post, checkpoint58b_post, checkpoint57g_post, checkpoint57y_post, checkpoint57r_post, checkpoint57i_post, checkpoint58, checkpoint58f_post, checkpoint57n_post, checkpoint58d_post, checkpoint58a_post, checkpoint57z_post, checkpoint58t_post, checkpoint58m_post, checkpoint57l_post, checkpoint57t_post, checkpoint57v_post, checkpoint57f_post, checkpoint57h_pre, checkpoint58w_post, checkpoint57h_post, checkpoint57y_pre, checkpoint58o_post, checkpoint58p_post, checkpoint58q_post, checkpoint58e_post, checkpoint58r_post, checkpoint58n_post, checkpoint57p_post, checkpint57u_post, checkpoint57q_post, checkpoint58k_post, checkpoint58v_post, checkpoint58l_post, checkpoint57h_done, checkpoint57j_post, checkpoint57f_pre, checkpoint58g_post, checkpoint58h_post, checkpoint58j_post, checkpoint57o_post, checkpoint57k_post, checkpoint57w_post, checkpoint58i_post, checkpoint57x_post, checkpoint58c_post, checkpoint58u_post, checkpoint58s_post
Changes since 1.5: +3 -1 lines
updated after changing port_rand function.

1 C $Header: /u/gcmpack/MITgcm/pkg/flt/flt_runga2.F,v 1.5 2004/09/13 16:13:42 edhill Exp $
2 C $Name: $
3
4 #include "FLT_CPPOPTIONS.h"
5
6 subroutine flt_runga2 (
7 I myCurrentIter,
8 I myCurrentTime,
9 I myThid
10 & )
11
12 c ==================================================================
13 c SUBROUTINE flt_runga2
14 c ==================================================================
15 c
16 c o This routine steps floats forward with second order Runge-Kutta
17 c
18 c started: Arne Biastoch
19 c
20 c changed: 2004.06.10 Antti Westerlund (antti.westerlund@helsinki.fi)
21 c and Sergio Jaramillo (sju@eos.ubc.ca)
22 c
23 c ==================================================================
24 c SUBROUTINE flt_runga2
25 c ==================================================================
26
27 c == global variables ==
28
29 #include "EEPARAMS.h"
30 #include "SIZE.h"
31 #include "DYNVARS.h"
32 #include "PARAMS.h"
33 #include "GRID.h"
34 #include "FLT.h"
35 #ifdef ALLOW_3D_FLT
36 #include "GW.h"
37 #endif
38
39 c == routine arguments ==
40
41 INTEGER myCurrentIter, myThid
42 _RL myCurrentTime
43 INTEGER bi, bj
44 _RL global2local_i
45 _RL global2local_j
46 _RL global2local_k
47 c == local variables ==
48
49 integer ip, kp, iG, jG
50 _RL phi, uu, vv, u1, v1
51 #ifdef ALLOW_3D_FLT
52 _RL ww, w1, zt, zz, scalez
53 #endif
54 _RL xx, yy, xt, yt
55 _RL scalex, scaley
56 character*(max_len_mbuf) msgbuf
57 _RL npart_dist
58 #ifdef USE_FLT_ALT_NOISE
59 Real*8 PORT_RAND_NORM
60 #else
61 Real*8 PORT_RAND
62 #undef _USE_INTEGERS
63 #ifdef _USE_INTEGERS
64 integer seed
65 seed = -1
66 #else
67 Real*8 seed
68 seed = -1.d0
69 #endif
70 #endif
71
72 c == end of interface ==
73
74 DO bj=myByLo(myThid),myByHi(myThid)
75 DO bi=myBxLo(myThid),myBxHi(myThid)
76 do ip=1,npart_tile(bi,bj)
77
78 c If float has died move to level 0
79 c
80 if(
81 & (tend(ip,bi,bj).ne.-1. .and. myCurrentTime.gt. tend(ip,bi,bj)))
82 & then
83 kpart(ip,bi,bj) = 0.
84 else
85 c Start integration between tstart and tend (individual for each float)
86 c
87 if(
88 & (tstart(ip,bi,bj).eq.-1. .or. myCurrentTime.ge.tstart(ip,bi,bj))
89 & .and.
90 & ( tend(ip,bi,bj).eq.-1. .or. myCurrentTime.le. tend(ip,bi,bj))
91 & .and.
92 & ( iup(ip,bi,bj).ne. -3.)
93 & ) then
94
95 c Convert to local indices
96 c
97
98 C Note: global2local_i and global2local_j use delX and delY.
99 C This may be a problem, especially if you are using a curvilinear
100 C grid. More information below.
101 xx=global2local_i(xpart(ip,bi,bj),bi,bj,mythid)
102 yy=global2local_j(ypart(ip,bi,bj),bi,bj,mythid)
103 kp=INT(kpart(ip,bi,bj))
104
105 scalex=recip_dxF(INT(xx),INT(yy),bi,bj)
106 scaley=recip_dyF(INT(xx),INT(yy),bi,bj)
107 iG = myXGlobalLo + (bi-1)*sNx
108 jG = myYGlobalLo + (bj-1)*sNy
109
110
111 #ifdef ALLOW_3D_FLT
112 if (iup(ip,bi,bj).eq.-1.) then
113 c zz=global2local_k(kpart(ip,bi,bj),bi,bj,mythid)
114
115 c recip_drF is in units 1/r (so if r is in m this is in 1/m)
116 scalez=recip_drF(kp)
117 c We should not do any special conversions for zz, since flt_trilinear
118 c expects it to be just a normal kpart type variable.
119 zz=kpart(ip,bi,bj)
120 call flt_trilinear(xx,yy,zz,uu,uVel,2,bi,bj)
121 call flt_trilinear(xx,yy,zz,vv,vVel,3,bi,bj)
122 call flt_trilinear(zz,yy,zz,ww,wVel,4,bi,bj)
123 zt=zz+0.5*deltaTmom*ww*scalez
124 else
125 #endif
126 call flt_bilinear(xx,yy,uu,kp,uVel,2,bi,bj)
127 call flt_bilinear(xx,yy,vv,kp,vVel,3,bi,bj)
128 #ifdef ALLOW_3D_FLT
129 endif
130 #endif
131
132 #ifdef USE_FLT_ALT_NOISE
133 c When using this alternative scheme the noise probably should not be added twice.
134 #else
135 if (iup(ip,bi,bj).ne.-2.) then
136 uu = uu + uu*(PORT_RAND(seed)-0.5)*flt_noise
137 vv = vv + vv*(PORT_RAND(seed)-0.5)*flt_noise
138 #ifdef ALLOW_3D_FLT
139 #ifdef ALLOW_FLT_3D_NOISE
140 if (iup(ip,bi,bj).eq.-1.) then
141 ww = ww + ww*(PORT_RAND(seed)-0.5)*flt_noise
142 endif
143 #endif
144 #endif
145 endif
146 #endif
147
148 c xx and xt are in indices. Therefore it is necessary to multiply
149 c with a grid scale factor.
150 c
151 xt=xx+0.5*deltaTmom*uu*scalex
152 yt=yy+0.5*deltaTmom*vv*scaley
153
154 c Second step
155 c
156
157 #ifdef ALLOW_3D_FLT
158 if (iup(ip,bi,bj).eq.-1.) then
159 call flt_trilinear(xt,yt,zt,u1,uVel,2,bi,bj)
160 call flt_trilinear(xt,yt,zt,v1,vVel,3,bi,bj)
161 call flt_trilinear(xt,yt,zt,w1,wVel,4,bi,bj)
162 else
163 #endif
164 call flt_bilinear(xt,yt,u1,kp,uVel,2,bi,bj)
165 call flt_bilinear(xt,yt,v1,kp,vVel,3,bi,bj)
166 #ifdef ALLOW_3D_FLT
167 endif
168 #endif
169
170 if (iup(ip,bi,bj).ne.-2.) then
171 #ifdef USE_FLT_ALT_NOISE
172 u1 = u1 + port_rand_norm()*flt_noise
173 v1 = v1 + port_rand_norm()*flt_noise
174 #ifdef ALLOW_3D_FLT
175 #ifdef ALLOW_FLT_3D_NOISE
176 if (iup(ip,bi,bj).eq.-1.) then
177 w1 = w1 + port_rand_norm()*flt_noise
178 endif
179 #endif
180 #endif
181
182 #else
183 u1 = u1 + u1*(PORT_RAND(seed)-0.5)*flt_noise
184 v1 = v1 + v1*(PORT_RAND(seed)-0.5)*flt_noise
185 #ifdef ALLOW_3D_FLT
186 #ifdef ALLOW_FLT_3D_NOISE
187 if (iup(ip,bi,bj).eq.-1.) then
188 w1 = w1 + w1*(PORT_RAND(seed)-0.5)*flt_noise
189 endif
190 #endif
191 #endif
192
193 #endif
194 endif
195
196 c xpart is in coordinates. Therefore it is necessary to multiply
197 c with a grid scale factor divided by the number grid points per
198 c geographical coordinate.
199 c
200 C This will only work if delX & delY are available.
201 C This may be a problem, especially if you are using a curvilinear
202 C grid. In that case you have to replace them for the values of
203 C your grid, which can be troublesome.
204 xpart(ip,bi,bj) = xpart(ip,bi,bj)
205 & + deltaTmom*u1*scalex*delX(iG)
206 ypart(ip,bi,bj) = ypart(ip,bi,bj)
207 & + deltaTmom*v1*scaley*delY(jG)
208 #ifdef ALLOW_3D_FLT
209 if (iup(ip,bi,bj).eq.-1.) then
210 kpart(ip,bi,bj) = kpart(ip,bi,bj)
211 & + deltaTmom*w1*scalez
212 endif
213 #endif
214
215 #ifdef ALLOW_3D_FLT
216 c If float is 3D, make sure that it remains in water
217 if (iup(ip,bi,bj).eq.-1.) then
218 c reflect on surface
219 if(kpart(ip,bi,bj).lt.1.0)
220 & kpart(ip,bi,bj)=1.0
221 & +abs(1.0-kpart(ip,bi,bj))
222 c stop at bottom
223 if(kpart(ip,bi,bj).gt.Nr)
224 & kpart(ip,bi,bj)=Nr
225 endif
226 #endif
227 endif
228 endif
229
230 enddo
231 ENDDO
232 ENDDO
233 c
234 return
235 end

  ViewVC Help
Powered by ViewVC 1.1.22