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

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

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

revision 1.12 by jmc, Fri May 20 16:29:49 2011 UTC revision 1.13 by jmc, Thu Dec 8 22:35:43 2011 UTC
# Line 13  C     *================================= Line 13  C     *=================================
13  C     | SUBROUTINE UPDATE_ETAH  C     | SUBROUTINE UPDATE_ETAH
14  C     | o Update etaH after mom-correction-step/integr_continuity  C     | o Update etaH after mom-correction-step/integr_continuity
15  C     |  (required with NLFS to derive surface layer thickness)  C     |  (required with NLFS to derive surface layer thickness)
 C     | o Also derive SSH tendency at grid-cell Western and  
 C     |   Southern edges (for hybrid sigma-coordinate)  
16  C     *==========================================================*  C     *==========================================================*
17  C     \ev  C     \ev
18    
# Line 27  C     == Global variables Line 25  C     == Global variables
25  #include "DYNVARS.h"  #include "DYNVARS.h"
26  #include "GRID.h"  #include "GRID.h"
27  #include "SURFACE.h"  #include "SURFACE.h"
 #include "FFIELDS.h"  
28    
29  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
30  C     == Routine arguments ==  C     == Routine arguments ==
31  C     myTime  :: Current time in simulation  C     myTime  :: Current time in simulation
32  C     myIter  :: Current iteration number in simulation  C     myIter  :: Current iteration number
33  C     myThid  :: Thread number for this instance of the routine.  C     myThid  :: my Thread Id number
34        _RL myTime        _RL myTime
35        INTEGER myIter        INTEGER myIter
36        INTEGER myThid        INTEGER myThid
# Line 47  C     i,j,bi,bj  :: Loop counters Line 44  C     i,j,bi,bj  :: Loop counters
44        INTEGER i,j,bi,bj        INTEGER i,j,bi,bj
45  CEOP  CEOP
46    
47    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
48    
49        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
50         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
51    
 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  
   
52  C--   before updating etaH, save current etaH field in etaHnm1  C--   before updating etaH, save current etaH field in etaHnm1
53           DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
54             DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
55               etaHnm1(i,j,bi,bj) = etaH(i,j,bi,bj)              etaHnm1(i,j,bi,bj) = etaH(i,j,bi,bj)
56             ENDDO            ENDDO
57           ENDDO          ENDDO
58    
59  C--   Update etaH at the end of the time step :  C--   Update etaH at the end of the time step :
60  C     Incorporate the Explicit part of -Divergence(Barotropic_Flow)  C     Incorporate the Explicit part of -Divergence(Barotropic_Flow)
# Line 83  C     Incorporate the Explicit part of - Line 79  C     Incorporate the Explicit part of -
79  #ifdef ALLOW_OBCS  #ifdef ALLOW_OBCS
80  C--    Apply OBC to etaH (NonLin-FreeSurf): needed since viscous terms  C--    Apply OBC to etaH (NonLin-FreeSurf): needed since viscous terms
81  C       depend on hFacZ which is not only function of boundary hFac values.  C       depend on hFacZ which is not only function of boundary hFac values.
82         IF ( useOBCS.AND.nonlinFreeSurf.GT.0 )          IF ( useOBCS.AND.nonlinFreeSurf.GT.0 )
83       &    CALL OBCS_APPLY_ETA( bi, bj, etaH, myThid )       &     CALL OBCS_APPLY_ETA( bi, bj, etaH, myThid )
84  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
85    
 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  
   
86  C- end bi,bj loop.  C- end bi,bj loop.
87         ENDDO         ENDDO
88        ENDDO        ENDDO
89    
90    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
91    
92        IF ( implicDiv2Dflow .NE. 1. _d 0 .OR.        IF ( implicDiv2Dflow .NE. 1. _d 0 .OR.
93       &    ( useOBCS.AND.nonlinFreeSurf.GT.0 ) )       &    ( useOBCS.AND.nonlinFreeSurf.GT.0 ) )
94       &    CALL EXCH_XY_RL( etaH, myThid )       &    CALL EXCH_XY_RL( etaH, myThid )
95    
 c     IF (useRealFreshWaterFlux .AND. myTime.EQ.startTime)  
 c    &    _EXCH_XY_RL( PmEpR, myThid )  
   
 #ifdef NONLIN_FRSURF  
 # ifndef DISABLE_SIGMA_CODE  
       IF ( nonlinFreeSurf.GT.0 .AND. selectSigmaCoord.NE.0 ) THEN  
   
        DO bj=myByLo(myThid),myByHi(myThid)  
         DO bi=myBxLo(myThid),myBxHi(myThid)  
 C-     2nd bi,bj loop :  
   
 C-- copy etaHX -> dEtaXdt  
          DO j=1-Oly,sNy+Oly  
           DO i=1-Olx,sNx+Olx  
             dEtaWdt(i,j,bi,bj) = etaHw(i,j,bi,bj)  
             dEtaSdt(i,j,bi,bj) = etaHs(i,j,bi,bj)  
           ENDDO  
          ENDDO  
   
          DO j=1,sNy+1  
           DO i=1,sNx+1  
             etaHw(i,j,bi,bj)   = ( etaH (i-1,j,bi,bj)  
      &                           + etaH ( i ,j,bi,bj) )*0.5 _d 0  
             etaHs(i,j,bi,bj)   = ( etaH (i,j-1,bi,bj)  
      &                           + etaH (i, j ,bi,bj) )*0.5 _d 0  
 c           etaHw(i,j,bi,bj)   = 0.5 _d 0  
 c    &                         *(   etaH (i-1,j,bi,bj)*rA(i-1,j,bi,bj)  
 c    &                            + etaH ( i ,j,bi,bj)*rA( i ,j,bi,bj)  
 c    &                          )*recip_rAw(i,j,bi,bj)  
 c           etaHs(i,j,bi,bj)   = 0.5 _d 0  
 c    &                         *(   etaH (i,j-1,bi,bj)*rA(i,j-1,bi,bj)  
 c    &                            + etaH (i, j ,bi,bj)*rA(i, j ,bi,bj)  
 c    &                          )*recip_rAs(i,j,bi,bj)  
           ENDDO  
          ENDDO  
   
 C- end 2nd bi,bj loop.  
         ENDDO  
        ENDDO  
   
        CALL EXCH_UV_XY_RL( etaHw, etaHs, .FALSE., myThid )  
        CALL EXCH_XY_RL( dEtaHdt, myThid )  
   
        DO bj=myByLo(myThid),myByHi(myThid)  
         DO bi=myBxLo(myThid),myBxHi(myThid)  
 C-     3rd bi,bj loop :  
   
          DO j=1-Oly,sNy+Oly  
           DO i=1-Olx,sNx+Olx  
             dEtaWdt(i,j,bi,bj) = ( etaHw(i,j,bi,bj)  
      &                           - dEtaWdt(i,j,bi,bj) )/deltaTfreesurf  
             dEtaSdt(i,j,bi,bj) = ( etaHs(i,j,bi,bj)  
      &                           - dEtaSdt(i,j,bi,bj) )/deltaTfreesurf  
           ENDDO  
          ENDDO  
   
 C- end 3rd bi,bj loop.  
         ENDDO  
        ENDDO  
   
       ENDIF  
 # endif /* DISABLE_SIGMA_CODE */  
 #endif /* NONLIN_FRSURF */  
   
96  #endif /* EXACT_CONSERV */  #endif /* EXACT_CONSERV */
97    
98        RETURN        RETURN

Legend:
Removed from v.1.12  
changed lines
  Added in v.1.13

  ViewVC Help
Powered by ViewVC 1.1.22