/[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.16 - (show annotations) (download)
Fri Apr 4 19:38:23 2014 UTC (10 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65o, checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64w, checkpoint64v, HEAD
Changes since 1.15: +7 -8 lines
Replace ALLOW_AUTODIFF_TAMC by ALLOW_AUTODIFF (except for tape/storage
  which are specific to TAF/TAMC).

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

  ViewVC Help
Powered by ViewVC 1.1.22