/[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.14 - (show annotations) (download)
Fri Feb 27 00:44:47 2009 UTC (15 years, 2 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 C $Header: /u/gcmpack/MITgcm/pkg/flt/flt_runga2.F,v 1.13 2009/02/10 21:30:21 jmc Exp $
2 C $Name: $
3
4 #include "FLT_OPTIONS.h"
5
6 SUBROUTINE FLT_RUNGA2 (
7 I myTime, myIter, myThid )
8
9 C ==================================================================
10 C SUBROUTINE FLT_RUNGA2
11 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
20 C !USES:
21 IMPLICIT NONE
22
23 C == global variables ==
24 #include "SIZE.h"
25 #include "EEPARAMS.h"
26 #include "PARAMS.h"
27 #include "GRID.h"
28 #include "DYNVARS.h"
29 #include "FLT.h"
30
31 C == routine arguments ==
32 _RL myTime
33 INTEGER myIter, myThid
34
35 C == Functions ==
36 c _RL FLT_MAP_R2K
37 c EXTERNAL FLT_MAP_R2K
38
39 C == local variables ==
40 INTEGER bi, bj
41 CHARACTER*(MAX_LEN_MBUF) msgBuf
42 INTEGER ip
43 INTEGER ic, jc, kc, iG, jG
44 _RL uu, vv, u1, v1
45 #ifdef ALLOW_3D_FLT
46 _RL ww, w1, ktz, kz, scalez
47 _RL kzlo, kzhi
48 #endif
49 _RL ix, jy, itx, jty
50 _RL scalex, scaley
51 #ifdef USE_FLT_ALT_NOISE
52 Real*8 PORT_RAND_NORM
53 #else
54 Real*8 PORT_RAND
55 #undef _USE_INTEGERS
56 #ifdef _USE_INTEGERS
57 INTEGER seed
58 seed = -1
59 #else
60 Real*8 seed
61 seed = -1.d0
62 #endif
63 #endif
64
65 C == end of interface ==
66
67 #ifdef ALLOW_3D_FLT
68 kzlo = 0.5 _d 0
69 kzhi = 0.5 _d 0 + DFLOAT(Nr)
70 #endif
71
72 DO bj=myByLo(myThid),myByHi(myThid)
73 DO bi=myBxLo(myThid),myBxHi(myThid)
74 DO ip=1,npart_tile(bi,bj)
75
76 C If float has died move to level 0
77 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 C Start integration between tstart and tend (individual for each float)
82 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
87 ix = ipart(ip,bi,bj)
88 jy = jpart(ip,bi,bj)
89 ic=NINT(ix)
90 jc=NINT(jy)
91 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
98 #ifdef ALLOW_3D_FLT
99 IF (iup(ip,bi,bj).EQ.-1.) THEN
100 c kz=global2local_k(kpart(ip,bi,bj),bi,bj,mjtyhid)
101
102 C recip_drF is in units 1/r (so IF r is in m this is in 1/m)
103 scalez=rkSign*recip_drF(kc)
104 C We should not do any special conversions for kz, since flt_trilinear
105 C expects it to be just a normal kpart type variable.
106 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 ELSE
111 #else /* ALLOW_3D_FLT */
112 IF ( .TRUE. ) THEN
113 #endif /* ALLOW_3D_FLT */
114 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 ENDIF
117
118 C When using this alternative scheme the noise probably should not be added twice.
119 #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 #ifdef ALLOW_3D_FLT
124 #ifdef ALLOW_FLT_3D_NOISE
125 IF (iup(ip,bi,bj).EQ.-1.) THEN
126 ww = ww + ww*(PORT_RAND(seed)-0.5)*flt_noise
127 ENDIF
128 #endif
129 #endif /* ALLOW_3D_FLT */
130 ENDIF
131 #endif
132
133 C ix and itx are in indices. Therefore it is necessary to multiply
134 C with a grid scale factor.
135
136 itx=ix+0.5*flt_deltaT*uu*scalex
137 jty=jy+0.5*flt_deltaT*vv*scaley
138
139 C Second step
140
141 #ifdef ALLOW_3D_FLT
142 IF (iup(ip,bi,bj).EQ.-1.) THEN
143 ktz=kz+0.5*flt_deltaT*ww*scalez
144 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 ELSE
148 #else /* ALLOW_3D_FLT */
149 IF ( .TRUE. ) THEN
150 #endif /* ALLOW_3D_FLT */
151 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 ENDIF
154
155 IF (iup(ip,bi,bj).NE.-2.) THEN
156 #ifdef USE_FLT_ALT_NOISE
157 u1 = u1 + port_rand_norm()*flt_noise
158 v1 = v1 + port_rand_norm()*flt_noise
159 #ifdef ALLOW_3D_FLT
160 #ifdef ALLOW_FLT_3D_NOISE
161 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 #ifdef ALLOW_3D_FLT
171 #ifdef ALLOW_FLT_3D_NOISE
172 IF (iup(ip,bi,bj).EQ.-1.) THEN
173 w1 = w1 + w1*(PORT_RAND(seed)-0.5)*flt_noise
174 ENDIF
175 #endif
176 #endif /* ALLOW_3D_FLT */
177
178 #endif /* USE_FLT_ALT_NOISE */
179 ENDIF
180
181 C ipart is in coordinates. Therefore it is necessary to multiply
182 C with a grid scale factor divided by the number grid points per
183 C geographical coordinate.
184 ipart(ip,bi,bj) = ipart(ip,bi,bj)
185 & + flt_deltaT*u1*scalex
186 jpart(ip,bi,bj) = jpart(ip,bi,bj)
187 & + flt_deltaT*v1*scaley
188 #ifdef ALLOW_3D_FLT
189 IF (iup(ip,bi,bj).EQ.-1.) THEN
190 kpart(ip,bi,bj) = kpart(ip,bi,bj)
191 & + flt_deltaT*w1*scalez
192 ENDIF
193 #endif /* ALLOW_3D_FLT */
194
195 #ifdef ALLOW_3D_FLT
196 C If float is 3D, make sure that it remains in water
197 IF (iup(ip,bi,bj).EQ.-1.) THEN
198 C reflect on surface
199 IF (kpart(ip,bi,bj).LT.kzlo) kpart(ip,bi,bj)=kzlo
200 & +kzlo-kpart(ip,bi,bj)
201 C stop at bottom
202 IF (kpart(ip,bi,bj).GT.kzhi) kpart(ip,bi,bj)=kzhi
203 ENDIF
204 #endif /* ALLOW_3D_FLT */
205 ENDIF
206 ENDIF
207
208 C- end ip loop
209 ENDDO
210 C- end bi,bj loops
211 ENDDO
212 ENDDO
213
214 RETURN
215 END

  ViewVC Help
Powered by ViewVC 1.1.22