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

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

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


Revision 1.5 - (show annotations) (download)
Wed Sep 26 18:09:13 2001 UTC (22 years, 9 months ago) by cnh
Branch: MAIN
CVS Tags: ecco-branch-mod1, release1_beta1, checkpoint43, checkpoint41, release1_b1, checkpoint42
Branch point for: ecco-branch, release1, release1_coupled
Changes since 1.4: +27 -14 lines
Bringing comments up to data and formatting for document extraction.

1 C $Header: /u/gcmpack/models/MITgcmUV/model/src/calc_exact_eta.F,v 1.4 2001/09/19 13:58:08 jmc Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: CALC_EXACT_ETA
8 C !INTERFACE:
9 SUBROUTINE CALC_EXACT_ETA( UpdateEtaN_EtaH,
10 I bi,bj, uFld,vFld,
11 I myTime, myIter, myThid )
12 C !DESCRIPTION: \bv
13 C *==========================================================*
14 C | SUBROUTINE CALC_EXACT_ETA
15 C | o Compute again the surface "r-anomaly" (eta) to satisfy
16 C | exactly the convervation of the Total Volume
17 C *==========================================================*
18 C \ev
19
20 C !USES:
21 IMPLICIT NONE
22 C == Global variables
23 #include "SIZE.h"
24 #include "EEPARAMS.h"
25 #include "PARAMS.h"
26 #include "DYNVARS.h"
27 #include "GRID.h"
28 #include "SURFACE.h"
29
30 C !INPUT/OUTPUT PARAMETERS:
31 C == Routine arguments ==
32 C UpdateEtaN_EtaH :: flag to distinguishe if this S/R is called
33 C at the end of a time step (TRUE) to update EtaN,
34 C or at the beginning of the time sptep (FALSE) to update EtaH
35 C uFld :: Zonal velocity ( m/s )
36 C vFld :: Meridional velocity ( m/s )
37 C bi,bj :: tile index
38 C myTime :: Current time in simulation
39 C myIter :: Current iteration number in simulation
40 C myThid :: Thread number for this instance of the routine.
41 _RL myTime
42 INTEGER myIter
43 INTEGER myThid
44 INTEGER bi,bj
45 LOGICAL UpdateEtaN_EtaH
46 _RL uFld(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
47 _RL vFld(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
48
49 C !LOCAL VARIABLES:
50 #ifdef EXACT_CONSERV
51 C Local variables in common block
52 C hDivFlow :: Div. Barotropic Flow at current time [transport unit m3/s]
53 COMMON /EXACT_ETA_LOCAL/ hDivFlow
54 _RL hDivFlow(1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
55
56 C Local variables
57 C i,j,k :: Loop counters
58 C uTrans :: Volume transports ( uVel.xA )
59 C vTrans :: Volume transports ( vVel.yA )
60 INTEGER i,j,k
61 _RL uTrans(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
62 _RL vTrans(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
63 CEOP
64
65 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
66
67 IF ( UpdateEtaN_EtaH .OR. myTime.EQ.StartTime ) THEN
68
69 C-- Compute the Divergence of The Barotropic Flow :
70
71 C- Initialise
72 DO j=1-Oly,sNy+Oly
73 DO i=1-Olx,sNx+Olx
74 hDivFlow(i,j,bi,bj) = 0.
75 ENDDO
76 ENDDO
77
78 DO k=1,Nr
79
80 C- Calculate velocity field "volume transports" through tracer cell faces
81 DO j=1,sNy+1
82 DO i=1,sNx+1
83 uTrans(i,j) = uFld(i,j,k,bi,bj)*_dyG(i,j,bi,bj)
84 & *drF(k)*_hFacW(i,j,k,bi,bj)
85 vTrans(i,j) = vFld(i,j,k,bi,bj)*_dxG(i,j,bi,bj)
86 & *drF(k)*_hFacS(i,j,k,bi,bj)
87 ENDDO
88 ENDDO
89
90 C- Integrate vertically the Horizontal Divergence
91 DO j=1,sNy
92 DO i=1,sNx
93 hDivFlow(i,j,bi,bj) = hDivFlow(i,j,bi,bj)
94 & +maskC(i,j,k,bi,bj)*( uTrans(i+1,j)-uTrans(i,j)
95 & +vTrans(i,j+1)-vTrans(i,j) )
96 ENDDO
97 ENDDO
98
99 C- End DO k=1,Nr
100 ENDDO
101
102 ENDIF
103
104 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
105
106 IF ( UpdateEtaN_EtaH ) THEN
107
108 C-- Update etaN at the end of the time step :
109 C Incorporate the Implicit part of -Divergence(Barotropic_Flow)
110 IF (implicDiv2Dflow .NE. 0. _d 0 ) THEN
111 DO j=1,sNy
112 DO i=1,sNx
113 etaN(i,j,bi,bj) = etaH(i,j,bi,bj)
114 & - implicDiv2Dflow*hDivFlow(i,j,bi,bj)
115 & *recip_rA(i,j,bi,bj)*DeltaTmom
116 ENDDO
117 ENDDO
118 ELSE
119 DO j=1-Oly,sNy+Oly
120 DO i=1-Olx,sNx+Olx
121 etaN(i,j,bi,bj) = etaH(i,j,bi,bj)
122 ENDDO
123 ENDDO
124 ENDIF
125
126 ELSE
127
128 C-- Update etaH at the beginning of the time step :
129 C Incorporate the Explicit part of -Divergence(Barotropic_Flow)
130 IF (implicDiv2Dflow .NE. 1. _d 0 ) THEN
131 DO j=1,sNy
132 DO i=1,sNx
133 etaH(i,j,bi,bj) = etaN(i,j,bi,bj)
134 & - (1. - implicDiv2Dflow)*hDivFlow(i,j,bi,bj)
135 & *recip_rA(i,j,bi,bj)*DeltaTmom
136 ENDDO
137 ENDDO
138 ELSE
139 DO j=1-Oly,sNy+Oly
140 DO i=1-Olx,sNx+Olx
141 etaH(i,j,bi,bj) = etaN(i,j,bi,bj)
142 ENDDO
143 ENDDO
144 ENDIF
145
146 ENDIF
147
148 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
149
150 #endif /* EXACT_CONSERV */
151
152 RETURN
153 END

  ViewVC Help
Powered by ViewVC 1.1.22