/[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.2 - (hide annotations) (download)
Tue Dec 10 03:00:59 2002 UTC (21 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint47e_post, checkpoint47c_post, checkpoint50c_post, checkpoint48e_post, checkpoint50c_pre, checkpoint48i_post, checkpoint50d_pre, checkpoint51, checkpoint50, checkpoint50d_post, checkpoint50b_pre, checkpoint51f_post, checkpoint48b_post, checkpoint51d_post, checkpoint48c_pre, checkpoint47d_pre, checkpoint48d_pre, checkpoint51j_post, checkpoint47i_post, checkpoint47d_post, checkpoint48d_post, checkpoint48f_post, checkpoint48h_post, checkpoint51b_pre, checkpoint47g_post, checkpoint51h_pre, checkpoint48a_post, checkpoint50f_post, checkpoint50a_post, checkpoint50f_pre, checkpoint47j_post, branch-exfmods-tag, branchpoint-genmake2, checkpoint48c_post, checkpoint51b_post, checkpoint51c_post, checkpoint50g_post, checkpoint50h_post, checkpoint50e_pre, checkpoint50i_post, checkpoint51i_pre, checkpoint47f_post, checkpoint50e_post, checkpoint51e_post, checkpoint48, checkpoint49, checkpoint51f_pre, checkpoint48g_post, checkpoint47h_post, checkpoint51g_post, checkpoint50b_post, checkpoint51a_post
Branch point for: branch-exfmods-curt, branch-genmake2, ecco-branch
Changes since 1.1: +17 -5 lines
 * OCEANICP & realFreshWater: include P-E direct effect on wVel ;
   NOTES: requires option NONLIN_FRSURF to be "#define".

1 jmc 1.2 C $Header: /u/gcmpack/MITgcm/model/src/update_etah.F,v 1.1 2002/10/07 16:17:09 jmc Exp $
2 jmc 1.1 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 jmc 1.2 c IF (useRealFreshWaterFlux .AND. nonlinFreeSurf.GT.0) THEN
54     IF ( (nonlinFreeSurf.GT.0 .OR. buoyancyRelation.EQ.'OCEANICP')
55     & .AND. useRealFreshWaterFlux ) THEN
56 jmc 1.1
57     C-- Called at the beginning of the time step :
58     C- keep present time EmPmR to compute later (S/R EXTERNAL_FORCING_SURF)
59     C tracers and momentum flux associated with fresh water input.
60    
61     IF ( myTime.NE.startTime ) THEN
62     DO j=1-Oly,sNy+Oly
63     DO i=1-Olx,sNx+Olx
64     PmEpR(i,j,bi,bj) = -EmPmR(i,j,bi,bj)
65     ENDDO
66     ENDDO
67    
68 jmc 1.2 ELSE
69 jmc 1.1 DO j=1-Oly,sNy+Oly
70     DO i=1-Olx,sNx+Olx
71     PmEpR(i,j,bi,bj) = 0. _d 0
72     ENDDO
73     ENDDO
74    
75 jmc 1.2 IF( myTime .NE. 0. _d 0 .AND. nonlinFreeSurf.GE.0 ) THEN
76 jmc 1.1 C needs previous time-step value of E-P-R, that has not been loaded
77     C and was not in pickup-file ; try to use etaN & etaH instead.
78     DO j=1,sNy
79     DO i=1,sNx
80     PmEpR(i,j,bi,bj) =
81     & hDivFlow(i,j,bi,bj)*recip_rA(i,j,bi,bj)
82     & + (etaN(i,j,bi,bj)-etaH(i,j,bi,bj))
83     & /(implicDiv2Dflow*deltaTfreesurf)
84 jmc 1.2 PmEpR(i,j,bi,bj) = PmEpR(i,j,bi,bj)/convertEmP2rUnit
85 jmc 1.1 ENDDO
86     ENDDO
87 jmc 1.2 ENDIF
88 jmc 1.1 ENDIF
89    
90     ENDIF
91     #endif /* NONLIN_FRSURF */
92    
93     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
94    
95     C-- Update etaH at the beginning of the time step :
96     C Incorporate the Explicit part of -Divergence(Barotropic_Flow)
97    
98     IF ( useRealFreshWaterFlux .AND. myTime.EQ.startTime ) THEN
99     C needs previous time-step value of E-P-R, that has not been loaded
100     C and was not in pickup-file ; try to use etaN & etaH instead.
101     DO j=1-Oly,sNy+Oly
102     DO i=1-Olx,sNx+Olx
103     etaH(i,j,bi,bj) = etaN(i,j,bi,bj)
104     & + (etaN(i,j,bi,bj)-etaH(i,j,bi,bj))
105     & *(1. - implicDiv2Dflow)/implicDiv2Dflow
106     ENDDO
107     ENDDO
108    
109     ELSEIF (implicDiv2Dflow.EQ. 1. _d 0) THEN
110     DO j=1-Oly,sNy+Oly
111     DO i=1-Olx,sNx+Olx
112     etaH(i,j,bi,bj) = etaN(i,j,bi,bj)
113     ENDDO
114     ENDDO
115    
116     ELSEIF (useRealFreshWaterFlux) THEN
117     DO j=1,sNy
118     DO i=1,sNx
119     etaH(i,j,bi,bj) = etaN(i,j,bi,bj)
120     & - (1. - implicDiv2Dflow)*( convertEmP2rUnit*EmPmR(i,j,bi,bj)
121     & +hDivFlow(i,j,bi,bj)*recip_rA(i,j,bi,bj)
122     & )*deltaTfreesurf
123     ENDDO
124     ENDDO
125    
126     ELSE
127     DO j=1,sNy
128     DO i=1,sNx
129     etaH(i,j,bi,bj) = etaN(i,j,bi,bj)
130     & - (1. - implicDiv2Dflow)*hDivFlow(i,j,bi,bj)
131     & *recip_rA(i,j,bi,bj)*deltaTfreesurf
132     ENDDO
133     ENDDO
134     ENDIF
135    
136     #ifdef ALLOW_OBCS
137     #ifdef NONLIN_FRSURF
138     C- note: 1) needs to apply OBC to etaH since viscous terms depend on hFacZ.
139     C that is not only function of boundaries hFac values.
140     C 2) has to be done before calc_surf_dr; but since obcs_calc is
141     C called later, hFacZ will lag 1 time step behind OBC update.
142     C 3) avoid also unrealistic value of etaH in OB regions that
143     C might produce many "WARNING" message from calc_surf_dr.
144     C-------
145     IF ( useOBCS .AND. nonlinFreeSurf.GT.0 )
146     & CALL OBCS_APPLY_ETA( bi, bj, etaH, myThid )
147     #endif /* NONLIN_FRSURF */
148     #endif /* ALLOW_OBCS */
149    
150     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
151    
152     C- end bi,bj loop.
153     ENDDO
154     ENDDO
155    
156     IF (implicDiv2Dflow .NE. 1. _d 0 .OR. useOBCS )
157 jmc 1.2 & _EXCH_XY_RL(etaH, myThid )
158 jmc 1.1
159     #endif /* EXACT_CONSERV */
160 jmc 1.2
161     #ifdef NONLIN_FRSURF
162     IF ( buoyancyRelation.EQ.'OCEANICP'
163     & .AND. useRealFreshWaterFlux
164     & .AND. myTime.EQ.startTime ) THEN
165     _EXCH_XY_RS(PmEpR, myThid )
166     ENDIF
167     #endif /* NONLIN_FRSURF */
168 jmc 1.1
169     RETURN
170     END

  ViewVC Help
Powered by ViewVC 1.1.22