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

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

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

revision 1.16 by heimbach, Thu Dec 8 15:44:34 2005 UTC revision 1.17 by jmc, Sat Jul 22 03:53:13 2006 UTC
# Line 12  C     !INTERFACE: Line 12  C     !INTERFACE:
12       I                             myTime, myIter, myThid )       I                             myTime, myIter, myThid )
13  C     !DESCRIPTION: \bv  C     !DESCRIPTION: \bv
14  C     *==========================================================*  C     *==========================================================*
15  C     | SUBROUTINE INTEGR_CONTINUITY                                  C     | SUBROUTINE INTEGR_CONTINUITY
16  C     | o Integrate the continuity Eq : compute vertical velocity  C     | o Integrate the continuity Eq : compute vertical velocity
17  C     |   and free surface "r-anomaly" (etaN) to satisfy    C     |   and free surface "r-anomaly" (etaN) to satisfy
18  C     |   exactly the convervation of the Total Volume              C     |   exactly the convervation of the Total Volume
19  C     *==========================================================*  C     *==========================================================*
20  C     \ev  C     \ev
21    
# Line 43  C     myThid  :: Thread number for this Line 43  C     myThid  :: Thread number for this
43        INTEGER myThid        INTEGER myThid
44        INTEGER bi,bj        INTEGER bi,bj
45        _RL uFld(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)        _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)        _RL vFld(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
47    
48  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
49  C     Local variables in common block  C     Local variables in common block
# Line 67  C---+----1----+----2----+----3----+----4 Line 67  C---+----1----+----2----+----3----+----4
67    
68  C--   Compute the Divergence of The Barotropic Flow :  C--   Compute the Divergence of The Barotropic Flow :
69    
70  C-    Initialise  C-    Initialise
71        DO j=1-Oly,sNy+Oly        DO j=1-Oly,sNy+Oly
72         DO i=1-Olx,sNx+Olx         DO i=1-Olx,sNx+Olx
73           hDivFlow(i,j)      = 0. _d 0           hDivFlow(i,j)      = 0. _d 0
# Line 77  C-    Initialise Line 77  C-    Initialise
77        ENDDO        ENDDO
78    
79        DO k=1,Nr        DO k=1,Nr
80          
81  C-    Calculate velocity field "volume transports" through tracer cell faces  C-    Calculate velocity field "volume transports" through tracer cell faces
82          DO j=1,sNy+1          DO j=1,sNy+1
83           DO i=1,sNx+1           DO i=1,sNx+1
# Line 88  C-    Calculate velocity field "volume t Line 88  C-    Calculate velocity field "volume t
88           ENDDO           ENDDO
89          ENDDO          ENDDO
90    
91  C-    Integrate vertically the Horizontal Divergence  C-    Integrate vertically the Horizontal Divergence
92          DO j=1,sNy          DO j=1,sNy
93           DO i=1,sNx           DO i=1,sNx
94             hDivFlow(i,j) = hDivFlow(i,j)             hDivFlow(i,j) = hDivFlow(i,j)
# Line 130  C     and was not in old pickup-file ; t Line 130  C     and was not in old pickup-file ; t
130              PmEpR(i,j,bi,bj) = 0. _d 0              PmEpR(i,j,bi,bj) = 0. _d 0
131              dEtaHdt(i,j,bi,bj) = -hDivFlow(i,j)*recip_rA(i,j,bi,bj)              dEtaHdt(i,j,bi,bj) = -hDivFlow(i,j)*recip_rA(i,j,bi,bj)
132            ENDDO            ENDDO
133           ENDDO                 ENDDO
134         ELSE         ELSE
135    C--    Needs to get valid PmEpR (for T,S forcing) also in overlap regions
136    C       (e.g., if using KPP) => set over full index range
137             DO j=1-OLy,sNy+OLy
138              DO i=1-OLx,sNx+OLx
139                PmEpR(i,j,bi,bj) = -EmPmR(i,j,bi,bj)
140              ENDDO
141             ENDDO
142           DO j=1,sNy           DO j=1,sNy
143            DO i=1,sNx            DO i=1,sNx
             PmEpR(i,j,bi,bj) = -EmPmR(i,j,bi,bj)  
144              dEtaHdt(i,j,bi,bj) = -hDivFlow(i,j)*recip_rA(i,j,bi,bj)              dEtaHdt(i,j,bi,bj) = -hDivFlow(i,j)*recip_rA(i,j,bi,bj)
145       &                           -facEmP*EmPmR(i,j,bi,bj)       &                           -facEmP*EmPmR(i,j,bi,bj)
146            ENDDO            ENDDO
# Line 147  C------------------------------------ Line 153  C------------------------------------
153  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
154    
155        IF (exactConserv .AND. myTime.NE.startTime) THEN        IF (exactConserv .AND. myTime.NE.startTime) THEN
156  C--   Update etaN at the end of the time step :  C--   Update etaN at the end of the time step :
157  C     Incorporate the Implicit part of -Divergence(Barotropic_Flow)  C     Incorporate the Implicit part of -Divergence(Barotropic_Flow)
158    
159         IF (implicDiv2Dflow.EQ. 0. _d 0) THEN         IF (implicDiv2Dflow.EQ. 0. _d 0) THEN
160          DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
161           DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
162             etaN(i,j,bi,bj) = etaH(i,j,bi,bj)             etaN(i,j,bi,bj) = etaH(i,j,bi,bj)
163           ENDDO           ENDDO
164          ENDDO          ENDDO
165         ELSE         ELSE
# Line 168  C     Incorporate the Implicit part of - Line 174  C     Incorporate the Implicit part of -
174  #ifdef ALLOW_OBCS  #ifdef ALLOW_OBCS
175  C--    Apply OBC to etaN if NonLin-FreeSurf, reset to zero otherwise:  C--    Apply OBC to etaN if NonLin-FreeSurf, reset to zero otherwise:
176         IF ( useOBCS ) CALL OBCS_APPLY_ETA( bi, bj, etaN, myThid )         IF ( useOBCS ) CALL OBCS_APPLY_ETA( bi, bj, etaN, myThid )
177  #endif /* ALLOW_OBCS */              #endif /* ALLOW_OBCS */
178    
179        ENDIF        ENDIF
180    
# Line 198  C--    Integrate continuity vertically f Line 204  C--    Integrate continuity vertically f
204       I                       bi, bj, k, uFld, vFld,       I                       bi, bj, k, uFld, vFld,
205       O                       wVel,       O                       wVel,
206       I                       myThid )       I                       myThid )
207    
208  #ifdef EXACT_CONSERV  #ifdef EXACT_CONSERV
209         IF ( k.EQ.Nr .AND. myTime.NE.baseTime .AND.         IF ( k.EQ.Nr .AND. myTime.NE.baseTime .AND.
210       &      useRealFreshWaterFlux .AND. usingPCoords ) THEN       &      useRealFreshWaterFlux .AND. usingPCoords ) THEN
211    
212            DO j=1,sNy            DO j=1,sNy
213             DO i=1,sNx             DO i=1,sNx
214               wVel(i,j,k,bi,bj) = wVel(i,j,k,bi,bj)               wVel(i,j,k,bi,bj) = wVel(i,j,k,bi,bj)
215       &         +convertEmP2rUnit*PmEpR(i,j,bi,bj)*maskC(i,j,k,bi,bj)       &         +convertEmP2rUnit*PmEpR(i,j,bi,bj)*maskC(i,j,k,bi,bj)
216             ENDDO             ENDDO
217            ENDDO            ENDDO
# Line 216  C--    Integrate continuity vertically f Line 222  C--    Integrate continuity vertically f
222  #ifdef ALLOW_OBCS  #ifdef ALLOW_OBCS
223  C--    Apply OBC to W if in N-H mode, reset to zero otherwise:  C--    Apply OBC to W if in N-H mode, reset to zero otherwise:
224         IF ( useOBCS ) CALL OBCS_APPLY_W( bi, bj, k, wVel, myThid )         IF ( useOBCS ) CALL OBCS_APPLY_W( bi, bj, k, wVel, myThid )
225  #endif /* ALLOW_OBCS */              #endif /* ALLOW_OBCS */
226    
227  C-    End DO k=Nr,1,-1  C-    End DO k=Nr,1,-1
228        ENDDO        ENDDO

Legend:
Removed from v.1.16  
changed lines
  Added in v.1.17

  ViewVC Help
Powered by ViewVC 1.1.22