/[MITgcm]/MITgcm/pkg/shap_filt/shap_filt_tracer_s2.F
ViewVC logotype

Contents of /MITgcm/pkg/shap_filt/shap_filt_tracer_s2.F

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


Revision 1.15 - (show annotations) (download)
Tue Apr 28 18:20:30 2009 UTC (15 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62c, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62w, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint63g, checkpoint64, checkpoint62, checkpoint63, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint62b, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint61n, checkpoint61q, checkpoint61o, checkpoint61m, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.14: +5 -5 lines
change macros (EXCH & GLOBAL_SUM/MAX) sufix _R4/_R8 to _RS/_RL
 when applied to _RS/_RL variable

1 C $Header: /u/gcmpack/MITgcm/pkg/shap_filt/shap_filt_tracer_s2.F,v 1.14 2008/10/22 00:28:47 jmc Exp $
2 C $Name: $
3
4 #include "SHAP_FILT_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: SHAP_FILT_TRACER_S2
8 C !INTERFACE:
9 SUBROUTINE SHAP_FILT_TRACER_S2(
10 U field, tmpFld,
11 I nShapTr, exchInOut, kSize,
12 I myTime, myIter, myThid )
13 C !DESCRIPTION: \bv
14 C *==========================================================*
15 C | S/R SHAP_FILT_TRACER_S2
16 C | o Applies Shapiro filter to 2D field (cell center).
17 C | o use filtering function "S2" = [1 - (d_xx+d_yy)^n]
18 C | o Options for computational filter (no grid spacing)
19 C | or physical space filter (with grid spacing) or both.
20 C *==========================================================*
21 C \ev
22
23 C !USES:
24 IMPLICIT NONE
25
26 C == Global variables ===
27 #include "SIZE.h"
28 #include "EEPARAMS.h"
29 #include "PARAMS.h"
30 #include "GRID.h"
31 #include "SHAP_FILT.h"
32
33 C !INPUT/OUTPUT PARAMETERS:
34 C == Routine arguments
35 C field :: cell-centered 2D field on which filter applies
36 C tmpFld :: working temporary array
37 C nShapTr :: (total) power of the filter for this tracer
38 C exchInOut :: apply Exchanges to fill overlap region:
39 C = 0 : do not apply Exch on neither input nor output field
40 C = 1 : apply Exch on input field
41 C (needed if input field has invalid overlap)
42 C = 2 : apply Exch on output field (after the filter)
43 C = 3 : apply Exch on both input & output field
44 C kSize :: length of 3rd Dim : either =1 (2D field) or =Nr (3D field)
45 C myTime :: Current time in simulation
46 C myIter :: Current iteration number in simulation
47 C myThid :: Thread number for this instance of SHAP_FILT_TRACER_S2
48 INTEGER kSize
49 _RL field(1-OLx:sNx+OLx,1-OLy:sNy+OLy,kSize,nSx,nSy)
50 _RL tmpFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,kSize,nSx,nSy)
51 INTEGER nShapTr, exchInOut
52 _RL myTime
53 INTEGER myIter
54 INTEGER myThid
55
56 #ifdef ALLOW_SHAP_FILT
57
58 C !LOCAL VARIABLES:
59 C == Local variables ==
60 INTEGER nShapComput
61 INTEGER bi,bj,k,i,j,n
62 _RL tmpGrd(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
63 _RL tmpFdx(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
64 _RL tmpFdy(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
65 CEOP
66
67 IF ( exchInOut.LT.0 .OR. exchInOut.GT.3 ) THEN
68 STOP 'S/R SHAP_FILT_TRACER_S2: exchInOut is wrong'
69 ENDIF
70
71 IF (nShapTr.GT.0) THEN
72 C-------
73 C Apply computational filter ^(nShap-nShapPhys) without grid factor
74 C then apply Physical filter ^nShapPhys with grid factors
75 C-------
76 nShapComput = nShapTr - nShapTrPhys
77
78 DO bj=myByLo(myThid),myByHi(myThid)
79 DO bi=myBxLo(myThid),myBxHi(myThid)
80 DO k=1,kSize
81 DO j=1-Oly,sNy+Oly
82 DO i=1-Olx,sNx+Olx
83 tmpFld(i,j,k,bi,bj)=field(i,j,k,bi,bj)
84 ENDDO
85 ENDDO
86 ENDDO
87 ENDDO
88 ENDDO
89
90
91 C ( d_xx +d_yy )^n tmpFld
92
93 DO n=1,nShapTr
94
95 IF ( ( MOD(n,2).EQ.1 .OR. Shap_alwaysExchTr ) .AND.
96 & ( n.GE.2 .OR. MOD(exchInOut,2).EQ.1 ) ) THEN
97 IF (kSize.EQ.Nr) THEN
98 _EXCH_XYZ_RL( tmpFld, myThid )
99 ELSEIF (kSize.EQ.1) THEN
100 _EXCH_XY_RL( tmpFld, myThid )
101 ELSE
102 STOP 'S/R SHAP_FILT_TRACER_S2: kSize is wrong'
103 ENDIF
104 ENDIF
105
106 DO bj=myByLo(myThid),myByHi(myThid)
107 DO bi=myBxLo(myThid),myBxHi(myThid)
108 DO k=1,kSize
109
110 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
111
112 C-- Calculate gradient in X direction:
113 #ifndef ALLOW_AUTODIFF_TAMC
114 IF ( .NOT.Shap_alwaysExchTr
115 & .AND. useCubedSphereExchange ) THEN
116 C to compute d/dx(tmpFld), fill corners with appropriate values:
117 CALL FILL_CS_CORNER_TR_RL( 1, .FALSE.,
118 & tmpFld(1-Olx,1-Oly,k,bi,bj),
119 & bi,bj, myThid )
120 ENDIF
121 #endif
122 IF ( n.LE.nShapComput ) THEN
123 C- Computational space: del_i
124 DO j=0,sNy+1
125 DO i=0,sNx+2
126 tmpFdx(i,j) =
127 & ( tmpFld(i,j,k,bi,bj)-tmpFld(i-1,j,k,bi,bj) )
128 & *_maskW(i,j,k,bi,bj)
129 ENDDO
130 ENDDO
131 ELSE
132 C- Physical space: grad_x
133 DO j=0,sNy+1
134 DO i=0,sNx+2
135 tmpFdx(i,j) =
136 & ( tmpFld(i,j,k,bi,bj)-tmpFld(i-1,j,k,bi,bj) )
137 & *_hFacW(i,j,k,bi,bj)
138 & *dyG(i,j,bi,bj)*recip_dxC(i,j,bi,bj)
139 ENDDO
140 ENDDO
141 ENDIF
142
143 C-- Calculate gradient in Y direction:
144 #ifndef ALLOW_AUTODIFF_TAMC
145 IF ( .NOT.Shap_alwaysExchTr
146 & .AND. useCubedSphereExchange ) THEN
147 C to compute d/dy(tmpFld), fill corners with appropriate values:
148 CALL FILL_CS_CORNER_TR_RL( 2, .FALSE.,
149 & tmpFld(1-Olx,1-Oly,k,bi,bj),
150 & bi,bj, myThid )
151 ENDIF
152 #endif
153 IF ( n.LE.nShapComput ) THEN
154 C- Computational space: del_j
155 DO j=0,sNy+2
156 DO i=0,sNx+1
157 tmpFdy(i,j) =
158 & ( tmpFld(i,j,k,bi,bj)-tmpFld(i,j-1,k,bi,bj) )
159 & *_maskS(i,j,k,bi,bj)
160 ENDDO
161 ENDDO
162 ELSE
163 C- Physical space: grad_y
164 DO j=0,sNy+2
165 DO i=0,sNx+1
166 tmpFdy(i,j) =
167 & ( tmpFld(i,j,k,bi,bj)-tmpFld(i,j-1,k,bi,bj) )
168 & *_hFacS(i,j,k,bi,bj)
169 & *dxG(i,j,bi,bj)*recip_dyC(i,j,bi,bj)
170 ENDDO
171 ENDDO
172 ENDIF
173
174 C-- Calculate (d_xx + d_yy) tmpFld :
175 DO j=0,sNy+1
176 DO i=0,sNx+1
177 tmpGrd(i,j) = ( tmpFdx(i+1,j) - tmpFdx(i,j) )
178 & + ( tmpFdy(i,j+1) - tmpFdy(i,j) )
179 ENDDO
180 ENDDO
181
182 C-- Computational space Filter
183 IF ( n.LE.nShapComput ) THEN
184 DO j=0,sNy+1
185 DO i=0,sNx+1
186 tmpFld(i,j,k,bi,bj) = -0.125*tmpGrd(i,j)
187 ENDDO
188 ENDDO
189 C-- Physical space Filter
190 ELSEIF (Shap_TrLength.LE.0.) THEN
191 DO j=0,sNy+1
192 DO i=0,sNx+1
193 tmpFld(i,j,k,bi,bj) = -0.125*tmpGrd(i,j)
194 & *recip_hFacC(i,j,k,bi,bj)
195 ENDDO
196 ENDDO
197 ELSE
198 DO j=0,sNy+1
199 DO i=0,sNx+1
200 tmpFld(i,j,k,bi,bj) = -0.125*tmpGrd(i,j)
201 & *recip_hFacC(i,j,k,bi,bj)*recip_rA(i,j,bi,bj)
202 & *Shap_TrLength*Shap_TrLength
203 ENDDO
204 ENDDO
205 ENDIF
206 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
207
208 C end k,bi,bj loop:
209 ENDDO
210 ENDDO
211 ENDDO
212 C end loop n=1,nShapTr
213 ENDDO
214
215 C F <- [1 - (d_xx+d_yy)^n *deltaT/tau].F
216 DO bj=myByLo(myThid),myByHi(myThid)
217 DO bi=myBxLo(myThid),myBxHi(myThid)
218 DO k=1,kSize
219 DO j=1,sNy
220 DO i=1,sNx
221 field(i,j,k,bi,bj)=field(i,j,k,bi,bj)
222 & -tmpFld(i,j,k,bi,bj)*dTtracerLev(1)/Shap_Trtau
223 tmpFld(i,j,k,bi,bj)= -tmpFld(i,j,k,bi,bj)/Shap_Trtau
224 ENDDO
225 ENDDO
226 ENDDO
227 ENDDO
228 ENDDO
229
230 IF ( exchInOut.GE.2 ) THEN
231 IF (kSize.EQ.Nr) THEN
232 _EXCH_XYZ_RL( field, myThid )
233 ELSEIF (kSize.EQ.1) THEN
234 _EXCH_XY_RL( field, myThid )
235 ELSE
236 STOP 'S/R SHAP_FILT_TRACER_S2: kSize is wrong'
237 ENDIF
238 ENDIF
239
240 ENDIF
241 #endif /* ALLOW_SHAP_FILT */
242
243 RETURN
244 END

  ViewVC Help
Powered by ViewVC 1.1.22