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

Annotation of /MITgcm/model/src/update_etah.F

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


Revision 1.1 - (hide 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 jmc 1.1 C $Header: $
2     C $Name: $
3    
4     #include "CPP_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: UPDATE_ETAH
8     C !INTERFACE:
9     SUBROUTINE UPDATE_ETAH( myTime, myIter, myThid )
10     C !DESCRIPTION: \bv
11     C *==========================================================*
12     C | SUBROUTINE UPDATE_ETAH
13     C | o Update etaH at the begining of the time step.
14     C | (required with NLFS to derive surface layer thickness)
15     C *==========================================================*
16     C \ev
17    
18     C !USES:
19     IMPLICIT NONE
20     C == Global variables
21     #include "SIZE.h"
22     #include "EEPARAMS.h"
23     #include "PARAMS.h"
24     #include "DYNVARS.h"
25     #include "GRID.h"
26     #include "SURFACE.h"
27     #include "FFIELDS.h"
28    
29     C !INPUT/OUTPUT PARAMETERS:
30     C == Routine arguments ==
31     C myTime :: Current time in simulation
32     C myIter :: Current iteration number in simulation
33     C myThid :: Thread number for this instance of the routine.
34     _RL myTime
35     INTEGER myIter
36     INTEGER myThid
37    
38     C !LOCAL VARIABLES:
39     #ifdef EXACT_CONSERV
40     C Local variables in common block
41    
42     C Local variables
43     C i,j,k,bi,bj :: Loop counters
44     INTEGER i,j,k,bi,bj
45     CEOP
46    
47    
48     DO bj=myByLo(myThid),myByHi(myThid)
49     DO bi=myBxLo(myThid),myBxHi(myThid)
50     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
51    
52     #ifdef NONLIN_FRSURF
53     IF (useRealFreshWaterFlux .AND. nonlinFreeSurf.GT.0) THEN
54    
55     C-- Called at the beginning of the time step :
56     C- keep present time EmPmR to compute later (S/R EXTERNAL_FORCING_SURF)
57     C tracers and momentum flux associated with fresh water input.
58    
59     IF ( myTime.NE.startTime ) THEN
60     DO j=1-Oly,sNy+Oly
61     DO i=1-Olx,sNx+Olx
62     PmEpR(i,j,bi,bj) = -EmPmR(i,j,bi,bj)
63     ENDDO
64     ENDDO
65    
66     ELSEIF( myTime .EQ. 0. _d 0 ) THEN
67     DO j=1-Oly,sNy+Oly
68     DO i=1-Olx,sNx+Olx
69     PmEpR(i,j,bi,bj) = 0. _d 0
70     ENDDO
71     ENDDO
72    
73     ELSE
74     C needs previous time-step value of E-P-R, that has not been loaded
75     C and was not in pickup-file ; try to use etaN & etaH instead.
76     DO j=1,sNy
77     DO i=1,sNx
78     PmEpR(i,j,bi,bj) =
79     & hDivFlow(i,j,bi,bj)*recip_rA(i,j,bi,bj)
80     & + (etaN(i,j,bi,bj)-etaH(i,j,bi,bj))
81     & /(implicDiv2Dflow*deltaTfreesurf)
82     ENDDO
83     ENDDO
84     ENDIF
85    
86     ENDIF
87     #endif /* NONLIN_FRSURF */
88    
89     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
90    
91     C-- Update etaH at the beginning of the time step :
92     C Incorporate the Explicit part of -Divergence(Barotropic_Flow)
93    
94     IF ( useRealFreshWaterFlux .AND. myTime.EQ.startTime ) THEN
95     C needs previous time-step value of E-P-R, that has not been loaded
96     C and was not in pickup-file ; try to use etaN & etaH instead.
97     DO j=1-Oly,sNy+Oly
98     DO i=1-Olx,sNx+Olx
99     etaH(i,j,bi,bj) = etaN(i,j,bi,bj)
100     & + (etaN(i,j,bi,bj)-etaH(i,j,bi,bj))
101     & *(1. - implicDiv2Dflow)/implicDiv2Dflow
102     ENDDO
103     ENDDO
104    
105     ELSEIF (implicDiv2Dflow.EQ. 1. _d 0) THEN
106     DO j=1-Oly,sNy+Oly
107     DO i=1-Olx,sNx+Olx
108     etaH(i,j,bi,bj) = etaN(i,j,bi,bj)
109     ENDDO
110     ENDDO
111    
112     ELSEIF (useRealFreshWaterFlux) THEN
113     DO j=1,sNy
114     DO i=1,sNx
115     etaH(i,j,bi,bj) = etaN(i,j,bi,bj)
116     & - (1. - implicDiv2Dflow)*( convertEmP2rUnit*EmPmR(i,j,bi,bj)
117     & +hDivFlow(i,j,bi,bj)*recip_rA(i,j,bi,bj)
118     & )*deltaTfreesurf
119     ENDDO
120     ENDDO
121    
122     ELSE
123     DO j=1,sNy
124     DO i=1,sNx
125     etaH(i,j,bi,bj) = etaN(i,j,bi,bj)
126     & - (1. - implicDiv2Dflow)*hDivFlow(i,j,bi,bj)
127     & *recip_rA(i,j,bi,bj)*deltaTfreesurf
128     ENDDO
129     ENDDO
130     ENDIF
131    
132     #ifdef ALLOW_OBCS
133     #ifdef NONLIN_FRSURF
134     C- note: 1) needs to apply OBC to etaH since viscous terms depend on hFacZ.
135     C that is not only function of boundaries hFac values.
136     C 2) has to be done before calc_surf_dr; but since obcs_calc is
137     C called later, hFacZ will lag 1 time step behind OBC update.
138     C 3) avoid also unrealistic value of etaH in OB regions that
139     C might produce many "WARNING" message from calc_surf_dr.
140     C-------
141     IF ( useOBCS .AND. nonlinFreeSurf.GT.0 )
142     & CALL OBCS_APPLY_ETA( bi, bj, etaH, myThid )
143     #endif /* NONLIN_FRSURF */
144     #endif /* ALLOW_OBCS */
145    
146     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
147    
148     C- end bi,bj loop.
149     ENDDO
150     ENDDO
151    
152     IF (implicDiv2Dflow .NE. 1. _d 0 .OR. useOBCS )
153     & _EXCH_XY_R8(etaH, myThid )
154    
155     #endif /* EXACT_CONSERV */
156    
157     RETURN
158     END

  ViewVC Help
Powered by ViewVC 1.1.22