/[MITgcm]/MITgcm/verification/internal_wave/code/obcs_calc.F
ViewVC logotype

Diff of /MITgcm/verification/internal_wave/code/obcs_calc.F

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

revision 1.4 by jmc, Sat Apr 6 01:33:42 2002 UTC revision 1.8 by jmc, Tue May 24 20:34:01 2011 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "OBCS_OPTIONS.h"  #include "OBCS_OPTIONS.h"
5    
6        SUBROUTINE OBCS_CALC( bi, bj, futureTime, futureIter,        SUBROUTINE OBCS_CALC( futureTime, futureIter,
7       &                      uVel, vVel, wVel, theta, salt,       &                      uVel, vVel, wVel, theta, salt,
8       &                      myThid )       &                      myThid )
9  C     /==========================================================\  C     *==========================================================*
10  C     | SUBROUTINE OBCS_CALC                                     |  C     | SUBROUTINE OBCS_CALC
11  C     | o Calculate future boundary data at open boundaries      |  C     | o Calculate future boundary data at open boundaries
12  C     |   at time = futureTime                                   |  C     |   at time = futureTime
13  C     |==========================================================|  C     *==========================================================*
 C     |                                                          |  
 C     \==========================================================/  
14        IMPLICIT NONE        IMPLICIT NONE
15    
16  C     === Global variables ===  C     === Global variables ===
17  #include "SIZE.h"  #include "SIZE.h"
18  #include "EEPARAMS.h"  #include "EEPARAMS.h"
19  #include "PARAMS.h"  #include "PARAMS.h"
20  #include "OBCS.h"  #include "GRID.h"
21    #include "OBCS_PARAMS.h"
22    #include "OBCS_GRID.h"
23    #include "OBCS_FIELDS.h"
24    #include "EOS.h"
25    
26  C     == Routine arguments ==  C     == Routine arguments ==
       INTEGER bi, bj  
27        INTEGER futureIter        INTEGER futureIter
28        _RL futureTime        _RL futureTime
29        _RL uVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)        _RL uVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
# Line 35  C     == Routine arguments == Line 36  C     == Routine arguments ==
36  #ifdef ALLOW_OBCS  #ifdef ALLOW_OBCS
37    
38  C     == Local variables ==  C     == Local variables ==
39          INTEGER bi, bj
40        INTEGER I, J ,K        INTEGER I, J ,K
   
 #include "GRID.h"  
41        _RL obTimeScale,Uinflow,rampTime2        _RL obTimeScale,Uinflow,rampTime2
42        _RL vertStructWst(Nr)        _RL vertStructWst(Nr)
43        _RL mz,strat,kx        _RL mz,strat,kx
44        _RL tmpsum        _RL tmpsum
45    
46    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
47    
48    #ifdef ALLOW_DEBUG
49          IF (debugMode) CALL DEBUG_ENTER('OBCS_CALC',myThid)
50    #endif
51    
52  C Vertical mode number  C Vertical mode number
53        mz=1.0 _d 0        mz=1.0 _d 0
54  C Stratification  C Stratification
# Line 70  C just to speed things up. You will prob Line 76  C just to speed things up. You will prob
76  C for smoother looking solutions.  C for smoother looking solutions.
77        rampTime2 = 4. _d 0*44567.0 _d 0        rampTime2 = 4. _d 0*44567.0 _d 0
78    
79          DO bj=myByLo(myThid),myByHi(myThid)
80          DO bi=myBxLo(myThid),myBxHi(myThid)
81    
82  C     Eastern OB  C     Eastern OB
83        IF (useOrlanskiEast) THEN        IF (useOrlanskiEast) THEN
84          CALL ORLANSKI_EAST(          CALL ORLANSKI_EAST(
85       &          bi, bj, futureTime,       &          bi, bj, futureTime,
86       &          uVel, vVel, wVel, theta, salt,       &          uVel, vVel, wVel, theta, salt,
87       &          myThid )       &          myThid )
88        ELSE        ELSE
89          DO K=1,Nr          DO K=1,Nr
# Line 94  C     Eastern OB Line 102  C     Eastern OB
102  C     Western OB  C     Western OB
103        IF (useOrlanskiWest) THEN        IF (useOrlanskiWest) THEN
104          CALL ORLANSKI_WEST(          CALL ORLANSKI_WEST(
105       &          bi, bj, futureTime,       &          bi, bj, futureTime,
106       &          uVel, vVel, wVel, theta, salt,       &          uVel, vVel, wVel, theta, salt,
107       &          myThid )       &          myThid )
108        ELSE        ELSE
109          DO K=1,Nr          DO K=1,Nr
# Line 147  c    &  + exp(-futureTime/rampTime2)) Line 155  c    &  + exp(-futureTime/rampTime2))
155  C         Northern OB, template for forcing  C         Northern OB, template for forcing
156        IF (useOrlanskiNorth) THEN        IF (useOrlanskiNorth) THEN
157          CALL ORLANSKI_NORTH(          CALL ORLANSKI_NORTH(
158       &          bi, bj, futureTime,       &          bi, bj, futureTime,
159       &          uVel, vVel, wVel, theta, salt,       &          uVel, vVel, wVel, theta, salt,
160       &          myThid )       &          myThid )
161        ELSE        ELSE
162          DO K=1,Nr          DO K=1,Nr
# Line 165  C         Northern OB, template for forc Line 173  C         Northern OB, template for forc
173        ENDIF        ENDIF
174    
175  C         Southern OB, template for forcing  C         Southern OB, template for forcing
176        IF (useOrlanskiSouth) THEN          IF (useOrlanskiSouth) THEN
177          CALL ORLANSKI_SOUTH(          CALL ORLANSKI_SOUTH(
178       &          bi, bj, futureTime,       &          bi, bj, futureTime,
179       &          uVel, vVel, wVel, theta, salt,       &          uVel, vVel, wVel, theta, salt,
180       &          myThid )       &          myThid )
181        ELSE        ELSE
182          DO K=1,Nr          DO K=1,Nr
# Line 184  C         Southern OB, template for forc Line 192  C         Southern OB, template for forc
192          ENDDO          ENDDO
193        ENDIF        ENDIF
194    
195    C--   end bi,bj loops.
196          ENDDO
197          ENDDO
198    
199    #ifdef ALLOW_OBCS_BALANCE
200          IF ( useOBCSbalance ) THEN
201            CALL OBCS_BALANCE_FLOW( futureTime, futureIter, myThid )
202          ENDIF
203    #endif /* ALLOW_OBCS_BALANCE */
204    
205    #ifdef ALLOW_DEBUG
206          IF (debugMode) CALL DEBUG_LEAVE('OBCS_CALC',myThid)
207    #endif
208  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
209    
210        RETURN        RETURN
211        END        END

Legend:
Removed from v.1.4  
changed lines
  Added in v.1.8

  ViewVC Help
Powered by ViewVC 1.1.22