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

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

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


Revision 1.3 - (hide annotations) (download)
Tue Sep 7 16:19:30 2004 UTC (19 years, 8 months ago) by edhill
Branch: MAIN
Changes since 1.2: +137 -76 lines
 o add Antti Westerlund's extensions to make flt work with 3D velocity
   fields

1 edhill 1.3 C $Header: /u/gcmpack/MITgcm/pkg/flt/flt_runga2.F,v 1.1 2001/09/13 17:43:56 adcroft Exp $
2 molod 1.2 C $Name: $
3 adcroft 1.1
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 edhill 1.3 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 adcroft 1.1 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 edhill 1.3 _RL global2local_k
47 adcroft 1.1 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 edhill 1.3 #ifdef USE_FLT_ALT_NOISE
59     Real*8 PORT_RAND_NORM
60     #else
61 adcroft 1.1 Real*8 PORT_RAND
62 molod 1.2 #endif
63 adcroft 1.1
64     c == end of interface ==
65    
66     DO bj=myByLo(myThid),myByHi(myThid)
67 edhill 1.3 DO bi=myBxLo(myThid),myBxHi(myThid)
68     do ip=1,npart_tile(bi,bj)
69 adcroft 1.1
70     c If float has died move to level 0
71     c
72 edhill 1.3 if(
73     & (tend(ip,bi,bj).ne.-1. .and. myCurrentTime.gt. tend(ip,bi,bj)))
74     & then
75     kpart(ip,bi,bj) = 0.
76     else
77 adcroft 1.1 c Start integration between tstart and tend (individual for each float)
78     c
79 edhill 1.3 if(
80     & (tstart(ip,bi,bj).eq.-1. .or. myCurrentTime.ge.tstart(ip,bi,bj))
81     & .and.
82     & ( tend(ip,bi,bj).eq.-1. .or. myCurrentTime.le. tend(ip,bi,bj))
83     & .and.
84     & ( iup(ip,bi,bj).ne. -3.)
85     & ) then
86 adcroft 1.1
87     c Convert to local indices
88     c
89    
90 edhill 1.3 C Note: global2local_i and global2local_j use delX and delY.
91     C This may be a problem, especially if you are using a curvilinear
92     C grid. More information below.
93     xx=global2local_i(xpart(ip,bi,bj),bi,bj,mythid)
94     yy=global2local_j(ypart(ip,bi,bj),bi,bj,mythid)
95     kp=INT(kpart(ip,bi,bj))
96    
97     scalex=recip_dxF(INT(xx),INT(yy),bi,bj)
98     scaley=recip_dyF(INT(xx),INT(yy),bi,bj)
99     iG = myXGlobalLo + (bi-1)*sNx
100     jG = myYGlobalLo + (bj-1)*sNy
101 adcroft 1.1
102    
103     #ifdef ALLOW_3D_FLT
104 edhill 1.3 if (iup(ip,bi,bj).eq.-1.) then
105     c zz=global2local_k(kpart(ip,bi,bj),bi,bj,mythid)
106    
107     c recip_drF is in units 1/r (so if r is in m this is in 1/m)
108     scalez=recip_drF(kp)
109     c We shouldn't do any special conversions for zz, since flt_trilinear
110     c expects it to be just a normal kpart type variable.
111     zz=kpart(ip,bi,bj)
112     call flt_trilinear(xx,yy,zz,uu,uVel,2,bi,bj)
113     call flt_trilinear(xx,yy,zz,vv,vVel,3,bi,bj)
114     call flt_trilinear(zz,yy,zz,ww,wVel,4,bi,bj)
115     zt=zz+0.5*deltaTmom*ww*scalez
116     else
117 adcroft 1.1 #endif
118 edhill 1.3 call flt_bilinear(xx,yy,uu,kp,uVel,2,bi,bj)
119     call flt_bilinear(xx,yy,vv,kp,vVel,3,bi,bj)
120 adcroft 1.1 #ifdef ALLOW_3D_FLT
121 edhill 1.3 endif
122 adcroft 1.1 #endif
123    
124 edhill 1.3 #ifdef USE_FLT_ALT_NOISE
125     c When using this alternative scheme the noise probably should not be added twice.
126     #else
127     if (iup(ip,bi,bj).ne.-2.) then
128     uu = uu + uu*(PORT_RAND()-0.5)*flt_noise
129     vv = vv + vv*(PORT_RAND()-0.5)*flt_noise
130     #ifdef ALLOW_3D_FLT
131     #ifdef ALLOW_FLT_3D_NOISE
132     if (iup(ip,bi,bj).eq.-1.) then
133     ww = ww + ww*(PORT_RAND()-0.5)*flt_noise
134     endif
135     #endif
136     #endif
137     endif
138     #endif
139 adcroft 1.1
140     c xx and xt are in indices. Therefore it is necessary to multiply
141     c with a grid scale factor.
142     c
143 edhill 1.3 xt=xx+0.5*deltaTmom*uu*scalex
144     yt=yy+0.5*deltaTmom*vv*scaley
145 adcroft 1.1
146     c Second step
147     c
148    
149     #ifdef ALLOW_3D_FLT
150 edhill 1.3 if (iup(ip,bi,bj).eq.-1.) then
151     call flt_trilinear(xt,yt,zt,u1,uVel,2,bi,bj)
152     call flt_trilinear(xt,yt,zt,v1,vVel,3,bi,bj)
153     call flt_trilinear(xt,yt,zt,w1,wVel,4,bi,bj)
154     else
155     #endif
156     call flt_bilinear(xt,yt,u1,kp,uVel,2,bi,bj)
157     call flt_bilinear(xt,yt,v1,kp,vVel,3,bi,bj)
158     #ifdef ALLOW_3D_FLT
159     endif
160     #endif
161    
162     if (iup(ip,bi,bj).ne.-2.) then
163     #ifdef USE_FLT_ALT_NOISE
164     u1 = u1 + port_rand_norm()*flt_noise
165     v1 = v1 + port_rand_norm()*flt_noise
166     #ifdef ALLOW_3D_FLT
167     #ifdef ALLOW_FLT_3D_NOISE
168     if (iup(ip,bi,bj).eq.-1.) then
169     w1 = w1 + port_rand_norm()*flt_noise
170     endif
171     #endif
172     #endif
173    
174     #else
175     u1 = u1 + u1*(PORT_RAND()-0.5)*flt_noise
176     v1 = v1 + v1*(PORT_RAND()-0.5)*flt_noise
177     #ifdef ALLOW_3D_FLT
178     #ifdef ALLOW_FLT_3D_NOISE
179     if (iup(ip,bi,bj).eq.-1.) then
180     w1 = w1 + w1*(PORT_RAND()-0.5)*flt_noise
181     endif
182     #endif
183     #endif
184    
185     #endif
186     endif
187 adcroft 1.1
188     c xpart is in coordinates. Therefore it is necessary to multiply
189     c with a grid scale factor divided by the number grid points per
190     c geographical coordinate.
191     c
192 edhill 1.3 C This will only work if delX & delY are available.
193     C This may be a problem, especially if you are using a curvilinear
194     C grid. In that case you have to replace them for the values of
195     C your grid, which can be troublesome.
196     xpart(ip,bi,bj) = xpart(ip,bi,bj)
197     & + deltaTmom*u1*scalex*delX(iG)
198     ypart(ip,bi,bj) = ypart(ip,bi,bj)
199     & + deltaTmom*v1*scaley*delY(jG)
200     #ifdef ALLOW_3D_FLT
201     if (iup(ip,bi,bj).eq.-1.) then
202     kpart(ip,bi,bj) = kpart(ip,bi,bj)
203     & + deltaTmom*w1*scalez
204     endif
205     #endif
206 adcroft 1.1
207 edhill 1.3 #ifdef ALLOW_3D_FLT
208     c If float is 3D, make sure that it remains in water
209     if (iup(ip,bi,bj).eq.-1.) then
210     c reflect on surface
211     if(kpart(ip,bi,bj).lt.1.0)
212     & kpart(ip,bi,bj)=1.0
213     & +abs(1.0-kpart(ip,bi,bj))
214     c stop at bottom
215     if(kpart(ip,bi,bj).gt.Nr)
216     & kpart(ip,bi,bj)=Nr
217     endif
218     #endif
219     endif
220     endif
221    
222     enddo
223     ENDDO
224 adcroft 1.1 ENDDO
225     c
226     return
227     end

  ViewVC Help
Powered by ViewVC 1.1.22