/[MITgcm]/MITgcm_contrib/bbl/code/mypackage_calc_rhs.F
ViewVC logotype

Annotation of /MITgcm_contrib/bbl/code/mypackage_calc_rhs.F

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


Revision 1.2 - (hide annotations) (download)
Tue Nov 23 07:06:25 2010 UTC (14 years, 7 months ago) by dimitri
Branch: MAIN
Changes since 1.1: +23 -1 lines
added check for salinity conservation at debug level 3

1 dimitri 1.2 C $Header: /u/gcmpack/MITgcm_contrib/bbl/code/mypackage_calc_rhs.F,v 1.1 2010/11/18 04:00:05 dimitri Exp $
2 dimitri 1.1 C $Name: $
3    
4     #include "BBL_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: BBL_CALC_RHS
8    
9     C !INTERFACE:
10     SUBROUTINE MYPACKAGE_CALC_RHS(
11     I bi, bj, myTime, myIter, myThid )
12    
13     C !DESCRIPTION:
14     C Calculate tendency of tracers due to bottom boundary layer.
15     C Scheme is currently coded for dTtracerLev(k) .EQ. deltaT.
16    
17     C !USES:
18     IMPLICIT NONE
19     #include "SIZE.h"
20     #include "EEPARAMS.h"
21     #include "PARAMS.h"
22     #include "GRID.h"
23     #include "DYNVARS.h"
24     #include "BBL.h"
25    
26     C !INPUT PARAMETERS:
27     C bi,bj :: Tile indices
28     C myTime :: Current time in simulation
29     C myIter :: Current time-step number
30     C myThid :: my Thread Id number
31     INTEGER bi, bj
32     _RL myTime
33     INTEGER myIter, myThid
34    
35     C !OUTPUT PARAMETERS:
36    
37     C !LOCAL VARIABLES:
38     C i,j :: Loop indices
39     C kBot :: k index of bottommost wet grid box
40     C resThk :: thickness of bottommost wet grid box minus bbl_eta
41     C resTheta :: temperature of this residual volume
42     C resSalt :: salinity of this residual volume
43     C deltaRho :: density change
44     C deltaDpt :: depth change
45     C bbl_tend :: temporary variable for tendency terms
46     C sloc :: salinity of bottommost wet grid box
47     C tloc :: temperature of bottommost wet grid box
48     C rholoc :: Potential density of bottommost wet grid box
49     C bbl_rho :: Potential density of bottom boundary layer
50     C fZon :: Zonal flux
51     C fMer :: Meridional flux
52     INTEGER i, j, kBot
53     _RL resThk, resTheta, resSalt
54     _RL deltaRho, deltaDpt, bbl_tend
55     _RL sloc ( 1-Olx:sNx+Olx, 1-Oly:sNy+Oly )
56     _RL tloc ( 1-Olx:sNx+Olx, 1-Oly:sNy+Oly )
57     _RL rholoc ( 1-Olx:sNx+Olx, 1-Oly:sNy+Oly )
58     _RL bbl_rho ( 1-Olx:sNx+Olx, 1-Oly:sNy+Oly )
59     _RL fZon ( 1-Olx:sNx+Olx, 1-Oly:sNy+Oly )
60     _RL fMer ( 1-Olx:sNx+Olx, 1-Oly:sNy+Oly )
61 dimitri 1.2 CHARACTER*(MAX_LEN_MBUF) msgBuf
62 dimitri 1.1 CEOP
63    
64     C Initialize tendency terms and
65     C make local copy of bottomost temperature and salinity
66     DO j=1-OLy,sNy+OLy
67     DO i=1-OLx,sNx+OLx
68     bbl_TendTheta(i,j,bi,bj) = 0. _d 0
69     bbl_TendSalt (i,j,bi,bj) = 0. _d 0
70     kBot = max(1,kLowC(i,j,bi,bj))
71     tLoc(i,j) = theta(i,j,kBot,bi,bj)
72     sLoc(i,j) = salt (i,j,kBot,bi,bj)
73     ENDDO
74     ENDDO
75    
76     C Calculate potential density of bottommost wet grid box
77     CALL FIND_RHO_2D(
78     I 1-OLx, sNx+OLx, 1-OLy, sNy+OLy, 1,
79     I tLoc, sLoc,
80     O rhoLoc,
81     I 1, bi, bj, myThid )
82    
83     C Calculate potential density of bbl
84     CALL FIND_RHO_2D(
85     I 1-OLx, sNx+OLx, 1-OLy, sNy+OLy, 1,
86     I bbl_theta(1-OLx,1-OLy,bi,bj), bbl_salt(1-OLx,1-OLy,bi,bj),
87     O bbl_rho,
88     I 1, bi, bj, myThid )
89    
90     C==== Compute and apply vertical exchange between BBL and
91     C residual volume of botommost wet grid box.
92     C This operation does not change total tracer quantity
93     C in botommost wet grid box.
94    
95     DO j=1-Oly,sNy+Oly
96     DO i=1-Olx,sNx+Olx
97     kBot = kLowC(i,j,bi,bj)
98     IF ( kBot .GT. 0 ) THEN
99     resThk = hFacC(i,j,kBot,bi,bj)*drF(kBot) - bbl_eta(i,j,bi,bj)
100    
101     C If bbl occupies the complete bottom model grid box or
102     C if model density is higher than BBL then mix instantly.
103     IF ( (resThk.LE.0) .OR. (rhoLoc(i,j).GE.bbl_rho(i,j)) ) THEN
104     bbl_theta(i,j,bi,bj) = tLoc(i,j)
105     bbl_salt (i,j,bi,bj) = sLoc(i,j)
106    
107     C If model density is lower than BBL, slowly diffuse upward.
108     ELSE
109     resTheta = ( tLoc(i,j) * (resThk+bbl_eta(i,j,bi,bj)) -
110     & (bbl_theta(i,j,bi,bj)*bbl_eta(i,j,bi,bj)) ) / resThk
111     resSalt = ( sLoc(i,j) * (resThk+bbl_eta(i,j,bi,bj)) -
112     & (bbl_salt (i,j,bi,bj)*bbl_eta(i,j,bi,bj)) ) / resThk
113     bbl_theta(i,j,bi,bj) = bbl_theta(i,j,bi,bj) +
114     & deltaT * (resTheta-bbl_theta(i,j,bi,bj)) / bbl_RelaxR
115     bbl_salt (i,j,bi,bj) = bbl_salt (i,j,bi,bj) +
116     & deltaT * (resSalt -bbl_salt (i,j,bi,bj)) / bbl_RelaxR
117     ENDIF
118     ENDIF
119     ENDDO
120     ENDDO
121    
122     C==== Compute zonal bbl exchange.
123     DO j=1-Oly,sNy+Oly
124     DO i=1-Olx,sNx+Olx-1
125     IF ((kLowC(i,j,bi,bj).GT.0).AND.(kLowC(i+1,j,bi,bj).GT.0)) THEN
126     deltaRho = bbl_rho(i+1,j) - bbl_rho(i,j)
127     deltaDpt = R_low(i ,j,bi,bj) + bbl_eta(i ,j,bi,bj) -
128     & R_low(i+1,j,bi,bj) - bbl_eta(i+1,j,bi,bj)
129    
130     C If heavy BBL water is higher than light BBL water,
131     C exchange properties laterally.
132     IF ( (deltaRho*deltaDpt) .LE. 0. ) THEN
133     bbl_TendTheta(i,j,bi,bj) = bbl_TendTheta(i,j,bi,bj) +
134     & ( bbl_theta(i+1,j,bi,bj) - bbl_theta(i,j,bi,bj) ) /
135     & bbl_RelaxH
136     bbl_TendTheta(i+1,j,bi,bj) = bbl_TendTheta(i+1,j,bi,bj) -
137     & ( bbl_theta(i+1,j,bi,bj) - bbl_theta(i,j,bi,bj) ) *
138     & ( rA(i ,j,bi,bj) * bbl_eta(i ,j,bi,bj) ) /
139     & ( rA(i+1,j,bi,bj) * bbl_eta(i+1,j,bi,bj) * bbl_RelaxH )
140     bbl_TendSalt(i,j,bi,bj) = bbl_TendSalt(i,j,bi,bj) +
141     & ( bbl_salt(i+1,j,bi,bj) - bbl_salt(i,j,bi,bj) ) /
142     & bbl_RelaxH
143     bbl_TendSalt(i+1,j,bi,bj) = bbl_TendSalt(i+1,j,bi,bj) -
144     & ( bbl_salt(i+1,j,bi,bj) - bbl_salt(i,j,bi,bj) ) *
145     & ( rA(i ,j,bi,bj) * bbl_eta(i ,j,bi,bj) ) /
146     & ( rA(i+1,j,bi,bj) * bbl_eta(i+1,j,bi,bj) * bbl_RelaxH )
147     ENDIF
148     ENDIF
149     ENDDO
150     ENDDO
151    
152     C==== Compute meridional bbl exchange.
153     DO j=1-Oly,sNy+Oly-1
154     DO i=1-Olx,sNx+Olx
155     IF ((kLowC(i,j,bi,bj).GT.0).AND.(kLowC(i,j+1,bi,bj).GT.0)) THEN
156     deltaRho = bbl_rho(i,j+1) - bbl_rho(i,j)
157     deltaDpt = R_low(i,j ,bi,bj) + bbl_eta(i,j ,bi,bj) -
158     & R_low(i,j+1,bi,bj) - bbl_eta(i,j+1,bi,bj)
159    
160     C If heavy BBL water is higher than light BBL water,
161     C exchange properties laterally.
162     IF ( (deltaRho*deltaDpt) .LE. 0. ) THEN
163     bbl_TendTheta(i,j,bi,bj) = bbl_TendTheta(i,j,bi,bj) +
164     & ( bbl_theta(i,j+1,bi,bj) - bbl_theta(i,j,bi,bj) ) /
165     & bbl_RelaxH
166     bbl_TendTheta(i,j+1,bi,bj) = bbl_TendTheta(i,j+1,bi,bj) -
167     & ( bbl_theta(i,j+1,bi,bj) - bbl_theta(i,j,bi,bj) ) *
168     & ( rA(i ,j,bi,bj) * bbl_eta(i ,j,bi,bj) ) /
169     & ( rA(i,j+1,bi,bj) * bbl_eta(i,j+1,bi,bj) ) /
170     & bbl_RelaxH
171     bbl_TendSalt(i,j,bi,bj) = bbl_TendSalt(i,j,bi,bj) +
172     & ( bbl_salt(i,j+1,bi,bj) - bbl_salt(i,j,bi,bj) ) /
173     & bbl_RelaxH
174     bbl_TendSalt(i,j+1,bi,bj) = bbl_TendSalt(i,j+1,bi,bj) -
175     & ( bbl_salt(i,j+1,bi,bj)-bbl_salt(i,j,bi,bj)) *
176     & ( rA(i ,j,bi,bj) * bbl_eta(i ,j,bi,bj) ) /
177     & ( rA(i,j+1,bi,bj) * bbl_eta(i,j+1,bi,bj) * bbl_RelaxH )
178     ENDIF
179     ENDIF
180     ENDDO
181     ENDDO
182    
183     C==== Apply lateral BBL exchange then scale tendency term
184     C for botommost wet grid box.
185     DO j=1-Oly,sNy+Oly-1
186     DO i=1-Olx,sNx+Olx-1
187     kBot = kLowC(i,j,bi,bj)
188     IF ( kBot .GT. 0 ) THEN
189     bbl_theta(i,j,bi,bj) = bbl_theta(i,j,bi,bj) +
190     & deltaT * bbl_TendTheta(i,j,bi,bj)
191     bbl_salt (i,j,bi,bj) = bbl_salt (i,j,bi,bj) +
192     & deltaT * bbl_TendSalt (i,j,bi,bj)
193     bbl_TendTheta(i,j,bi,bj) = bbl_TendTheta(i,j,bi,bj) *
194     & bbl_eta(i,j,bi,bj) / (hFacC(i,j,kBot,bi,bj)*drF(kBot))
195     bbl_TendSalt (i,j,bi,bj) = bbl_TendSalt (i,j,bi,bj) *
196     & bbl_eta(i,j,bi,bj) / (hFacC(i,j,kBot,bi,bj)*drF(kBot))
197     ENDIF
198     ENDDO
199     ENDDO
200    
201 dimitri 1.2 #ifdef ALLOW_DEBUG
202     IF ( debugLevel .GE. debLevB ) THEN
203     C Check salinity conservation
204     bbl_tend=0
205     DO j=1,sNy
206     DO i=1,sNx
207     kBot = kLowC(i,j,bi,bj)
208     IF ( kBot .GT. 0 ) THEN
209     bbl_tend = bbl_tend + bbl_TendSalt(i,j,bi,bj) *
210     & hFacC(i,j,kBot,bi,bj) * drF(kBot) *rA(i,j,bi,bj)
211     ENDIF
212     ENDDO
213     ENDDO
214     _GLOBAL_SUM_RL( bbl_tend, myThid )
215     WRITE(msgBuf,'(A,E10.2)') 'total salt tendency = ', bbl_tend
216     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
217     & SQUEEZE_RIGHT, myThid )
218     ENDIF
219     #endif /* ALLOW_DEBUG */
220    
221    
222 dimitri 1.1 CALL EXCH_XY_RL( bbl_theta, myThid )
223     CALL EXCH_XY_RL( bbl_salt , myThid )
224    
225     RETURN
226     END

  ViewVC Help
Powered by ViewVC 1.1.22