/[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.14 - (hide annotations) (download)
Fri Feb 27 00:44:47 2009 UTC (15 years, 3 months ago) by dfer
Branch: MAIN
CVS Tags: checkpoint62c, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62h, checkpoint62, checkpoint62b, checkpoint61n, checkpoint61q, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.13: +7 -7 lines
Add time-step for floats as run-time parameter, default = deltaTClock

1 dfer 1.14 C $Header: /u/gcmpack/MITgcm/pkg/flt/flt_runga2.F,v 1.13 2009/02/10 21:30:21 jmc Exp $
2 molod 1.2 C $Name: $
3 adcroft 1.1
4 jmc 1.8 #include "FLT_OPTIONS.h"
5 adcroft 1.1
6 jmc 1.9 SUBROUTINE FLT_RUNGA2 (
7     I myTime, myIter, myThid )
8 adcroft 1.1
9 jmc 1.9 C ==================================================================
10 jmc 1.12 C SUBROUTINE FLT_RUNGA2
11 jmc 1.9 C ==================================================================
12     C o This routine steps floats forward with second order Runge-Kutta
13     C
14     C started: Arne Biastoch
15     C
16     C changed: 2004.06.10 Antti Westerlund (antti.westerlund@helsinki.fi)
17     C and Sergio Jaramillo (sju@eos.ubc.ca)
18     C ==================================================================
19 jmc 1.12
20     C !USES:
21     IMPLICIT NONE
22 jmc 1.9
23     C == global variables ==
24 jmc 1.12 #include "SIZE.h"
25 adcroft 1.1 #include "EEPARAMS.h"
26     #include "PARAMS.h"
27     #include "GRID.h"
28 jmc 1.12 #include "DYNVARS.h"
29 adcroft 1.1 #include "FLT.h"
30    
31 jmc 1.9 C == routine arguments ==
32     _RL myTime
33     INTEGER myIter, myThid
34 adcroft 1.1
35 jmc 1.12 C == Functions ==
36 jmc 1.13 c _RL FLT_MAP_R2K
37     c EXTERNAL FLT_MAP_R2K
38 adcroft 1.1
39 jmc 1.12 C == local variables ==
40     INTEGER bi, bj
41     CHARACTER*(MAX_LEN_MBUF) msgBuf
42     INTEGER ip
43     INTEGER ic, jc, kc, iG, jG
44 jmc 1.9 _RL uu, vv, u1, v1
45 adcroft 1.1 #ifdef ALLOW_3D_FLT
46 jmc 1.13 _RL ww, w1, ktz, kz, scalez
47 jmc 1.12 _RL kzlo, kzhi
48 adcroft 1.1 #endif
49 jmc 1.13 _RL ix, jy, itx, jty
50 adcroft 1.1 _RL scalex, scaley
51 edhill 1.3 #ifdef USE_FLT_ALT_NOISE
52     Real*8 PORT_RAND_NORM
53     #else
54 adcroft 1.1 Real*8 PORT_RAND
55 edhill 1.5 #undef _USE_INTEGERS
56     #ifdef _USE_INTEGERS
57 jmc 1.9 INTEGER seed
58 jmc 1.6 seed = -1
59 edhill 1.5 #else
60     Real*8 seed
61 jmc 1.6 seed = -1.d0
62 edhill 1.5 #endif
63 molod 1.2 #endif
64 adcroft 1.1
65 jmc 1.9 C == end of interface ==
66 adcroft 1.1
67 jmc 1.12 #ifdef ALLOW_3D_FLT
68     kzlo = 0.5 _d 0
69     kzhi = 0.5 _d 0 + DFLOAT(Nr)
70     #endif
71    
72 adcroft 1.1 DO bj=myByLo(myThid),myByHi(myThid)
73 jmc 1.12 DO bi=myBxLo(myThid),myBxHi(myThid)
74     DO ip=1,npart_tile(bi,bj)
75 adcroft 1.1
76 jmc 1.9 C If float has died move to level 0
77 jmc 1.12 IF ( tend(ip,bi,bj).NE.-1. .AND. myTime.GT.tend(ip,bi,bj)
78     & ) THEN
79     kpart(ip,bi,bj) = 0.
80     ELSE
81 jmc 1.9 C Start integration between tstart and tend (individual for each float)
82 jmc 1.12 IF ( (tstart(ip,bi,bj).EQ.-1..OR.myTime.GE.tstart(ip,bi,bj))
83     & .AND.( tend(ip,bi,bj).EQ.-1..OR.myTime.LE. tend(ip,bi,bj))
84     & .AND.( iup(ip,bi,bj).NE.-3.)
85     & ) THEN
86 adcroft 1.1
87 jmc 1.13 ix = ipart(ip,bi,bj)
88     jy = jpart(ip,bi,bj)
89     ic=NINT(ix)
90     jc=NINT(jy)
91 jmc 1.12 kc=NINT(kpart(ip,bi,bj))
92    
93     scalex=recip_dxF(ic,jc,bi,bj)
94     scaley=recip_dyF(ic,jc,bi,bj)
95     iG = myXGlobalLo + (bi-1)*sNx + ic-1
96     jG = myYGlobalLo + (bj-1)*sNy + jc-1
97 adcroft 1.1
98     #ifdef ALLOW_3D_FLT
99 jmc 1.12 IF (iup(ip,bi,bj).EQ.-1.) THEN
100 jmc 1.13 c kz=global2local_k(kpart(ip,bi,bj),bi,bj,mjtyhid)
101 edhill 1.3
102 jmc 1.9 C recip_drF is in units 1/r (so IF r is in m this is in 1/m)
103 jmc 1.12 scalez=rkSign*recip_drF(kc)
104 jmc 1.13 C We should not do any special conversions for kz, since flt_trilinear
105 jmc 1.9 C expects it to be just a normal kpart type variable.
106 jmc 1.13 kz=kpart(ip,bi,bj)
107     CALL FLT_TRILINEAR(ix,jy,kz,uu,uVel,1,bi,bj,myThid)
108     CALL FLT_TRILINEAR(ix,jy,kz,vv,vVel,2,bi,bj,myThid)
109     CALL FLT_TRILINEAR(ix,jy,kz,ww,wVel,4,bi,bj,myThid)
110 jmc 1.12 ELSE
111     #else /* ALLOW_3D_FLT */
112     IF ( .TRUE. ) THEN
113     #endif /* ALLOW_3D_FLT */
114 jmc 1.13 CALL FLT_BILINEAR(ix,jy,uu,uVel,kc,1,bi,bj,myThid)
115     CALL FLT_BILINEAR(ix,jy,vv,vVel,kc,2,bi,bj,myThid)
116 jmc 1.12 ENDIF
117 adcroft 1.1
118 jmc 1.9 C When using this alternative scheme the noise probably should not be added twice.
119 jmc 1.12 #ifndef USE_FLT_ALT_NOISE
120     IF (iup(ip,bi,bj).NE.-2.) THEN
121     uu = uu + uu*(PORT_RAND(seed)-0.5)*flt_noise
122     vv = vv + vv*(PORT_RAND(seed)-0.5)*flt_noise
123 edhill 1.3 #ifdef ALLOW_3D_FLT
124     #ifdef ALLOW_FLT_3D_NOISE
125 jmc 1.12 IF (iup(ip,bi,bj).EQ.-1.) THEN
126     ww = ww + ww*(PORT_RAND(seed)-0.5)*flt_noise
127     ENDIF
128 edhill 1.3 #endif
129 jmc 1.12 #endif /* ALLOW_3D_FLT */
130     ENDIF
131 edhill 1.3 #endif
132 adcroft 1.1
133 jmc 1.13 C ix and itx are in indices. Therefore it is necessary to multiply
134 jmc 1.9 C with a grid scale factor.
135    
136 dfer 1.14 itx=ix+0.5*flt_deltaT*uu*scalex
137     jty=jy+0.5*flt_deltaT*vv*scaley
138 adcroft 1.1
139 jmc 1.9 C Second step
140    
141 adcroft 1.1 #ifdef ALLOW_3D_FLT
142 jmc 1.12 IF (iup(ip,bi,bj).EQ.-1.) THEN
143 dfer 1.14 ktz=kz+0.5*flt_deltaT*ww*scalez
144 jmc 1.13 CALL FLT_TRILINEAR(itx,jty,ktz,u1,uVel,1,bi,bj,myThid)
145     CALL FLT_TRILINEAR(itx,jty,ktz,v1,vVel,2,bi,bj,myThid)
146     CALL FLT_TRILINEAR(itx,jty,ktz,w1,wVel,4,bi,bj,myThid)
147 jmc 1.12 ELSE
148     #else /* ALLOW_3D_FLT */
149     IF ( .TRUE. ) THEN
150     #endif /* ALLOW_3D_FLT */
151 jmc 1.13 CALL FLT_BILINEAR(itx,jty,u1,uVel,kc,1,bi,bj,myThid)
152     CALL FLT_BILINEAR(itx,jty,v1,vVel,kc,2,bi,bj,myThid)
153 jmc 1.12 ENDIF
154 edhill 1.3
155 jmc 1.12 IF (iup(ip,bi,bj).NE.-2.) THEN
156 edhill 1.3 #ifdef USE_FLT_ALT_NOISE
157 jmc 1.12 u1 = u1 + port_rand_norm()*flt_noise
158     v1 = v1 + port_rand_norm()*flt_noise
159 edhill 1.3 #ifdef ALLOW_3D_FLT
160     #ifdef ALLOW_FLT_3D_NOISE
161 jmc 1.12 IF (iup(ip,bi,bj).EQ.-1.) THEN
162     w1 = w1 + port_rand_norm()*flt_noise
163     ENDIF
164     #endif
165     #endif /* ALLOW_3D_FLT */
166    
167     #else /* USE_FLT_ALT_NOISE */
168     u1 = u1 + u1*(PORT_RAND(seed)-0.5)*flt_noise
169     v1 = v1 + v1*(PORT_RAND(seed)-0.5)*flt_noise
170 edhill 1.3 #ifdef ALLOW_3D_FLT
171     #ifdef ALLOW_FLT_3D_NOISE
172 jmc 1.12 IF (iup(ip,bi,bj).EQ.-1.) THEN
173     w1 = w1 + w1*(PORT_RAND(seed)-0.5)*flt_noise
174     ENDIF
175 edhill 1.3 #endif
176 jmc 1.12 #endif /* ALLOW_3D_FLT */
177 edhill 1.3
178 jmc 1.12 #endif /* USE_FLT_ALT_NOISE */
179     ENDIF
180 adcroft 1.1
181 jmc 1.13 C ipart is in coordinates. Therefore it is necessary to multiply
182 jmc 1.9 C with a grid scale factor divided by the number grid points per
183     C geographical coordinate.
184 jmc 1.13 ipart(ip,bi,bj) = ipart(ip,bi,bj)
185 dfer 1.14 & + flt_deltaT*u1*scalex
186 jmc 1.13 jpart(ip,bi,bj) = jpart(ip,bi,bj)
187 dfer 1.14 & + flt_deltaT*v1*scaley
188 jmc 1.12 #ifdef ALLOW_3D_FLT
189     IF (iup(ip,bi,bj).EQ.-1.) THEN
190     kpart(ip,bi,bj) = kpart(ip,bi,bj)
191 dfer 1.14 & + flt_deltaT*w1*scalez
192 jmc 1.12 ENDIF
193     #endif /* ALLOW_3D_FLT */
194 adcroft 1.1
195 edhill 1.3 #ifdef ALLOW_3D_FLT
196 jmc 1.9 C If float is 3D, make sure that it remains in water
197 jmc 1.12 IF (iup(ip,bi,bj).EQ.-1.) THEN
198 jmc 1.9 C reflect on surface
199 jmc 1.12 IF (kpart(ip,bi,bj).LT.kzlo) kpart(ip,bi,bj)=kzlo
200     & +kzlo-kpart(ip,bi,bj)
201 jmc 1.9 C stop at bottom
202 jmc 1.12 IF (kpart(ip,bi,bj).GT.kzhi) kpart(ip,bi,bj)=kzhi
203     ENDIF
204     #endif /* ALLOW_3D_FLT */
205     ENDIF
206     ENDIF
207 jmc 1.9
208 jmc 1.12 C- end ip loop
209 edhill 1.3 ENDDO
210 jmc 1.12 C- end bi,bj loops
211     ENDDO
212 adcroft 1.1 ENDDO
213 jmc 1.9
214     RETURN
215     END

  ViewVC Help
Powered by ViewVC 1.1.22