/[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.9 - (show annotations) (download)
Fri Oct 7 00:27:53 2005 UTC (18 years, 7 months ago) by jmc
Branch: MAIN
Changes since 1.8: +115 -94 lines
Compute over a wider range of index to reduce (by 2) the number of
 exch call needed; and comment out the last exch call (not needed).

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

  ViewVC Help
Powered by ViewVC 1.1.22