/[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.6 - (show annotations) (download)
Thu Nov 8 20:57:51 2001 UTC (22 years, 10 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint43a-release1mods, release1-branch_tutorials, release1-branch-end, checkpoint44, release1-branch_branchpoint
Branch point for: release1-branch
Changes since 1.5: +5 -6 lines
Preparing adjoint of Held-Suarez:
- bugfix for storing in absence of CD code
- adding EXACT_CONSERV to AD list
- new routine ini_autodiff to add TAMC-specific initialisations
- adding Shapiro filter to AD list

1 C $Header: /u/gcmpack/models/MITgcmUV/model/src/calc_exact_eta.F,v 1.5 2001/09/26 18:09:13 cnh Exp $
2 C $Name: checkpoint43 $
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
53 C Local variables
54 C i,j,k :: Loop counters
55 C uTrans :: Volume transports ( uVel.xA )
56 C vTrans :: Volume transports ( vVel.yA )
57 INTEGER i,j,k
58 _RL uTrans(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
59 _RL vTrans(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
60 CEOP
61
62 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
63
64 IF ( UpdateEtaN_EtaH .OR. myTime.EQ.StartTime ) THEN
65
66 C-- Compute the Divergence of The Barotropic Flow :
67
68 C- Initialise
69 DO j=1-Oly,sNy+Oly
70 DO i=1-Olx,sNx+Olx
71 hDivFlow(i,j,bi,bj) = 0. _d 0
72 utrans(i,j) = 0. _d 0
73 vtrans(i,j) = 0. _d 0
74 ENDDO
75 ENDDO
76
77 DO k=1,Nr
78
79 C- Calculate velocity field "volume transports" through tracer cell faces
80 DO j=1,sNy+1
81 DO i=1,sNx+1
82 uTrans(i,j) = uFld(i,j,k,bi,bj)*_dyG(i,j,bi,bj)
83 & *drF(k)*_hFacW(i,j,k,bi,bj)
84 vTrans(i,j) = vFld(i,j,k,bi,bj)*_dxG(i,j,bi,bj)
85 & *drF(k)*_hFacS(i,j,k,bi,bj)
86 ENDDO
87 ENDDO
88
89 C- Integrate vertically the Horizontal Divergence
90 DO j=1,sNy
91 DO i=1,sNx
92 hDivFlow(i,j,bi,bj) = hDivFlow(i,j,bi,bj)
93 & +maskC(i,j,k,bi,bj)*( uTrans(i+1,j)-uTrans(i,j)
94 & +vTrans(i,j+1)-vTrans(i,j) )
95 ENDDO
96 ENDDO
97
98 C- End DO k=1,Nr
99 ENDDO
100
101 ENDIF
102
103 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
104
105 IF ( UpdateEtaN_EtaH ) THEN
106
107 C-- Update etaN at the end of the time step :
108 C Incorporate the Implicit part of -Divergence(Barotropic_Flow)
109 IF (implicDiv2Dflow .NE. 0. _d 0 ) THEN
110 DO j=1,sNy
111 DO i=1,sNx
112 etaN(i,j,bi,bj) = etaH(i,j,bi,bj)
113 & - implicDiv2Dflow*hDivFlow(i,j,bi,bj)
114 & *recip_rA(i,j,bi,bj)*DeltaTmom
115 ENDDO
116 ENDDO
117 ELSE
118 DO j=1-Oly,sNy+Oly
119 DO i=1-Olx,sNx+Olx
120 etaN(i,j,bi,bj) = etaH(i,j,bi,bj)
121 ENDDO
122 ENDDO
123 ENDIF
124
125 ELSE
126
127 C-- Update etaH at the beginning of the time step :
128 C Incorporate the Explicit part of -Divergence(Barotropic_Flow)
129 IF (implicDiv2Dflow .NE. 1. _d 0 ) THEN
130 DO j=1,sNy
131 DO i=1,sNx
132 etaH(i,j,bi,bj) = etaN(i,j,bi,bj)
133 & - (1. - implicDiv2Dflow)*hDivFlow(i,j,bi,bj)
134 & *recip_rA(i,j,bi,bj)*DeltaTmom
135 ENDDO
136 ENDDO
137 ELSE
138 DO j=1-Oly,sNy+Oly
139 DO i=1-Olx,sNx+Olx
140 etaH(i,j,bi,bj) = etaN(i,j,bi,bj)
141 ENDDO
142 ENDDO
143 ENDIF
144
145 ENDIF
146
147 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
148
149 #endif /* EXACT_CONSERV */
150
151 RETURN
152 END

  ViewVC Help
Powered by ViewVC 1.1.22