/[MITgcm]/MITgcm/pkg/gmredi/gmredi_calc_tensor.F
ViewVC logotype

Contents of /MITgcm/pkg/gmredi/gmredi_calc_tensor.F

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


Revision 1.15 - (show annotations) (download)
Sun Jan 12 21:35:27 2003 UTC (21 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint47i_post
Changes since 1.14: +13 -16 lines
fix few bugs and restore parameter value (e.g., Small_Number=1.D-12)
and scheme (e.g., Large_SlopeSqr=1.D+48) of checkpoint47f_post

1 C $Header: /u/gcmpack/MITgcm/pkg/gmredi/gmredi_calc_tensor.F,v 1.14 2003/01/10 00:48:39 heimbach Exp $
2 C $Name: $
3
4 #include "GMREDI_OPTIONS.h"
5
6 CStartOfInterface
7 SUBROUTINE GMREDI_CALC_TENSOR(
8 I bi, bj, iMin, iMax, jMin, jMax,
9 I sigmaX, sigmaY, sigmaR,
10 I myThid )
11 C /==========================================================\
12 C | SUBROUTINE GMREDI_CALC_TENSOR |
13 C | o Calculate tensor elements for GM/Redi tensor. |
14 C |==========================================================|
15 C \==========================================================/
16 IMPLICIT NONE
17
18 C == Global variables ==
19 #include "SIZE.h"
20 #include "GRID.h"
21 #include "DYNVARS.h"
22 #include "EEPARAMS.h"
23 #include "PARAMS.h"
24 #include "GMREDI.h"
25 #include "GMREDI_DIAGS.h"
26
27 #ifdef ALLOW_AUTODIFF_TAMC
28 #include "tamc.h"
29 #include "tamc_keys.h"
30 #endif /* ALLOW_AUTODIFF_TAMC */
31
32 C == Routine arguments ==
33 C
34 _RL sigmaX(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
35 _RL sigmaY(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
36 _RL sigmaR(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
37 INTEGER bi,bj,iMin,iMax,jMin,jMax
38 INTEGER myThid
39 CEndOfInterface
40
41 #ifdef ALLOW_GMREDI
42
43 C == Local variables ==
44 INTEGER i,j,k,kp1
45 _RL SlopeX(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
46 _RL SlopeY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
47 _RL dSigmaDx(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
48 _RL dSigmaDy(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
49 _RL dSigmaDrReal(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
50 _RL SlopeSqr(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
51 _RL taperFct(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
52 _RL maskp1, Kgm_tmp
53
54 #ifdef GM_VISBECK_VARIABLE_K
55 _RL deltaH,zero_rs
56 PARAMETER(zero_rs=0.D0)
57 _RL N2,SN
58 _RL Ssq(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
59 #endif
60
61 #ifdef ALLOW_AUTODIFF_TAMC
62 act1 = bi - myBxLo(myThid)
63 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
64 act2 = bj - myByLo(myThid)
65 max2 = myByHi(myThid) - myByLo(myThid) + 1
66 act3 = myThid - 1
67 max3 = nTx*nTy
68 act4 = ikey_dynamics - 1
69 igmkey = (act1 + 1) + act2*max1
70 & + act3*max1*max2
71 & + act4*max1*max2*max3
72 #endif /* ALLOW_AUTODIFF_TAMC */
73
74 #ifdef GM_VISBECK_VARIABLE_K
75 DO j=1-Oly,sNy+Oly
76 DO i=1-Olx,sNx+Olx
77 VisbeckK(i,j,bi,bj) = 0. _d 0
78 ENDDO
79 ENDDO
80 #endif
81
82 DO k=2,Nr
83 C-- 1rst loop on k : compute Tensor Coeff. at W points.
84
85 #ifdef ALLOW_AUTODIFF_TAMC
86 kkey = (igmkey-1)*Nr + k
87 DO j=1-Oly,sNy+Oly
88 DO i=1-Olx,sNx+Olx
89 SlopeX(i,j) = 0. _d 0
90 SlopeY(i,j) = 0. _d 0
91 dSigmaDx(i,j) = 0. _d 0
92 dSigmaDy(i,j) = 0. _d 0
93 dSigmaDrReal(i,j) = 0. _d 0
94 SlopeSqr(i,j) = 0. _d 0
95 taperFct(i,j) = 0. _d 0
96 Kwx(i,j,k,bi,bj) = 0. _d 0
97 Kwy(i,j,k,bi,bj) = 0. _d 0
98 Kwz(i,j,k,bi,bj) = 0. _d 0
99 # ifdef GM_NON_UNITY_DIAGONAL
100 Kux(i,j,k,bi,bj) = 0. _d 0
101 Kvy(i,j,k,bi,bj) = 0. _d 0
102 # endif
103 # ifdef GM_EXTRA_DIAGONAL
104 Kuz(i,j,k,bi,bj) = 0. _d 0
105 Kvz(i,j,k,bi,bj) = 0. _d 0
106 # endif
107 # ifdef GM_BOLUS_ADVEC
108 GM_PsiX(i,j,k,bi,bj) = 0. _d 0
109 GM_PsiY(i,j,k,bi,bj) = 0. _d 0
110 # endif
111 ENDDO
112 ENDDO
113 #endif
114
115 DO j=1-Oly+1,sNy+Oly-1
116 DO i=1-Olx+1,sNx+Olx-1
117 C Gradient of Sigma at rVel points
118 dSigmaDx(i,j)=op25*( sigmaX(i+1, j ,k-1) +sigmaX(i,j,k-1)
119 & +sigmaX(i+1, j , k ) +sigmaX(i,j, k ) )
120 & *maskC(i,j,k,bi,bj)
121 dSigmaDy(i,j)=op25*( sigmaY( i ,j+1,k-1) +sigmaY(i,j,k-1)
122 & +sigmaY( i ,j+1, k ) +sigmaY(i,j, k ) )
123 & *maskC(i,j,k,bi,bj)
124 dSigmaDrReal(i,j)=sigmaR(i,j,k)
125 ENDDO
126 ENDDO
127
128 #ifdef ALLOW_AUTODIFF_TAMC
129 CADJ STORE dSigmaDx(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
130 CADJ STORE dSigmaDy(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
131 CADJ STORE dsigmadrreal(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
132 #endif /* ALLOW_AUTODIFF_TAMC */
133
134 C Calculate slopes for use in tensor, taper and/or clip
135 CALL GMREDI_SLOPE_LIMIT(
136 U dSigmadRReal,
137 I rF(K),K,
138 U SlopeX, SlopeY,
139 U dSigmaDx, dSigmaDy,
140 O SlopeSqr, taperFct,
141 I bi, bj, myThid )
142
143 DO j=1-Oly+1,sNy+Oly-1
144 DO i=1-Olx+1,sNx+Olx-1
145
146 C Mask Iso-neutral slopes
147 SlopeX(i,j)=SlopeX(i,j)*maskC(i,j,k,bi,bj)
148 SlopeY(i,j)=SlopeY(i,j)*maskC(i,j,k,bi,bj)
149 SlopeSqr(i,j)=SlopeSqr(i,j)*maskC(i,j,k,bi,bj)
150
151 ENDDO
152 ENDDO
153
154 #ifdef ALLOW_AUTODIFF_TAMC
155 CADJ STORE SlopeSqr(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
156 #endif /* ALLOW_AUTODIFF_TAMC */
157
158 DO j=1-Oly+1,sNy+Oly-1
159 DO i=1-Olx+1,sNx+Olx-1
160
161 C Components of Redi/GM tensor
162 Kwx(i,j,k,bi,bj)= SlopeX(i,j)*taperFct(i,j)
163 Kwy(i,j,k,bi,bj)= SlopeY(i,j)*taperFct(i,j)
164 Kwz(i,j,k,bi,bj)= SlopeSqr(i,j)*taperFct(i,j)
165
166 #ifdef GM_VISBECK_VARIABLE_K
167
168 C- note (jmc) : moved here since only used in VISBECK_VARIABLE_K
169 C but don't know if *taperFct (or **2 ?) is necessary
170 Ssq(i,j)=SlopeSqr(i,j)*taperFct(i,j)
171
172 C-- Depth average of M^2/N^2 * N
173
174 C Calculate terms for mean Richardson number
175 C which is used in the "variable K" parameterisaton.
176 C Distance between interface above layer and the integration depth
177 deltaH=abs(GM_Visbeck_depth)-abs(rF(k))
178 C If positive we limit this to the layer thickness
179 deltaH=min(deltaH,drF(k))
180 C If negative then we are below the integration level
181 deltaH=max(deltaH,zero_rs)
182 C Now we convert deltaH to a non-dimensional fraction
183 deltaH=deltaH/GM_Visbeck_depth
184
185 IF (K.eq.2) VisbeckK(i,j,bi,bj)=0.
186 IF ( Ssq(i,j).NE.0. .AND. dSigmaDrReal(i,j).NE.0. ) THEN
187 N2= -Gravity*recip_RhoConst*dSigmaDrReal(i,j)
188 SN=sqrt(Ssq(i,j)*N2)
189 VisbeckK(i,j,bi,bj)=VisbeckK(i,j,bi,bj)+deltaH
190 & *GM_Visbeck_alpha*GM_Visbeck_length*GM_Visbeck_length*SN
191 ENDIF
192
193 #endif /* GM_VISBECK_VARIABLE_K */
194
195 ENDDO
196 ENDDO
197
198 C-- end 1rst loop on vertical level index k
199 ENDDO
200
201
202 #ifdef GM_VISBECK_VARIABLE_K
203 #ifdef ALLOW_AUTODIFF_TAMC
204 CADJ STORE VisbeckK(:,:,bi,bj) = comlev1_bibj, key=igmkey, byte=isbyte
205 #endif
206 IF ( GM_Visbeck_alpha.NE.0. ) THEN
207 C- Limit range that KapGM can take
208 DO j=1-Oly+1,sNy+Oly-1
209 DO i=1-Olx+1,sNx+Olx-1
210 VisbeckK(i,j,bi,bj)=
211 & MIN(VisbeckK(i,j,bi,bj),GM_Visbeck_maxval_K)
212 #ifdef ALLOW_TIMEAVE
213 Visbeck_K_T(i,j,bi,bj)=Visbeck_K_T(i,j,bi,bj)
214 & +VisbeckK(i,j,bi,bj)*deltaTclock
215 #endif
216 ENDDO
217 ENDDO
218 ENDIF
219 #endif /* GM_VISBECK_VARIABLE_K */
220
221
222 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
223
224 C-- 2nd loop on k : compute Tensor Coeff. at U,V levels.
225 DO k=1,Nr
226 kp1 = MIN(Nr,k+1)
227 maskp1 = 1. _d 0
228 IF (k.GE.Nr) maskp1 = 0. _d 0
229
230 #ifdef ALLOW_AUTODIFF_TAMC
231 kkey = (igmkey-1)*Nr + k
232 #ifdef GM_NON_UNITY_DIAGONAL
233 CADJ STORE Kwx(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
234 CADJ STORE Kwy(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
235 CADJ STORE Kwz(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
236 #endif
237 #endif
238
239 C- express the Tensor in term of Diffusivity (= m**2 / s )
240 DO j=1-Oly+1,sNy+Oly-1
241 DO i=1-Olx+1,sNx+Olx-1
242 Kgm_tmp = GM_isopycK + GM_skewflx*GM_background_K
243 #ifdef GM_VISBECK_VARIABLE_K
244 & + VisbeckK(i,j,bi,bj)*(1.+GM_skewflx)
245 #endif
246 Kwx(i,j,k,bi,bj)= Kgm_tmp*Kwx(i,j,k,bi,bj)
247 Kwy(i,j,k,bi,bj)= Kgm_tmp*Kwy(i,j,k,bi,bj)
248 Kwz(i,j,k,bi,bj)= ( GM_isopycK
249 #ifdef GM_VISBECK_VARIABLE_K
250 & + VisbeckK(i,j,bi,bj)
251 #endif
252 & )*Kwz(i,j,k,bi,bj)
253 ENDDO
254 ENDDO
255
256 #if ( defined (GM_NON_UNITY_DIAGONAL) || defined (GM_EXTRA_DIAGONAL) )
257
258 C Gradient of Sigma at U points
259 DO j=1-Oly+1,sNy+Oly-1
260 DO i=1-Olx+1,sNx+Olx-1
261 dSigmaDx(i,j)=sigmaX(i,j,k)
262 & *_maskW(i,j,k,bi,bj)
263 dSigmaDy(i,j)=op25*( sigmaY(i-1,j+1,k) +sigmaY(i,j+1,k)
264 & +sigmaY(i-1, j ,k) +sigmaY(i, j ,k) )
265 & *_maskW(i,j,k,bi,bj)
266 dSigmaDrReal(i,j)=op25*( sigmaR(i-1,j, k ) +sigmaR(i,j, k )
267 & +maskp1*(sigmaR(i-1,j,kp1) +sigmaR(i,j,kp1)) )
268 & *_maskW(i,j,k,bi,bj)
269 ENDDO
270 ENDDO
271
272 #ifdef ALLOW_AUTODIFF_TAMC
273 CADJ STORE dSigmaDx(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
274 CADJ STORE dSigmaDy(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
275 CADJ STORE dsigmadrreal(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
276 #endif /* ALLOW_AUTODIFF_TAMC */
277
278 C Calculate slopes for use in tensor, taper and/or clip
279 CALL GMREDI_SLOPE_LIMIT(
280 U dSigmadRReal,
281 I rF(K),K,
282 U SlopeX, SlopeY,
283 U dSigmaDx, dSigmaDy,
284 O SlopeSqr, taperFct,
285 I bi, bj, myThid )
286
287 #ifdef GM_NON_UNITY_DIAGONAL
288 DO j=1-Oly+1,sNy+Oly-1
289 DO i=1-Olx+1,sNx+Olx-1
290 Kux(i,j,k,bi,bj) =
291 & ( GM_isopycK
292 #ifdef GM_VISBECK_VARIABLE_K
293 & +op5*(VisbeckK(i,j,bi,bj)+VisbeckK(i-1,j,bi,bj))
294 #endif
295 & )
296 & *taperFct(i,j)
297 ENDDO
298 ENDDO
299 #ifdef ALLOW_AUTODIFF_TAMC
300 # ifndef GM_TAPER_ORIG_CLIPPING
301 CADJ STORE Kux(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
302 # endif
303 #endif
304 DO j=1-Oly+1,sNy+Oly-1
305 DO i=1-Olx+1,sNx+Olx-1
306 Kux(i,j,k,bi,bj) = MAX( Kux(i,j,k,bi,bj), GM_Kmin_horiz )
307 ENDDO
308 ENDDO
309 #endif /* GM_NON_UNITY_DIAGONAL */
310
311 #ifdef GM_EXTRA_DIAGONAL
312
313 #ifdef ALLOW_AUTODIFF_TAMC
314 CADJ STORE SlopeX(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
315 CADJ STORE taperFct(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
316 #endif /* ALLOW_AUTODIFF_TAMC */
317 IF (GM_ExtraDiag) THEN
318 DO j=1-Oly+1,sNy+Oly-1
319 DO i=1-Olx+1,sNx+Olx-1
320 Kuz(i,j,k,bi,bj) =
321 & ( GM_isopycK - GM_skewflx*GM_background_K
322 #ifdef GM_VISBECK_VARIABLE_K
323 & +op5*(VisbeckK(i,j,bi,bj)+VisbeckK(i-1,j,bi,bj))*GM_advect
324 #endif
325 & )*SlopeX(i,j)*taperFct(i,j)
326 ENDDO
327 ENDDO
328 ENDIF
329 #endif /* GM_EXTRA_DIAGONAL */
330
331 C Gradient of Sigma at V points
332 DO j=1-Oly+1,sNy+Oly-1
333 DO i=1-Olx+1,sNx+Olx-1
334 dSigmaDx(i,j)=op25*( sigmaX(i, j ,k) +sigmaX(i+1, j ,k)
335 & +sigmaX(i,j-1,k) +sigmaX(i+1,j-1,k) )
336 & *_maskS(i,j,k,bi,bj)
337 dSigmaDy(i,j)=sigmaY(i,j,k)
338 & *_maskS(i,j,k,bi,bj)
339 dSigmaDrReal(i,j)=op25*( sigmaR(i,j-1, k ) +sigmaR(i,j, k )
340 & +maskp1*(sigmaR(i,j-1,kp1) +sigmaR(i,j,kp1)) )
341 & *_maskS(i,j,k,bi,bj)
342 ENDDO
343 ENDDO
344
345 #ifdef ALLOW_AUTODIFF_TAMC
346 CADJ STORE dSigmaDx(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
347 CADJ STORE dSigmaDy(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
348 CADJ STORE dsigmadrreal(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
349 #endif /* ALLOW_AUTODIFF_TAMC */
350
351 C Calculate slopes for use in tensor, taper and/or clip
352 CALL GMREDI_SLOPE_LIMIT(
353 U dSigmadRReal,
354 I rF(K),K,
355 U SlopeX, SlopeY,
356 U dSigmaDx, dSigmaDy,
357 O SlopeSqr, taperFct,
358 I bi, bj, myThid )
359
360 #ifdef GM_NON_UNITY_DIAGONAL
361 DO j=1-Oly+1,sNy+Oly-1
362 DO i=1-Olx+1,sNx+Olx-1
363 Kvy(i,j,k,bi,bj) =
364 & ( GM_isopycK
365 #ifdef GM_VISBECK_VARIABLE_K
366 & +op5*(VisbeckK(i,j,bi,bj)+VisbeckK(i,j-1,bi,bj))
367 #endif
368 & )
369 & *taperFct(i,j)
370 ENDDO
371 ENDDO
372 #ifdef ALLOW_AUTODIFF_TAMC
373 # ifndef GM_TAPER_ORIG_CLIPPING
374 CADJ STORE Kvy(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
375 # endif
376 #endif
377 DO j=1-Oly+1,sNy+Oly-1
378 DO i=1-Olx+1,sNx+Olx-1
379 Kvy(i,j,k,bi,bj) = MAX( Kvy(i,j,k,bi,bj), GM_Kmin_horiz )
380 ENDDO
381 ENDDO
382 #endif /* GM_NON_UNITY_DIAGONAL */
383
384 #ifdef GM_EXTRA_DIAGONAL
385
386 #ifdef ALLOW_AUTODIFF_TAMC
387 CADJ STORE SlopeY(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
388 CADJ STORE taperFct(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
389 #endif /* ALLOW_AUTODIFF_TAMC */
390 IF (GM_ExtraDiag) THEN
391 DO j=1-Oly+1,sNy+Oly-1
392 DO i=1-Olx+1,sNx+Olx-1
393 Kvz(i,j,k,bi,bj) =
394 & ( GM_isopycK - GM_skewflx*GM_background_K
395 #ifdef GM_VISBECK_VARIABLE_K
396 & +op5*(VisbeckK(i,j,bi,bj)+VisbeckK(i,j-1,bi,bj))*GM_advect
397 #endif
398 & )*SlopeY(i,j)*taperFct(i,j)
399 ENDDO
400 ENDDO
401 ENDIF
402 #endif /* GM_EXTRA_DIAGONAL */
403
404 #endif /* GM_NON_UNITY_DIAGONAL || GM_EXTRA_DIAGONAL */
405
406 #ifdef ALLOW_TIMEAVE
407 C-- Time-average
408 DO j=1-Oly+1,sNy+Oly-1
409 DO i=1-Olx+1,sNx+Olx-1
410 GM_Kwx_T(i,j,k,bi,bj)=GM_Kwx_T(i,j,k,bi,bj)
411 & +Kwx(i,j,k,bi,bj)*deltaTclock
412 GM_Kwy_T(i,j,k,bi,bj)=GM_Kwy_T(i,j,k,bi,bj)
413 & +Kwy(i,j,k,bi,bj)*deltaTclock
414 GM_Kwz_T(i,j,k,bi,bj)=GM_Kwz_T(i,j,k,bi,bj)
415 & +Kwz(i,j,k,bi,bj)*deltaTclock
416 ENDDO
417 ENDDO
418 GM_TimeAve(k,bi,bj)=GM_TimeAve(k,bi,bj)+deltaTclock
419 #endif /* ALLOW_TIMEAVE */
420
421 C-- end 2nd loop on vertical level index k
422 ENDDO
423
424
425 #ifdef GM_BOLUS_ADVEC
426 IF (GM_AdvForm) THEN
427 CALL GMREDI_CALC_PSI_B(
428 I bi, bj, iMin, iMax, jMin, jMax,
429 I sigmaX, sigmaY, sigmaR,
430 I myThid )
431 ENDIF
432 #endif
433
434 #endif /* ALLOW_GMREDI */
435
436 RETURN
437 END
438
439
440 SUBROUTINE GMREDI_CALC_TENSOR_DUMMY(
441 I bi, bj, iMin, iMax, jMin, jMax,
442 I sigmaX, sigmaY, sigmaR,
443 I myThid )
444 C /==========================================================\
445 C | SUBROUTINE GMREDI_CALC_TENSOR |
446 C | o Calculate tensor elements for GM/Redi tensor. |
447 C |==========================================================|
448 C \==========================================================/
449 IMPLICIT NONE
450
451 C == Global variables ==
452 #include "SIZE.h"
453 #include "GRID.h"
454 #include "DYNVARS.h"
455 #include "EEPARAMS.h"
456 #include "PARAMS.h"
457 #include "GMREDI.h"
458
459 C == Routine arguments ==
460 C
461 _RL sigmaX(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
462 _RL sigmaY(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
463 _RL sigmaR(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
464 INTEGER bi,bj,iMin,iMax,jMin,jMax
465 INTEGER myThid
466 CEndOfInterface
467
468 INTEGER i, j, k
469
470 #ifdef ALLOW_GMREDI
471
472 DO k=1,Nr
473 DO j=1-Oly+1,sNy+Oly-1
474 DO i=1-Olx+1,sNx+Olx-1
475 Kwx(i,j,k,bi,bj) = 0.0
476 Kwy(i,j,k,bi,bj) = 0.0
477 Kwz(i,j,k,bi,bj) = 0.0
478 ENDDO
479 ENDDO
480 ENDDO
481 #endif /* ALLOW_GMREDI */
482
483 RETURN
484 END

  ViewVC Help
Powered by ViewVC 1.1.22