/[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.2 - (hide annotations) (download)
Mon Jul 19 15:13:07 2004 UTC (19 years, 10 months ago) by molod
Branch: MAIN
CVS Tags: checkpoint54d_post, checkpoint54e_post
Changes since 1.1: +12 -6 lines
Change argument list to port_rand - change call sequence everywhere

1 molod 1.2 C $Header: /u/u3/gcmpack/MITgcm/pkg/flt/flt_runga2.F,v 1.1 2001/09/13 17:43:56 adcroft Exp $
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     c o This routine steps floats forward with second order Runga-Kutta
17     c
18     c ==================================================================
19     c SUBROUTINE flt_runga2
20     c ==================================================================
21    
22     c == global variables ==
23    
24     #include "EEPARAMS.h"
25     #include "SIZE.h"
26     #include "DYNVARS.h"
27     #include "PARAMS.h"
28     #include "GRID.h"
29     #include "FLT.h"
30     #ifdef ALLOW_3D_FLT
31     #include "GW.h"
32     #endif
33    
34     c == routine arguments ==
35    
36     INTEGER myCurrentIter, myThid
37     _RL myCurrentTime
38     INTEGER bi, bj
39     _RL global2local_i
40     _RL global2local_j
41    
42     c == local variables ==
43    
44     integer ip, kp, iG, jG
45     _RL phi, uu, vv, u1, v1
46     #ifdef ALLOW_3D_FLT
47     _RL ww, w1, zt, zz, scalez
48     #endif
49     _RL xx, yy, xt, yt
50     _RL scalex, scaley
51     character*(max_len_mbuf) msgbuf
52     _RL npart_dist
53     Real*8 PORT_RAND
54 molod 1.2 #undef _USE_INTEGERS
55     #ifdef _USE_INTEGERS
56     integer seed
57     #else
58     Real*8 seed
59     #endif
60 adcroft 1.1
61     c == end of interface ==
62    
63     DO bj=myByLo(myThid),myByHi(myThid)
64     DO bi=myBxLo(myThid),myBxHi(myThid)
65    
66     do ip=1,npart_tile(bi,bj)
67    
68     c If float has died move to level 0
69     c
70     if(
71     & (tend(ip,bi,bj).ne.-1. .and. myCurrentTime.gt. tend(ip,bi,bj))
72     & ) then
73    
74     kpart(ip,bi,bj) = 0.
75    
76     else
77     c Start integration between tstart and tend (individual for each float)
78     c
79     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    
87     c Convert to local indices
88     c
89     xx=global2local_i(xpart(ip,bi,bj),bi,bj,mythid)
90     yy=global2local_j(ypart(ip,bi,bj),bi,bj,mythid)
91     kp=INT(kpart(ip,bi,bj))
92    
93     scalex=recip_dxF(INT(xx),INT(yy),bi,bj)
94     scaley=recip_dyF(INT(xx),INT(yy),bi,bj)
95     iG = myXGlobalLo + (bi-1)*sNx
96     jG = myYGlobalLo + (bj-1)*sNy
97    
98    
99     #ifdef ALLOW_3D_FLT
100     if (iup(ip,bi,bj).eq.-1.) then
101     scalez=recip_drF(kp)
102     zt=global2local_j(kpart(ip,bi,bj),bi,bj,mythid)
103     call flt_bilinear3D(xx,yy,uu,zp,uVel,2,bi,bj)
104     call flt_bilinear3D(xx,yy,vv,zp,vVel,3,bi,bj)
105     call flt_bilinear3D(zz,yy,ww,zp,wVel,4,bi,bj)
106     zt=zz+0.5*deltaTmom*zz*scalez
107     else
108     #endif
109     call flt_bilinear(xx,yy,uu,kp,uVel,2,bi,bj)
110     call flt_bilinear(xx,yy,vv,kp,vVel,3,bi,bj)
111     #ifdef ALLOW_3D_FLT
112     endif
113     #endif
114    
115     if (iup(ip,bi,bj).ne.-2.) then
116 molod 1.2 uu = uu + uu*(PORT_RAND(seed)-0.5)*flt_noise
117     vv = vv + vv*(PORT_RAND(seed)-0.5)*flt_noise
118 adcroft 1.1 endif
119    
120     c xx and xt are in indices. Therefore it is necessary to multiply
121     c with a grid scale factor.
122     c
123     xt=xx+0.5*deltaTmom*uu*scalex
124     yt=yy+0.5*deltaTmom*vv*scaley
125    
126     c Second step
127     c
128    
129     #ifdef ALLOW_3D_FLT
130     if (iup(ip,bi,bj).eq.-1.) then
131     call flt_bilinear3D(xt,yt,u1,zt,uVel,2,bi,bj)
132     call flt_bilinear3D(xt,yt,v1,zt,vVel,3,bi,bj)
133     call flt_bilinear3D(xx,yy,w1,zt,wVel,4,bi,bj)
134     kpart(ip,bi,bj) = kpart(ip,bi,bj) + deltaTmom*w1*scalez
135     else
136     #endif
137     call flt_bilinear(xt,yt,u1,kp,uVel,2,bi,bj)
138     call flt_bilinear(xt,yt,v1,kp,vVel,3,bi,bj)
139     #ifdef ALLOW_3D_FLT
140     endif
141     #endif
142    
143     if (iup(ip,bi,bj).ne.-2.) then
144 molod 1.2 u1 = u1 + u1*(PORT_RAND(seed)-0.5)*flt_noise
145     v1 = v1 + v1*(PORT_RAND(seed)-0.5)*flt_noise
146 adcroft 1.1 endif
147    
148     c xpart is in coordinates. Therefore it is necessary to multiply
149     c with a grid scale factor divided by the number grid points per
150     c geographical coordinate.
151     c
152     xpart(ip,bi,bj) = xpart(ip,bi,bj)
153     & + deltaTmom*u1*scalex*delX(iG)
154     ypart(ip,bi,bj) = ypart(ip,bi,bj)
155     & + deltaTmom*v1*scaley*delY(jG)
156    
157     endif
158     endif
159    
160     enddo
161    
162     ENDDO
163     ENDDO
164     c
165     return
166     end

  ViewVC Help
Powered by ViewVC 1.1.22