/[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.10 - (show annotations) (download)
Fri Oct 7 14:19:42 2005 UTC (18 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58b_post, checkpoint57y_post, checkpoint58, checkpoint58a_post, checkpoint57z_post, checkpoint57v_post, checkpoint57y_pre, checkpint57u_post, checkpoint57w_post, checkpoint57x_post, checkpoint58c_post
Changes since 1.9: +5 -1 lines
for now, put FILL_CS_CORNER_TR_RL call between #ifndef ALLOW_AUTODIFF_TAMC/#endif

1 C $Header: /u/gcmpack/MITgcm/pkg/shap_filt/shap_filt_tracer_s2.F,v 1.9 2005/10/07 00:27:53 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 #ifndef ALLOW_AUTODIFF_TAMC
99 IF ( .NOT.Shap_alwaysExchTr
100 & .AND. useCubedSphereExchange ) THEN
101 C to compute d/dx(tmpFld), fill corners with appropriate values:
102 CALL FILL_CS_CORNER_TR_RL( .TRUE.,
103 & tmpFld(1-Olx,1-Oly,k,bi,bj),
104 & bi,bj, myThid )
105 ENDIF
106 #endif
107 IF ( n.LE.nShapComput ) THEN
108 C- Computational space: del_i
109 DO j=0,sNy+1
110 DO i=0,sNx+2
111 tmpFdx(i,j) =
112 & ( tmpFld(i,j,k,bi,bj)-tmpFld(i-1,j,k,bi,bj) )
113 & *_maskW(i,j,k,bi,bj)
114 ENDDO
115 ENDDO
116 ELSE
117 C- Physical space: grad_x
118 DO j=0,sNy+1
119 DO i=0,sNx+2
120 tmpFdx(i,j) =
121 & ( tmpFld(i,j,k,bi,bj)-tmpFld(i-1,j,k,bi,bj) )
122 & *_hFacW(i,j,k,bi,bj)
123 & *dyG(i,j,bi,bj)*recip_dxC(i,j,bi,bj)
124 ENDDO
125 ENDDO
126 ENDIF
127
128 C-- Calculate gradient in Y direction:
129 #ifndef ALLOW_AUTODIFF_TAMC
130 IF ( .NOT.Shap_alwaysExchTr
131 & .AND. useCubedSphereExchange ) THEN
132 C to compute d/dy(tmpFld), fill corners with appropriate values:
133 CALL FILL_CS_CORNER_TR_RL(.FALSE.,
134 & tmpFld(1-Olx,1-Oly,k,bi,bj),
135 & bi,bj, myThid )
136 ENDIF
137 #endif
138 IF ( n.LE.nShapComput ) THEN
139 C- Computational space: del_j
140 DO j=0,sNy+2
141 DO i=0,sNx+1
142 tmpFdy(i,j) =
143 & ( tmpFld(i,j,k,bi,bj)-tmpFld(i,j-1,k,bi,bj) )
144 & *_maskS(i,j,k,bi,bj)
145 ENDDO
146 ENDDO
147 ELSE
148 C- Physical space: grad_y
149 DO j=0,sNy+2
150 DO i=0,sNx+1
151 tmpFdy(i,j) =
152 & ( tmpFld(i,j,k,bi,bj)-tmpFld(i,j-1,k,bi,bj) )
153 & *_hFacS(i,j,k,bi,bj)
154 & *dxG(i,j,bi,bj)*recip_dyC(i,j,bi,bj)
155 ENDDO
156 ENDDO
157 ENDIF
158
159 C-- Calculate (d_xx + d_yy) tmpFld :
160 DO j=0,sNy+1
161 DO i=0,sNx+1
162 tmpGrd(i,j) = ( tmpFdx(i+1,j) - tmpFdx(i,j) )
163 & + ( tmpFdy(i,j+1) - tmpFdy(i,j) )
164 ENDDO
165 ENDDO
166
167 C-- Computational space Filter
168 IF ( n.LE.nShapComput ) THEN
169 DO j=0,sNy+1
170 DO i=0,sNx+1
171 tmpFld(i,j,k,bi,bj) = -0.125*tmpGrd(i,j)
172 ENDDO
173 ENDDO
174 C-- Physical space Filter
175 ELSEIF (Shap_TrLength.LE.0.) THEN
176 DO j=0,sNy+1
177 DO i=0,sNx+1
178 tmpFld(i,j,k,bi,bj) = -0.125*tmpGrd(i,j)
179 & *recip_hFacC(i,j,k,bi,bj)
180 ENDDO
181 ENDDO
182 ELSE
183 DO j=0,sNy+1
184 DO i=0,sNx+1
185 tmpFld(i,j,k,bi,bj) = -0.125*tmpGrd(i,j)
186 & *recip_hFacC(i,j,k,bi,bj)*recip_rA(i,j,bi,bj)
187 & *Shap_TrLength*Shap_TrLength
188 ENDDO
189 ENDDO
190 ENDIF
191 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
192
193 C end k,bi,bj loop:
194 ENDDO
195 ENDDO
196 ENDDO
197 C end loop n=1,nShapTr
198 ENDDO
199
200 C F <- [1 - (d_xx+d_yy)^n *deltaT/tau].F
201 DO bj=myByLo(myThid),myByHi(myThid)
202 DO bi=myBxLo(myThid),myBxHi(myThid)
203 DO k=1,kSize
204 DO j=1,sNy
205 DO i=1,sNx
206 field(i,j,k,bi,bj)=field(i,j,k,bi,bj)
207 & -tmpFld(i,j,k,bi,bj)*dTtracerLev(1)/Shap_Trtau
208 tmpFld(i,j,k,bi,bj)= -tmpFld(i,j,k,bi,bj)/Shap_Trtau
209 ENDDO
210 ENDDO
211 ENDDO
212 ENDDO
213 ENDDO
214
215 c IF (kSize.EQ.Nr) THEN
216 c _EXCH_XYZ_R8( field, myThid )
217 c ELSEIF (kSize.EQ.1) THEN
218 c _EXCH_XY_R8( field, myThid )
219 c ELSE
220 c STOP 'S/R SHAP_FILT_TRACER_S2: kSize is wrong'
221 c ENDIF
222
223 ENDIF
224 #endif /* ALLOW_SHAP_FILT */
225
226 RETURN
227 END

  ViewVC Help
Powered by ViewVC 1.1.22