/[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.5 - (hide annotations) (download)
Mon Sep 13 16:13:42 2004 UTC (19 years, 8 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint57b_post, checkpoint56b_post, checkpoint57d_post, checkpoint55, checkpoint57, checkpoint56, checkpoint54f_post, checkpoint55i_post, checkpoint55c_post, checkpoint57a_post, checkpoint55g_post, checkpoint57c_post, checkpoint55d_post, checkpoint55d_pre, checkpoint57c_pre, checkpoint55j_post, checkpoint55h_post, checkpoint57e_post, checkpoint55b_post, checkpoint55f_post, eckpoint57e_pre, checkpoint56a_post, checkpoint56c_post, checkpoint57a_pre, checkpoint55a_post, checkpoint55e_post
Changes since 1.4: +13 -7 lines
 o more fixes from Antti Westerlund

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

  ViewVC Help
Powered by ViewVC 1.1.22