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

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

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


Revision 1.1 - (hide annotations) (download)
Wed Jul 13 22:59:53 2011 UTC (12 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c
add Sub-Meso Eddies parameterisation (from Baylor)

1 jmc 1.1 C $Header: /u/gcmpack/MITgcm/pkg/gmredi/gmredi_calc_psi_b.F,v 1.11 2011/01/11 00:54:45 jmc Exp $
2     C $Name: $
3    
4     #include "GMREDI_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: SUBMESO_CALC_PSI
8     C !INTERFACE:
9     SUBROUTINE SUBMESO_CALC_PSI(
10     I bi, bj, iMin, iMax, jMin, jMax,
11     I sigmaX, sigmaY, sigmaR,
12     I locMixLayer,
13     I myIter, myThid )
14    
15     C !DESCRIPTION: \bv
16     C *==========================================================*
17     C | SUBROUTINE SUBMESO_CALC_PSI
18     C | o Calculate stream-functions for Sub-Meso bolus velocity
19     C *==========================================================*
20     C | Ref: B. Fox-Kemper etal, Oce.Model., 39:61-78, 2011
21     C | B. Fox-Kemper etal, JPO, 38(6):1145-1165, 2008
22     C *==========================================================*
23     C \ev
24    
25     C !USES:
26     IMPLICIT NONE
27    
28     C == Global variables ==
29     #include "SIZE.h"
30     #include "GRID.h"
31     #include "EEPARAMS.h"
32     #include "PARAMS.h"
33     #include "GMREDI.h"
34    
35     C !INPUT/OUTPUT PARAMETERS:
36     C == Routine arguments ==
37     _RL sigmaX(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
38     _RL sigmaY(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
39     _RL sigmaR(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
40     _RL locMixLayer(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
41     INTEGER bi,bj,iMin,iMax,jMin,jMax
42     INTEGER myIter
43     INTEGER myThid
44     CEOP
45    
46     #ifndef GM_EXCLUDE_SUBMESO
47    
48     C !LOCAL VARIABLES:
49     C == Local variables ==
50     INTEGER i,j,k
51     _RL mixLayerU (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
52     _RL mixLayerV (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
53     _RL dBuoyX_Hu (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
54     _RL dBuoyY_Hv (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
55     _RL NHmixLay (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
56     _RL MsquareH (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
57     _RL lengthScaleF(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
58     _RL fcorLoc (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
59     _RL PsiLoc (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
60     _RL dzLoc, z2H, mu_z
61     _RL five_ov21
62    
63     PARAMETER( five_ov21 = 5. _d 0 / 21. _d 0 )
64    
65     C-- parameter to move to GMREDI.h
66     c _RL subMeso_invTau, subMeso_LfMin, subMeso_Ceff
67     c _RS subMeso_Lmax
68    
69     c subMeso_invTau = 1.6 _d -6 ! ~ 1/(7.2 days)
70     c subMeso_LfMin = 1000. _d 0
71     c subMeso_Ceff = 0.07 _d 0
72     c subMeso_Lmax = 111. _d 3
73    
74     C- Initialization : <= done in S/R gmredi_init
75    
76     c IF ( GM_useSubMeso ) THEN
77     DO j=1-Oly,sNy+Oly
78     DO i=1-Olx+1,sNx+Olx
79     mixLayerU(i,j) = op5*( locMixLayer(i-1,j)+locMixLayer(i,j) )
80     mixLayerU(i,j) = MIN( mixLayerU(i,j), -rLowW(i,j,bi,bj) )
81     ENDDO
82     ENDDO
83     DO j=1-Oly+1,sNy+Oly
84     DO i=1-Olx,sNx+Olx
85     mixLayerV(i,j)=op5*( locMixLayer(i,j-1)+locMixLayer(i,j) )
86     mixLayerV(i,j) = MIN( mixLayerV(i,j), -rLowS(i,j,bi,bj) )
87     ENDDO
88     ENDDO
89    
90     C-- Integrate buoyancy gradient over the Mixed-Layer
91     DO j=1-Oly,sNy+Oly
92     DO i=1-Olx,sNx+Olx
93     dBuoyX_Hu(i,j)= 0.
94     dBuoyY_Hv(i,j)= 0.
95     NHmixLay(i,j) = 0.
96     fcorLoc(i,j) = SQRT( fCori(i,j,bi,bj)*fCori(i,j,bi,bj)
97     & + subMeso_invTau*subMeso_invTau )
98     ENDDO
99     ENDDO
100     DO k=1,Nr
101     DO j=1-Oly,sNy+Oly
102     DO i=1-Olx+1,sNx+Olx
103     dzLoc = MAX( 0. _d 0, MIN( drF(k), mixLayerU(i,j)+rF(k) ) )
104     dBuoyX_Hu(i,j) = dBuoyX_Hu(i,j) + sigmaX(i,j,k)*dzLoc
105     ENDDO
106     ENDDO
107     DO j=1-Oly+1,sNy+Oly
108     DO i=1-Olx,sNx+Olx
109     dzLoc = MAX( 0. _d 0, MIN( drF(k), mixLayerV(i,j)+rF(k) ) )
110     dBuoyY_Hv(i,j) = dBuoyY_Hv(i,j) + sigmaY(i,j,k)*dzLoc
111     ENDDO
112     ENDDO
113     ENDDO
114     DO k=2,Nr
115     DO j=1-Oly,sNy+Oly
116     DO i=1-Olx,sNx+Olx
117     dzLoc = 0.
118     IF ( locMixLayer(i,j)+rC(k-1).GE.0. ) dzLoc = drC(k)
119     NHmixLay(i,j) = NHmixLay(i,j)
120     & + dzLoc*MAX( -sigmaR(i,j,k), 0. _d 0 )
121     ENDDO
122     ENDDO
123     ENDDO
124     DO j=1-Oly,sNy+Oly
125     DO i=1-Olx,sNx+Olx
126     dBuoyX_Hu(i,j)= -dBuoyX_Hu(i,j)*gravity*recip_rhoConst
127     dBuoyY_Hv(i,j)= -dBuoyY_Hv(i,j)*gravity*recip_rhoConst
128     NHmixLay(i,j) = SQRT( NHmixLay(i,j)*gravity*recip_rhoConst
129     & *locMixLayer(i,j) )
130     ENDDO
131     ENDDO
132     DO j=2-Oly,sNy+Oly-1
133     DO i=2-Olx,sNx+Olx-1
134     MsquareH(i,j)= SQRT( op25*(
135     & (dBuoyX_Hu(i,j) + dBuoyX_Hu(i+1,j))**2
136     & + (dBuoyY_Hv(i,j) + dBuoyY_Hv(i,j+1))**2
137     & ) )
138     ENDDO
139     ENDDO
140     C- Compute Lf at grid-cell center
141     DO j=2-Oly,sNy+Oly-1
142     DO i=2-Olx,sNx+Olx-1
143     lengthScaleF(i,j)= MAX(
144     & MsquareH(i,j)/(fcorLoc(i,j)*fcorLoc(i,j)) ,
145     & NHmixLay(i,j)/fcorLoc(i,j) ,
146     & subMeso_LfMin )
147     ENDDO
148     ENDDO
149    
150     C Mix-Layer Eddies contribution to Bolus Transport in X dir.
151     DO j=2-Oly,sNy+Oly-1
152     DO i=3-Olx,sNx+Olx-1
153     PsiLoc(i,j) = -subMeso_Ceff*dBuoyX_Hu(i,j)
154     & *mixLayerU(i,j)
155     & *MIN( dxC(i,j,bi,bj), subMeso_Lmax )
156     & *2. _d 0/(lengthScaleF(i-1,j)+lengthScaleF(i,j))
157     & *2. _d 0/(fcorLoc(i-1,j)+fcorLoc(i,j))
158     ENDDO
159     ENDDO
160     #ifdef GM_BOLUS_ADVEC
161     DO k=2,Nr
162     DO j=2-Oly,sNy+Oly-1
163     DO i=3-Olx,sNx+Olx-1
164     IF ( mixLayerU(i,j).GT.0. _d 0 ) THEN
165     z2H = 2. _d 0*rF(k)/mixLayerU(i,j)
166     ELSE
167     z2H = 0. _d 0
168     ENDIF
169     mu_z = ( z2H + 1. _d 0 )*( z2H + 1. _d 0 )
170     mu_z = ( 1. _d 0 - mu_z )*(1. _d 0 + mu_z*five_ov21 )
171     mu_z = MAX( 0. _d 0, mu_z )
172     GM_PsiX(i,j,k,bi,bj) = GM_PsiX(i,j,k,bi,bj)
173     & + mu_z*PsiLoc(i,j)
174     ENDDO
175     ENDDO
176     ENDDO
177     #endif /* GM_BOLUS_ADVEC */
178     #ifdef ALLOW_DIAGNOSTICS
179     IF ( useDiagnostics ) THEN
180     CALL DIAGNOSTICS_FILL( lengthScaleF, 'SubMesLf',
181     & 0, 1, 2, bi, bj, myThid )
182     CALL DIAGNOSTICS_FILL( PsiLoc, 'SubMpsiX',
183     & 0, 1, 2, bi, bj, myThid )
184     ENDIF
185     #endif
186     IF ( debugLevel.GE.debLevD ) THEN
187     CALL WRITE_LOCAL_RL( 'subMeso_Lf','I10',1,lengthScaleF,
188     & bi,bj,1,myIter,myThid )
189     CALL WRITE_LOCAL_RL( 'subMeso_psiX','I10',1,PsiLoc,
190     & bi,bj,1,myIter,myThid )
191     ENDIF
192    
193     C Mix-Layer Eddies contribution to Bolus Transport in Y dir.
194     DO j=3-Oly,sNy+Oly-1
195     DO i=2-Olx,sNx+Olx-1
196     PsiLoc(i,j) = -subMeso_Ceff*dBuoyY_Hv(i,j)
197     & *mixLayerV(i,j)
198     & *MIN( dyC(i,j,bi,bj), subMeso_Lmax )
199     & *2. _d 0/(lengthScaleF(i,j-1)+lengthScaleF(i,j))
200     & *2. _d 0/(fcorLoc(i,j-1)+fcorLoc(i,j))
201     ENDDO
202     ENDDO
203     #ifdef GM_BOLUS_ADVEC
204     DO k=2,Nr
205     DO j=3-Oly,sNy+Oly-1
206     DO i=2-Olx,sNx+Olx-1
207     IF ( mixLayerV(i,j).GT.0. _d 0 ) THEN
208     z2H = 2. _d 0*rF(k)/mixLayerV(i,j)
209     ELSE
210     z2H = 0. _d 0
211     ENDIF
212     mu_z = ( z2H + 1. _d 0 )*( z2H + 1. _d 0 )
213     mu_z = ( 1. _d 0 - mu_z )*(1. _d 0 + mu_z*five_ov21 )
214     mu_z = MAX( 0. _d 0, mu_z )
215     GM_PsiY(i,j,k,bi,bj) = GM_PsiY(i,j,k,bi,bj)
216     & + mu_z*PsiLoc(i,j)
217     ENDDO
218     ENDDO
219     ENDDO
220     #endif /* GM_BOLUS_ADVEC */
221     #ifdef ALLOW_DIAGNOSTICS
222     IF ( useDiagnostics ) THEN
223     CALL DIAGNOSTICS_FILL( PsiLoc, 'SubMpsiY',
224     & 0, 1, 2, bi, bj, myThid )
225     ENDIF
226     #endif
227     IF ( debugLevel.GE.debLevD ) THEN
228     CALL WRITE_LOCAL_RL( 'subMeso_psiY','I10',1,PsiLoc,
229     & bi,bj,1,myIter,myThid )
230     ENDIF
231    
232     c ENDIF
233     #endif /* ndef GM_EXCLUDE_SUBMESO */
234    
235     RETURN
236     END

  ViewVC Help
Powered by ViewVC 1.1.22