/[MITgcm]/MITgcm/pkg/gmredi/gmredi_calc_tensor.F
ViewVC logotype

Annotation of /MITgcm/pkg/gmredi/gmredi_calc_tensor.F

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


Revision 1.5 - (hide annotations) (download)
Sun Feb 4 14:38:49 2001 UTC (23 years, 3 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint36, checkpoint35
Changes since 1.4: +2 -1 lines
Made sure each .F and .h file had
the CVS keywords Header and Name at its start.
Most had header but very few currently have Name, so
lots of changes!

1 cnh 1.5 C $Header: /u/gcmpack/models/MITgcmUV/pkg/gmredi/gmredi_calc_tensor.F,v 1.4 2001/02/02 21:36:29 adcroft Exp $
2     C $Name: $
3 adcroft 1.1
4     #include "GMREDI_OPTIONS.h"
5    
6     CStartOfInterface
7     SUBROUTINE GMREDI_CALC_TENSOR(
8     I bi, bj, iMin, iMax, jMin, jMax, K,
9     I sigmaX, sigmaY, sigmaR,
10     I myThid )
11     C /==========================================================\
12     C | SUBROUTINE GMREDI_CALC_TENSOR |
13     C | o Calculate tensor elements for GM/Redi tensor. |
14     C |==========================================================|
15     C \==========================================================/
16     IMPLICIT NONE
17    
18     C == Global variables ==
19     #include "SIZE.h"
20     #include "GRID.h"
21     #include "DYNVARS.h"
22     #include "EEPARAMS.h"
23     #include "PARAMS.h"
24     #include "GMREDI.h"
25     #include "GMREDI_DIAGS.h"
26    
27     C == Routine arguments ==
28     C
29     _RL sigmaX(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
30     _RL sigmaY(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
31     _RL sigmaR(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
32     INTEGER bi,bj,iMin,iMax,jMin,jMax,K
33     INTEGER myThid
34     CEndOfInterface
35    
36     #ifdef ALLOW_GMREDI
37    
38     C == Local variables ==
39     INTEGER i,j,km1,kp1
40     _RL SlopeX(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
41     _RL SlopeY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
42     _RL dSigmaDrReal(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
43     _RL dRdSigmaLtd(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
44     _RL Ssq
45    
46     #ifdef GM_VISBECK_VARIABLE_K
47     _RS deltaH,zero_rs
48     PARAMETER(zero_rs=0.)
49     _RL N2,SN
50     #endif
51    
52    
53     km1=max(1,K-1)
54     kp1=min(Nr,K)
55    
56    
57     #ifdef ALLOW_AUTODIFF_TAMC
58     !HPF$ INDEPENDENT
59     #endif
60     DO j=1-Oly+1,sNy+Oly-1
61     #ifdef ALLOW_AUTODIFF_TAMC
62     !HPF$ INDEPENDENT
63     #endif
64     DO i=1-Olx+1,sNx+Olx-1
65    
66     C Gradient of Sigma at rVel points
67     SlopeX(i,j)=0.25*( sigmaX(i+1, j ,km1) +sigmaX(i,j,km1)
68     & +sigmaX(i+1, j , k ) +sigmaX(i,j, k ) )
69     SlopeY(i,j)=0.25*( sigmaY( i ,j+1,km1) +sigmaY(i,j,km1)
70     & +sigmaY( i ,j+1, k ) +sigmaY(i,j, k ) )
71     dSigmaDrReal(i,j)=sigmaR(i,j,k)
72    
73     if (hFacC(i,j,k,bi,bj).eq.0.) then
74     SlopeX(i,j)=0.
75     SlopeY(i,j)=0.
76     endif
77    
78     ENDDO
79     ENDDO
80    
81     C Calculate slopes for use in tensor, taper and/or clip
82     CALL GMREDI_SLOPE_LIMIT(
83     I dSigmadRReal,
84     I rF(K),
85     U SlopeX, SlopeY,
86     O dRdSigmaLtd,
87     I bi, bj, myThid )
88    
89     DO j=1-Oly+1,sNy+Oly-1
90     DO i=1-Olx+1,sNx+Olx-1
91    
92     C Mask Iso-neutral slopes
93     if (hFacC(i,j,k,bi,bj).eq.0.) then
94     SlopeX(i,j)=0.
95     SlopeY(i,j)=0.
96     endif
97     Ssq=SlopeX(i,j)*SlopeX(i,j)+SlopeY(i,j)*SlopeY(i,j)
98    
99     C Components of Redi/GM tensor
100 heimbach 1.3 Kwx(i,j,k,bi,bj)=2.*SlopeX(i,j)
101     Kwy(i,j,k,bi,bj)=2.*SlopeY(i,j)
102     Kwz(i,j,k,bi,bj)=Ssq
103 adcroft 1.1
104     #ifdef GM_VISBECK_VARIABLE_K
105     C-- Depth average of M^2/N^2 * N
106    
107     C Calculate terms for mean Richardson number
108     C which is used in the "variable K" parameterisaton.
109     C Distance between interface above layer and the integration depth
110     deltaH=abs(GM_Visbeck_depth)-abs(rF(k))
111     C If positive we limit this to the layer thickness
112     deltaH=min(deltaH,drF(k))
113     C If negative then we are below the integration level
114     deltaH=max(deltaH,zero_rs)
115     C Now we convert deltaH to a non-dimensional fraction
116     deltaH=deltaH/GM_Visbeck_depth
117    
118 heimbach 1.3 if (K.eq.2) VisbeckK(i,j,bi,bj)=0.
119 adcroft 1.1 Calt? if (dSigmaDrReal(i,j).NE.0.) then
120     Calt? N2=(-Gravity*recip_Rhonil)*dSigmaDrReal(i,j)
121     if (dRdSigmaLtd(i,j).NE.0.) then
122     N2=(-Gravity*recip_Rhonil)/dRdSigmaLtd(i,j)
123     SN=sqrt(Ssq*N2)
124 heimbach 1.3 VisbeckK(i,j,bi,bj)=VisbeckK(i,j,bi,bj)+deltaH
125 adcroft 1.1 & *GM_Visbeck_alpha*GM_Visbeck_length*GM_Visbeck_length*SN
126     endif
127    
128     C Limit range that KapGM can take
129 heimbach 1.3 VisbeckK(i,j,bi,bj)=
130     & min(VisbeckK(i,j,bi,bj),GM_Visbeck_maxval_K)
131 adcroft 1.1
132     #endif /* GM_VISBECK_VARIABLE_K */
133    
134    
135     #ifdef INCLUDE_DIAGNOSTICS_INTERFACE_CODE
136     C-- Time-average
137     GM_Kwx_T(i,j,k,bi,bj)=GM_Kwx_T(i,j,k,bi,bj)
138 heimbach 1.3 & +Kwx(i,j,k,bi,bj)*deltaTclock
139 adcroft 1.1 GM_Kwy_T(i,j,k,bi,bj)=GM_Kwy_T(i,j,k,bi,bj)
140 heimbach 1.3 & +Kwy(i,j,k,bi,bj)*deltaTclock
141 adcroft 1.1 GM_Kwz_T(i,j,k,bi,bj)=GM_Kwz_T(i,j,k,bi,bj)
142 heimbach 1.3 & +Kwz(i,j,k,bi,bj)*deltaTclock
143 adcroft 1.1 #ifdef GM_VISBECK_VARIABLE_K
144     IF (K.EQ.Nr)
145     & Visbeck_K_T(i,j,bi,bj)=Visbeck_K_T(i,j,bi,bj)
146 heimbach 1.3 & +VisbeckK(i,j,bi,bj)*deltaTclock
147 adcroft 1.1 #endif
148 adcroft 1.4 #endif /* INCLUDE_DIAGNOSTICS_INTERFACE_CODE */
149 adcroft 1.1 ENDDO
150     ENDDO
151 adcroft 1.4
152     #ifdef INCLUDE_DIAGNOSTICS_INTERFACE_CODE
153 adcroft 1.1 GM_TimeAve(k,bi,bj)=GM_TimeAve(k,bi,bj)+deltaTclock
154 adcroft 1.4 #endif
155 adcroft 1.1
156    
157     #ifdef GM_NON_UNITY_DIAGONAL
158     C Gradient of Sigma at U points
159     DO j=1-Oly+1,sNy+Oly-1
160     DO i=1-Olx+1,sNx+Olx-1
161     SlopeX(i,j)=sigmaX(i,j,km1)
162     & *_maskW(i,j,k,bi,bj)
163     SlopeY(i,j)=0.25*( sigmaY(i-1,j+1,k) +sigmaY(i,j+1,k)
164     & +sigmaY(i-1, j ,k) +sigmaY(i, j ,k) )
165     & *_maskW(i,j,k,bi,bj)
166     dSigmaDrReal(i,j)=0.25*( sigmaR(i-1,j, k ) +sigmaR(i,j, k )
167     & +sigmaR(i-1,j,kp1) +sigmaR(i,j,kp1) )
168     & *_maskW(i,j,k,bi,bj)
169     ENDDO
170     ENDDO
171    
172     C Calculate slopes for use in tensor, taper and/or clip
173     CALL GMREDI_SLOPE_LIMIT(
174     I dSigmadRReal,
175     I rF(K),
176     U SlopeX, SlopeY,
177     O dRdSigmaLtd,
178     I bi, bj, myThid )
179    
180     DO j=1-Oly+1,sNy+Oly-1
181     DO i=1-Olx+1,sNx+Olx-1
182 heimbach 1.3 Kux(i,j,k,bi,bj)=(dSigmaDrReal(i,j)*dRdSigmaLtd(i,j))**2
183 adcroft 1.1 ENDDO
184     ENDDO
185    
186     C Gradient of Sigma at V points
187     DO j=1-Oly+1,sNy+Oly-1
188     DO i=1-Olx+1,sNx+Olx-1
189     SlopeX(i,j)=0.25*( sigmaX(i, j ,k) +sigmaX(i+1, j ,k)
190     & +sigmaX(i,j-1,k) +sigmaX(i+1,j-1,k) )
191     & *_maskS(i,j,k,bi,bj)
192     SlopeY(i,j)=sigmaY(i,j,km1)
193     & *_maskS(i,j,k,bi,bj)
194     dSigmaDrReal(i,j)=0.25*( sigmaR(i,j-1, k ) +sigmaR(i,j, k )
195     & +sigmaR(i,j-1,kp1) +sigmaR(i,j,kp1) )
196     & *_maskS(i,j,k,bi,bj)
197     ENDDO
198     ENDDO
199    
200     C Calculate slopes for use in tensor, taper and/or clip
201     CALL GMREDI_SLOPE_LIMIT(
202     I dSigmadRReal,
203     I rF(K),
204     U SlopeX, SlopeY,
205     O dRdSigmaLtd,
206     I bi, bj, myThid )
207    
208     DO j=1-Oly+1,sNy+Oly-1
209     DO i=1-Olx+1,sNx+Olx-1
210 heimbach 1.3 Kvy(i,j,k,bi,bj)=(dSigmaDrReal(i,j)*dRdSigmaLtd(i,j))**2
211 adcroft 1.1 ENDDO
212     ENDDO
213    
214     #endif /* GM_NON_UNITY_DIAGONAL */
215    
216    
217    
218     #endif /* ALLOW_GMREDI */
219    
220     RETURN
221     END
222 heimbach 1.2
223    
224     SUBROUTINE GMREDI_CALC_TENSOR_DUMMY(
225     I bi, bj, iMin, iMax, jMin, jMax, K,
226     I sigmaX, sigmaY, sigmaR,
227     I myThid )
228     C /==========================================================\
229     C | SUBROUTINE GMREDI_CALC_TENSOR |
230     C | o Calculate tensor elements for GM/Redi tensor. |
231     C |==========================================================|
232     C \==========================================================/
233     IMPLICIT NONE
234    
235     C == Global variables ==
236     #include "SIZE.h"
237     #include "GRID.h"
238     #include "DYNVARS.h"
239     #include "EEPARAMS.h"
240     #include "PARAMS.h"
241     #include "GMREDI.h"
242    
243     C == Routine arguments ==
244     C
245     _RL sigmaX(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
246     _RL sigmaY(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
247     _RL sigmaR(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
248     INTEGER bi,bj,iMin,iMax,jMin,jMax,K
249     INTEGER myThid
250     CEndOfInterface
251    
252     INTEGER i, j
253    
254     #ifdef ALLOW_GMREDI
255    
256     DO j=1-Oly+1,sNy+Oly-1
257     DO i=1-Olx+1,sNx+Olx-1
258 heimbach 1.3 Kwx(i,j,k,bi,bj) = 0.0
259     Kwy(i,j,k,bi,bj) = 0.0
260     Kwz(i,j,k,bi,bj) = 0.0
261 heimbach 1.2 ENDDO
262     ENDDO
263     #endif /* ALLOW_GMREDI */
264    
265     end

  ViewVC Help
Powered by ViewVC 1.1.22