/[MITgcm]/MITgcm/model/src/integr_continuity.F
ViewVC logotype

Contents of /MITgcm/model/src/integr_continuity.F

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


Revision 1.1 - (show annotations) (download)
Mon Oct 7 16:17:09 2002 UTC (21 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint46n_post, checkpoint46l_post, checkpoint46l_pre, checkpoint47a_post, checkpoint46j_post, checkpoint46k_post, checkpoint47b_post, checkpoint46m_post, checkpoint47
* split calc_exact_eta in 2 S/R : integr_continuity & update_etaH
* move wVel computation at the end of the time step, in S/R integr_continuity
* create specific S/R to exchange T,S before DYNAMICS (for stagger time step)
* update timeave pkg for wVel diagnostic ; put convertEmP2rUnit in PARAMS.h

1 C $Header: $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: INTEGR_CONTINUITY
8 C !INTERFACE:
9 SUBROUTINE INTEGR_CONTINUITY(
10 I bi, bj, uFld, vFld,
11 I myTime, myIter, myThid )
12 C !DESCRIPTION: \bv
13 C *==========================================================*
14 C | SUBROUTINE INTEGR_CONTINUITY
15 C | o Integrate the continuity Eq : compute vertical velocity
16 C | and free surface "r-anomaly" (etaN) to satisfy
17 C | exactly the convervation of the Total Volume
18 C *==========================================================*
19 C \ev
20
21 C !USES:
22 IMPLICIT NONE
23 C == Global variables
24 #include "SIZE.h"
25 #include "EEPARAMS.h"
26 #include "PARAMS.h"
27 #include "DYNVARS.h"
28 #include "GRID.h"
29 #include "SURFACE.h"
30 #include "FFIELDS.h"
31
32 C !INPUT/OUTPUT PARAMETERS:
33 C == Routine arguments ==
34 C uFld :: Zonal velocity ( m/s )
35 C vFld :: Meridional velocity ( m/s )
36 C bi,bj :: tile index
37 C myTime :: Current time in simulation
38 C myIter :: Current iteration number in simulation
39 C myThid :: Thread number for this instance of the routine.
40 _RL myTime
41 INTEGER myIter
42 INTEGER myThid
43 INTEGER bi,bj
44 LOGICAL UpdateEtaN_EtaH
45 _RL uFld(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
46 _RL vFld(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
47
48 C !LOCAL VARIABLES:
49 C Local variables in common block
50
51 C Local variables
52 C i,j,k :: Loop counters
53 C uTrans :: Volume transports ( uVel.xA )
54 C vTrans :: Volume transports ( vVel.yA )
55 INTEGER i,j,k
56 _RL uTrans(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
57 _RL vTrans(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
58 CEOP
59
60 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
61
62 #ifdef EXACT_CONSERV
63 IF (exactConserv) THEN
64
65 C-- Compute the Divergence of The Barotropic Flow :
66
67 C- Initialise
68 DO j=1-Oly,sNy+Oly
69 DO i=1-Olx,sNx+Olx
70 hDivFlow(i,j,bi,bj) = 0. _d 0
71 utrans(i,j) = 0. _d 0
72 vtrans(i,j) = 0. _d 0
73 ENDDO
74 ENDDO
75
76 DO k=1,Nr
77
78 C- Calculate velocity field "volume transports" through tracer cell faces
79 DO j=1,sNy+1
80 DO i=1,sNx+1
81 uTrans(i,j) = uFld(i,j,k,bi,bj)*_dyG(i,j,bi,bj)
82 & *drF(k)*_hFacW(i,j,k,bi,bj)
83 vTrans(i,j) = vFld(i,j,k,bi,bj)*_dxG(i,j,bi,bj)
84 & *drF(k)*_hFacS(i,j,k,bi,bj)
85 ENDDO
86 ENDDO
87
88 C- Integrate vertically the Horizontal Divergence
89 DO j=1,sNy
90 DO i=1,sNx
91 hDivFlow(i,j,bi,bj) = hDivFlow(i,j,bi,bj)
92 & +maskC(i,j,k,bi,bj)*( uTrans(i+1,j)-uTrans(i,j)
93 & +vTrans(i,j+1)-vTrans(i,j) )
94 ENDDO
95 ENDDO
96
97 C- End DO k=1,Nr
98 ENDDO
99
100 ENDIF
101
102 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
103
104 IF (exactConserv .AND. myTime.NE.startTime) THEN
105 C-- Update etaN at the end of the time step :
106 C Incorporate the Implicit part of -Divergence(Barotropic_Flow)
107
108 IF (implicDiv2Dflow.EQ. 0. _d 0) THEN
109 DO j=1-Oly,sNy+Oly
110 DO i=1-Olx,sNx+Olx
111 etaN(i,j,bi,bj) = etaH(i,j,bi,bj)
112 ENDDO
113 ENDDO
114 ELSEIF (useRealFreshWaterFlux) THEN
115 DO j=1,sNy
116 DO i=1,sNx
117 etaN(i,j,bi,bj) = etaH(i,j,bi,bj)
118 & - implicDiv2Dflow*( convertEmP2rUnit*EmPmR(i,j,bi,bj)
119 & +hDivFlow(i,j,bi,bj)*recip_rA(i,j,bi,bj)
120 & )*deltaTfreesurf
121 ENDDO
122 ENDDO
123 ELSE
124 DO j=1,sNy
125 DO i=1,sNx
126 etaN(i,j,bi,bj) = etaH(i,j,bi,bj)
127 & - implicDiv2Dflow*hDivFlow(i,j,bi,bj)
128 & *recip_rA(i,j,bi,bj)*deltaTfreesurf
129 ENDDO
130 ENDDO
131 ENDIF
132
133 ENDIF
134 #endif /* EXACT_CONSERV */
135
136 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
137
138 DO k=Nr,1,-1
139 C-- Integrate continuity vertically for vertical velocity
140
141 CALL INTEGRATE_FOR_W(
142 I bi, bj, k, uFld, vFld,
143 O wVel,
144 I myThid )
145
146 #ifdef ALLOW_OBCS
147 #ifdef ALLOW_NONHYDROSTATIC
148 C-- Apply OBC to W if in N-H mode
149 IF (useOBCS.AND.nonHydrostatic) THEN
150 CALL OBCS_APPLY_W( bi, bj, k, wVel, myThid )
151 ENDIF
152 #endif /* ALLOW_NONHYDROSTATIC */
153 #endif /* ALLOW_OBCS */
154
155 C- End DO k=Nr,1,-1
156 ENDDO
157
158 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
159
160 RETURN
161 END

  ViewVC Help
Powered by ViewVC 1.1.22