/[MITgcm]/MITgcm/pkg/smooth/smooth_filtervar3d.F
ViewVC logotype

Contents of /MITgcm/pkg/smooth/smooth_filtervar3d.F

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


Revision 1.2 - (show annotations) (download)
Tue Sep 4 14:37:18 2012 UTC (11 years, 8 months ago) by gforget
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63s, checkpoint64, checkpoint65, checkpoint65h, checkpoint65i, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e
Changes since 1.1: +4 -6 lines
- remove in-necessary includes.
- remove ALLOW_SMOOTH*D and ALLOW_SMOOTH_CORREL*D brakets.
  Those CPP options were never defined, and not necessary.

1 C $Header: /u/gcmpack/MITgcm/pkg/smooth/smooth_filtervar3d.F,v 1.1 2010/02/15 23:46:04 gforget Exp $
2 C $Name: $
3
4 #include "SMOOTH_OPTIONS.h"
5
6 subroutine smooth_filtervar3D (smoothOpNb,myThid)
7
8 C *==========================================================*
9 C | SUBROUTINE smooth_filtervar3D
10 C | o Routine that computes the filter variance
11 C | field associated with a diffusion operator, as part
12 C | a 3D spatial correlation operator (smooth_correld3D.F)
13 C | See Weaver and Courtier 01 for details.
14 C *==========================================================*
15
16
17 IMPLICIT NONE
18 #include "SIZE.h"
19 #include "EEPARAMS.h"
20 #include "PARAMS.h"
21 #include "GRID.h"
22 #include "SMOOTH.h"
23
24 integer smoothOpNb, myThid
25
26 integer i,j,k, bi, bj, ii, jj, kk
27 integer itlo,ithi, jtlo,jthi
28 integer diLoc, djLoc, dkLoc
29 integer nbRand, nbt_in
30 character*( 80) fnamegeneric
31 _RL smoothTmpFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
32 _RL smoothTmpMean(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
33 _RL smoothTmpVar(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
34 _RL port_rand, port_rand_norm
35
36 jtlo = mybylo(myThid)
37 jthi = mybyhi(myThid)
38 itlo = mybxlo(myThid)
39 ithi = mybxhi(myThid)
40
41 c if smooth3Dfilter(smoothOpNb)=0: the filter variance field
42 c has been computed earlier and is already in the run directory
43 c so this routine does not do anything
44
45 IF (smooth3Dfilter(smoothOpNb).NE.0) then
46
47 nbt_in=smooth3Dnbt(smoothOpNb)/2
48
49 c read smoothing [i.e diffusion] operator:
50 write(fnamegeneric(1:80),'(1a,i3.3)')
51 & 'smooth3Doperator',smoothOpNb
52 CALL READ_REC_3D_RL( fnamegeneric,smoothprec, Nr,smooth3D_Kwx,
53 & 1, 1, myThid )
54 CALL READ_REC_3D_RL( fnamegeneric,smoothprec, Nr,smooth3D_Kwy,
55 & 2, 1, myThid )
56 CALL READ_REC_3D_RL( fnamegeneric,smoothprec, Nr,smooth3D_Kwz,
57 & 3, 1, myThid )
58 CALL READ_REC_3D_RL( fnamegeneric,smoothprec, Nr,smooth3D_Kux,
59 & 4, 1, myThid )
60 CALL READ_REC_3D_RL( fnamegeneric,smoothprec, Nr,smooth3D_Kvy,
61 & 5, 1, myThid )
62 CALL READ_REC_3D_RL( fnamegeneric,smoothprec, Nr,smooth3D_Kuz,
63 & 6, 1, myThid )
64 CALL READ_REC_3D_RL( fnamegeneric,smoothprec, Nr,smooth3D_Kvz,
65 & 7, 1, myThid )
66 CALL READ_REC_3D_RL( fnamegeneric,smoothprec, Nr,smooth3D_Kuy,
67 & 8, 1, myThid )
68 CALL READ_REC_3D_RL( fnamegeneric,smoothprec, Nr,smooth3D_Kvx,
69 & 9, 1, myThid )
70 CALL READ_REC_3D_RL( fnamegeneric,smoothprec, Nr,smooth3D_kappaR,
71 & 10,1, myThid )
72 _EXCH_XYZ_RL ( smooth3D_Kwx, myThid )
73 _EXCH_XYZ_RL ( smooth3D_Kwy, myThid )
74 _EXCH_XYZ_RL ( smooth3D_Kwz, myThid )
75 _EXCH_XYZ_RL ( smooth3D_Kux, myThid )
76 _EXCH_XYZ_RL ( smooth3D_Kvy, myThid )
77 _EXCH_XYZ_RL ( smooth3D_Kuz, myThid )
78 _EXCH_XYZ_RL ( smooth3D_Kvz, myThid )
79 _EXCH_XYZ_RL ( smooth3D_Kuy, myThid )
80 _EXCH_XYZ_RL ( smooth3D_Kvx, myThid )
81 _EXCH_XYZ_RL ( smooth3D_kappaR, myThid )
82
83 c initialize filter variance field:
84 DO bj=jtlo,jthi
85 DO bi=itlo,ithi
86 DO k=1,Nr
87 DO j=1-OLy,sNy+OLy
88 DO i=1-OLx,sNx+OLx
89 smooth3Dnorm(i,j,k,bi,bj)=0.
90 ENDDO
91 ENDDO
92 ENDDO
93 ENDDO
94 ENDDO
95
96 IF (smooth3Dfilter(smoothOpNb).EQ.2) then
97 c compute the normalization matrix using the approximate method
98 c
99 c This method can be quite expensive -- so that the approximate
100 c method (see below) is usually the prefered one.
101 c The exact method can be used to check the accuracy
102 c of the approximate method results (that can be predicted).
103 c
104 c note: the exact method requires the adjoint of smooth_diff2D.F (see below)
105
106 diLoc=15 !int(5*smooth_L/smooth_dx)
107 djLoc=20 !int(5*smooth_L/smooth_dx)
108 dkLoc=8
109
110 DO kk=1,dkLoc
111 DO ii=1,diLoc,2
112 DO jj=1,djLoc,2
113
114 DO bj=jtlo,jthi
115 DO bi=itlo,ithi
116 DO k=1,Nr
117 DO j=1-OLy,sNy+OLy
118 DO i=1-OLx,sNx+OLx
119 smoothTmpFld(i,j,k,bi,bj)=0.
120 ENDDO
121 ENDDO
122 ENDDO
123
124 DO k=kk,Nr,dkLoc
125 DO j=jj,sNy,djLoc
126 DO i=ii,sNx,diLoc
127 smoothTmpFld(i,j,k,bi,bj)=1.
128 ENDDO
129 ENDDO
130 ENDDO
131 ENDDO
132 ENDDO
133
134 c note: as we go to adjoint part, we need to have 0 in overlaps
135 c so we must NOT have done an exchange for smoothTmpFld
136
137 c adjoint:
138 WRITE(errorMessageUnit,'(A,/,A)' )
139 & "you need to have adsmooth_diff3D compiled and then:",
140 & "uncomment the line below and comment the stop"
141 STOP 'ABNORMAL END: S/R smooth_filtervar3D'
142 c call adsmooth_diff3D(smoothTmpFld,nbt_in,myThid)
143
144 c division by sqrt(volume)*sqrt(volume) [1 to end adj, 1 to begin fwd]
145 DO bj=jtlo,jthi
146 DO bi=itlo,ithi
147 DO k=1,Nr
148 DO j=1,sNy
149 DO i=1,sNx
150 c division by ~sqrt(volume):
151 smoothTmpFld(i,j,k,bi,bj)=smoothTmpFld(i,j,k,bi,bj)
152 & *(recip_rA(i,j,bi,bj)*recip_drF(k))
153 ENDDO
154 ENDDO
155 ENDDO
156 ENDDO
157 ENDDO
158
159 c coming out of adjoint part: overlaps are 0
160 c going in fwd part: we need to fill them up
161 _EXCH_XYZ_RL ( smoothTmpFld , myThid )
162
163 c fwd:
164 call smooth_diff3D(smoothTmpFld,nbt_in,myThid)
165
166 c convert variance to normalization factor:
167 DO bj=jtlo,jthi
168 DO bi=itlo,ithi
169 DO k=1,Nr,dkLoc
170 DO j=jj,sNy,djLoc
171 DO i=ii,sNx,diLoc
172 if (smoothTmpFld(i,j,k,bi,bj).NE.0.) then
173 smooth3Dnorm(i,j,k,bi,bj)=
174 & 1/sqrt(smoothTmpFld(i,j,k,bi,bj))
175 endif
176 ENDDO
177 ENDDO
178 ENDDO
179 ENDDO
180 ENDDO
181
182 ENDDO !DO ii=1,diLoc
183 ENDDO !DO jj=1,djLoc
184 ENDDO !DO kk=1,dkLoc
185
186
187 ELSEIF (smooth3Dfilter(smoothOpNb).EQ.1) then
188 c compute the normalization matrix using the approximate method
189
190 DO bj=jtlo,jthi
191 DO bi=itlo,ithi
192 DO k=1,Nr
193 DO j=1-OLy,sNy+OLy
194 DO i=1-OLx,sNx+OLx
195 smoothTmpMean(i,j,k,bi,bj) = 0. _d 0
196 smoothTmpVar(i,j,k,bi,bj) = 0. _d 0
197 ENDDO
198 ENDDO
199 ENDDO
200 ENDDO
201 ENDDO
202
203 c initialize random number generator
204 smoothTmpFld(1,1,1,1,1)=port_rand(1)
205 nbRand=1000
206
207 DO ii=1,nbRand
208 WRITE(standardMessageUnit,'(A,I4,A,I4)')
209 & 'smooth_filtervar3D: ',ii,' members done out of ',nbRand
210
211 c fill smoothTmpFld with random numbers:
212 DO bj=jtlo,jthi
213 DO bi=itlo,ithi
214 DO k=1,Nr
215 DO j=1-OLy,sNy+OLy
216 DO i=1-OLx,sNx+OLx
217 smoothTmpFld(i,j,k,bi,bj) = 0. _d 0
218 if (maskC(i,j,k,bi,bj).NE.0) then
219 smoothTmpFld(i,j,k,bi,bj)=port_rand_norm()
220 endif
221 c division by sqrt(volume):
222 smoothTmpFld(i,j,k,bi,bj)=smoothTmpFld(i,j,k,bi,bj)
223 & *sqrt(recip_rA(i,j,bi,bj)*recip_drF(k))
224 ENDDO
225 ENDDO
226 ENDDO
227 ENDDO
228 ENDDO
229
230 _EXCH_XYZ_RL ( smoothTmpFld, myThid )
231
232 c smooth random number field
233 call smooth_diff3D(smoothTmpFld,nbt_in,myThid)
234
235 c accumulate statistics (to compute the variance later)
236 DO bj=jtlo,jthi
237 DO bi=itlo,ithi
238 DO k=1,Nr
239 DO j=1-OLy,sNy+OLy
240 DO i=1-OLx,sNx+OLx
241 smoothTmpVar(i,j,k,bi,bj)=smoothTmpVar(i,j,k,bi,bj)
242 & +smoothTmpFld(i,j,k,bi,bj)*smoothTmpFld(i,j,k,bi,bj)/nbRand
243 smoothTmpMean(i,j,k,bi,bj)=smoothTmpMean(i,j,k,bi,bj)
244 & +smoothTmpFld(i,j,k,bi,bj)/nbRand
245 ENDDO
246 ENDDO
247 ENDDO
248 ENDDO
249 ENDDO
250
251 ENDDO
252
253 c compute variance and convert it to normalization factor:
254 DO bj=jtlo,jthi
255 DO bi=itlo,ithi
256 DO k=1,Nr
257 DO j=1-OLy,sNy+OLy
258 DO i=1-OLx,sNx+OLx
259 if (maskC(i,j,k,bi,bj).NE.0) then
260 smooth3Dnorm(i,j,k,bi,bj)=
261 & 1/sqrt ( nbRand/(nbRand-1)* ( smoothTmpVar(i,j,k,bi,bj) -
262 & smoothTmpMean(i,j,k,bi,bj)*smoothTmpMean(i,j,k,bi,bj)
263 & ) )
264 endif
265 ENDDO
266 ENDDO
267 ENDDO
268 ENDDO
269 ENDDO
270
271 ENDIF
272
273 c write smooth3Dnorm_3D to file:
274 write(fnamegeneric(1:80),'(1a,i3.3)')
275 & 'smooth3Dnorm',smoothOpNb
276 CALL WRITE_REC_3D_RL( fnamegeneric, smoothprec,
277 & Nr, smooth3Dnorm, 1, 1, myThid )
278 _EXCH_XYZ_RL ( smooth3Dnorm, myThid )
279
280 ENDIF
281
282 RETURN
283 END

  ViewVC Help
Powered by ViewVC 1.1.22