/[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.4 - (hide annotations) (download)
Tue Jun 29 22:21:43 2004 UTC (19 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint54, checkpoint54a_pre, checkpoint53g_post
Changes since 1.3: +4 -58 lines
store d.etaH/dt (instead of Div.hV) in common ; clean-up integr_continuity

1 jmc 1.4 C $Header: /u/gcmpack/MITgcm/model/src/update_etah.F,v 1.3 2003/10/09 04:19:18 edhill Exp $
2 jmc 1.1 C $Name: $
3    
4 edhill 1.3 #include "PACKAGES_CONFIG.h"
5 jmc 1.1 #include "CPP_OPTIONS.h"
6    
7     CBOP
8     C !ROUTINE: UPDATE_ETAH
9     C !INTERFACE:
10     SUBROUTINE UPDATE_ETAH( myTime, myIter, myThid )
11     C !DESCRIPTION: \bv
12     C *==========================================================*
13     C | SUBROUTINE UPDATE_ETAH
14     C | o Update etaH at the begining of the time step.
15     C | (required with NLFS to derive surface layer thickness)
16     C *==========================================================*
17     C \ev
18    
19     C !USES:
20     IMPLICIT NONE
21     C == Global variables
22     #include "SIZE.h"
23     #include "EEPARAMS.h"
24     #include "PARAMS.h"
25     #include "DYNVARS.h"
26     #include "GRID.h"
27     #include "SURFACE.h"
28     #include "FFIELDS.h"
29    
30     C !INPUT/OUTPUT PARAMETERS:
31     C == Routine arguments ==
32     C myTime :: Current time in simulation
33     C myIter :: Current iteration number in simulation
34     C myThid :: Thread number for this instance of the routine.
35     _RL myTime
36     INTEGER myIter
37     INTEGER myThid
38    
39     C !LOCAL VARIABLES:
40     #ifdef EXACT_CONSERV
41     C Local variables in common block
42    
43     C Local variables
44     C i,j,k,bi,bj :: Loop counters
45     INTEGER i,j,k,bi,bj
46     CEOP
47    
48    
49     DO bj=myByLo(myThid),myByHi(myThid)
50     DO bi=myBxLo(myThid),myBxHi(myThid)
51    
52     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
53    
54     C-- Update etaH at the beginning of the time step :
55     C Incorporate the Explicit part of -Divergence(Barotropic_Flow)
56    
57     IF ( useRealFreshWaterFlux .AND. myTime.EQ.startTime ) THEN
58     C needs previous time-step value of E-P-R, that has not been loaded
59     C and was not in pickup-file ; try to use etaN & etaH instead.
60     DO j=1-Oly,sNy+Oly
61     DO i=1-Olx,sNx+Olx
62     etaH(i,j,bi,bj) = etaN(i,j,bi,bj)
63     & + (etaN(i,j,bi,bj)-etaH(i,j,bi,bj))
64     & *(1. - implicDiv2Dflow)/implicDiv2Dflow
65     ENDDO
66     ENDDO
67    
68     ELSEIF (implicDiv2Dflow.EQ. 1. _d 0) THEN
69     DO j=1-Oly,sNy+Oly
70     DO i=1-Olx,sNx+Olx
71     etaH(i,j,bi,bj) = etaN(i,j,bi,bj)
72     ENDDO
73     ENDDO
74    
75     ELSE
76     DO j=1,sNy
77     DO i=1,sNx
78     etaH(i,j,bi,bj) = etaN(i,j,bi,bj)
79 jmc 1.4 & + (1. - implicDiv2Dflow)*dEtaHdt(i,j,bi,bj)
80     & *deltaTfreesurf
81 jmc 1.1 ENDDO
82     ENDDO
83     ENDIF
84    
85     #ifdef ALLOW_OBCS
86     #ifdef NONLIN_FRSURF
87     C- note: 1) needs to apply OBC to etaH since viscous terms depend on hFacZ.
88     C that is not only function of boundaries hFac values.
89     C 2) has to be done before calc_surf_dr; but since obcs_calc is
90     C called later, hFacZ will lag 1 time step behind OBC update.
91     C 3) avoid also unrealistic value of etaH in OB regions that
92     C might produce many "WARNING" message from calc_surf_dr.
93     C-------
94     IF ( useOBCS .AND. nonlinFreeSurf.GT.0 )
95     & CALL OBCS_APPLY_ETA( bi, bj, etaH, myThid )
96     #endif /* NONLIN_FRSURF */
97     #endif /* ALLOW_OBCS */
98    
99     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
100    
101     C- end bi,bj loop.
102     ENDDO
103     ENDDO
104    
105     IF (implicDiv2Dflow .NE. 1. _d 0 .OR. useOBCS )
106 jmc 1.2 & _EXCH_XY_RL(etaH, myThid )
107 jmc 1.1
108 jmc 1.2
109     IF ( buoyancyRelation.EQ.'OCEANICP'
110     & .AND. useRealFreshWaterFlux
111     & .AND. myTime.EQ.startTime ) THEN
112     _EXCH_XY_RS(PmEpR, myThid )
113     ENDIF
114 jmc 1.4 #endif /* EXACT_CONSERV */
115 jmc 1.1
116     RETURN
117     END

  ViewVC Help
Powered by ViewVC 1.1.22