/[MITgcm]/MITgcm/pkg/zonal_filt/zonal_filter.F
ViewVC logotype

Annotation of /MITgcm/pkg/zonal_filt/zonal_filter.F

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


Revision 1.4 - (hide annotations) (download)
Tue Apr 10 22:35:27 2001 UTC (23 years, 1 month ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint40pre3, checkpoint40pre1, checkpoint40pre7, checkpoint40pre6, checkpoint40pre9, checkpoint40pre8, release1_b1, checkpoint43, checkpoint38, checkpoint40pre2, checkpoint40pre4, checkpoint39, checkpoint40pre5, ecco-branch-mod1, release1_beta1, checkpoint42, checkpoint40, checkpoint41
Branch point for: release1, ecco-branch, release1_coupled
Changes since 1.3: +3 -3 lines
See doc/tag-index and doc/notes_c37_adj.txt
Preparation for stand-alone autodifferentiability.

1 heimbach 1.4 C $Header: /u/gcmpack/models/MITgcmUV/pkg/zonal_filt/zonal_filter.F,v 1.3 2001/02/04 14:38:51 cnh Exp $
2     C $Name: checkpoint37 $
3 adcroft 1.2
4     #include "ZONAL_FILT_OPTIONS.h"
5    
6     SUBROUTINE ZONAL_FILTER(
7     U field, fieldMask,
8     I jMin, jMax, kMin, kMax, bi, bj, gridLoc, myThid )
9     C /==========================================================\
10     C | S/R ZONAL_FILTER |
11     C | o Apply FFT filter to a latitude circle. |
12     C \==========================================================/
13     IMPLICIT NONE
14    
15     C == Global data ==
16     #include "SIZE.h"
17     #include "ZONAL_FILT.h"
18     #include "FFTPACK.h"
19    
20     C == Routine arguments ==
21     C jMin - Range of points to filter
22     C jMax
23     C kMin
24     C kMax
25     C bi
26     C bj
27     C myThid - Thread number of this instance of FILTER_LATCIRC_FFT_APPLY
28     C field - Field to filter
29     C gridLoc - Orientation (U or V) of field.
30     INTEGER myThid
31     INTEGER gridLoc
32     Real*8 field(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
33     Real*8 fieldMask(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
34     INTEGER jMin, jMax, kMin, kMax, bi, bj
35    
36     #ifdef ALLOW_ZONAL_FILT
37    
38     C == Local data ==
39     Real*8 phi(Nx)
40     Real*8 phiMask(Nx)
41     Real*8 avPhi
42     INTEGER I, J, K
43    
44     DO k=kMin, kMax
45     DO j=jMin, jMax
46    
47     C o Copy zonal line of field into local workspace
48     DO i=1,sNx
49     phi(I) = field(i,j,k,bi,bj)
50     phiMask(I) = fieldMask(i,j,k,bi,bj)
51     ENDDO
52    
53     C Interpolate through land
54     CALL ZONAL_FILT_PRESMOOTH( phiMask,phi,avPhi,sNx,myThid )
55    
56     C o Forward transform (using specific FFT package)
57     C CALL R8FFTF( Nx, phi, FFTPACKWS(1,bj) )
58     CALL R8FFTF1( Nx, phi,
59     & FFTPACKWS1(1,bj), FFTPACKWS2(1,bj),FFTPACKWS3(1,bj) )
60    
61     C o Apply amplitude filter and normalize
62     IF (gridLoc .EQ. 1) THEN
63     DO i=1, Nx
64     phi(i)=phi(i)*ampFactor(i,j,bi,bj)/float(Nx)
65     ENDDO
66     ELSEIF (gridLoc .EQ. 2) THEN
67     DO i=1, Nx
68     phi(i)=phi(i)*ampFactorV(i,j,bi,bj)/float(Nx)
69     ENDDO
70     ELSE
71 heimbach 1.4 WRITE(*,*) 'Error: gridLoc = ',gridLoc
72 adcroft 1.2 STOP 'Error: gridLoc has illegal value'
73     ENDIF
74    
75     C o Backward transform (using specific FFT package)
76     C CALL R8FFTB( Nx, phi, FFTPACKWS(1,bj) )
77     CALL R8FFTB1( Nx, phi,
78     & FFTPACKWS1(1,bj), FFTPACKWS2(1,bj),FFTPACKWS3(1,bj) )
79    
80     C De-interpolate through land
81     CALL ZONAL_FILT_POSTSMOOTH(phiMask,phi,avPhi,sNx,myThid)
82    
83     C o Do periodic wrap around by hand
84     DO i=1-OLx,0
85     field(i,j,k,bi,bj) = phi(sNx+i)
86     ENDDO
87     DO i=1,sNx
88     field(i,j,k,bi,bj) = phi(I)
89     ENDDO
90     DO i=sNx+1,sNx+OLx
91     field(i,j,k,bi,bj) = phi(i-sNx)
92     ENDDO
93    
94     ENDDO
95     ENDDO
96    
97     #endif /* ALLOW_ZONAL_FILT */
98    
99     RETURN
100     END

  ViewVC Help
Powered by ViewVC 1.1.22