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

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

  ViewVC Help
Powered by ViewVC 1.1.22