/[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.2 by adcroft, Fri Feb 2 21:36:34 2001 UTC revision 1.4 by jmc, Sat Apr 6 01:33:42 2002 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,        SUBROUTINE OBCS_CALC( bi, bj, futureTime, futureIter,
7       &                      uVel, vVel, wVel, theta, salt,       &                      uVel, vVel, wVel, theta, salt,
8       &                      myThid )       &                      myThid )
9  C     /==========================================================\  C     /==========================================================\
# Line 23  C     === Global variables === Line 23  C     === Global variables ===
23    
24  C     == Routine arguments ==  C     == Routine arguments ==
25        INTEGER bi, bj        INTEGER bi, bj
26          INTEGER futureIter
27        _RL futureTime        _RL futureTime
28        _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)
29        _RL vVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)        _RL vVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
# Line 43  C     == Local variables == Line 44  C     == Local variables ==
44        _RL tmpsum        _RL tmpsum
45    
46  C Vertical mode number  C Vertical mode number
47        mz=1.0        mz=1.0 _d 0
48  C Stratification  C Stratification
49        strat = 1.0 _d -6 / (gravity*tAlpha)        strat = 1.0 _d -6 / (gravity*tAlpha)
50    
# Line 58  C Create a vertical structure function w Line 59  C Create a vertical structure function w
59         vertStructWst(K)=vertStructWst(K)-tmpsum         vertStructWst(K)=vertStructWst(K)-tmpsum
60        enddo        enddo
61  c  c
62        obTimeScale = 44567.0        obTimeScale = 44567.0 _d 0
63         kx=mz*2.*pi/400.0*sqrt((2.0*pi*2.0*pi/(obTimeScale*obTimeScale)         kx=mz*2. _d 0*pi/400.0 _d 0
64         &  *sqrt((2.0 _d 0*pi*2.0 _d 0*pi/(obTimeScale*obTimeScale)
65       & - f0*f0)/(1.0 _d -6       & - f0*f0)/(1.0 _d -6
66       & - 2.0*pi*2.0*pi/(obTimeScale*obTimeScale)))       & - 2.0 _d 0*pi*2.0 _d 0*pi/(obTimeScale*obTimeScale)))
67        Uinflow = 0.024        Uinflow = 0.024 _d 0
68        rampTime2 = 4*44567.0  C *NOTE* I have commented out the ramp function below
69    C just to speed things up. You will probably want to use it
70    C for smoother looking solutions.
71          rampTime2 = 4. _d 0*44567.0 _d 0
72    
73    
74  C     Eastern OB  C     Eastern OB
# Line 95  C     Western OB Line 100  C     Western OB
100        ELSE        ELSE
101          DO K=1,Nr          DO K=1,Nr
102            DO J=1-Oly,sNy+Oly            DO J=1-Oly,sNy+Oly
103            OBWu(J,K,bi,bj)=0.            OBWu(J,K,bi,bj)=0. _d 0
104       &       +Uinflow       &       +Uinflow
105       &       *vertStructWst(K)       &       *vertStructWst(K)
106       &       *sin(2.*PI*futureTime/obTimeScale)       &       *sin(2. _d 0*PI*futureTime/obTimeScale)
107       &       *(exp(futureTime/rampTime2)  c    &       *(exp(futureTime/rampTime2)
108       &   - exp(-futureTime/rampTime2))  c    &   - exp(-futureTime/rampTime2))
109       &   /(exp(futureTime/rampTime2)  c    &   /(exp(futureTime/rampTime2)
110       &  + exp(-futureTime/rampTime2))  c    &  + exp(-futureTime/rampTime2))
111       &   *cos(kx*(3-2-0.5)*delX(1))       &   *cos(kx*(3. _d 0-2. _d 0-0.5 _d 0)*delX(1))
112            OBWv(J,K,bi,bj)=0.            OBWv(J,K,bi,bj)=0. _d 0
113       &       +Uinflow       &       +Uinflow
114       &       *f0/(2.0*PI/obTimeScale)       &       *f0/(2.0 _d 0*PI/obTimeScale)
115       &       *vertStructWst(K)       &       *vertStructWst(K)
116       &       *cos(2.*PI*futureTime/obTimeScale )       &       *cos(2. _d 0*PI*futureTime/obTimeScale )
117       & * (exp(futureTime/rampTime2)       & * (exp(futureTime/rampTime2)
118       &   - exp(-futureTime/rampTime2))       &   - exp(-futureTime/rampTime2))
119       &   /(exp(futureTime/rampTime2)       &   /(exp(futureTime/rampTime2)
120       &  + exp(-futureTime/rampTime2))       &  + exp(-futureTime/rampTime2))
121            OBWt(J,K,bi,bj)=tRef(K)            OBWt(J,K,bi,bj)=tRef(K)
122       & + Uinflow*sin(mz*PI*(float(k)-0.5)/float(Nr))       & + Uinflow*sin(mz*PI*(float(k)-0.5 _d 0)/float(Nr))
123       & * sin(2.0*PI*futureTime/obTimeScale)       & * sin(2.0 _d 0*PI*futureTime/obTimeScale)
124       & *sqrt(strat/(tAlpha*gravity))       & *sqrt(strat/(tAlpha*gravity))
125       & *sqrt(2.0*PI/obTimeScale*2.0*PI/obTimeScale - f0*f0)       & *sqrt(2.0 _d 0*PI/obTimeScale*2.0*PI/obTimeScale - f0*f0)
126       & /(2.0*PI/obTimeScale)       & /(2.0 _d 0*PI/obTimeScale)
127       & * (exp(futureTime/rampTime2)  c    & * (exp(futureTime/rampTime2)
128       &   - exp(-futureTime/rampTime2))  c    &   - exp(-futureTime/rampTime2))
129       &   /(exp(futureTime/rampTime2)  c    &   /(exp(futureTime/rampTime2)
130       &  + exp(-futureTime/rampTime2))  c    &  + exp(-futureTime/rampTime2))
131  #ifdef ALLOW_NONHYDROSTATIC  #ifdef ALLOW_NONHYDROSTATIC
132            OBWw(J,K,bi,bj)=-Uinflow            OBWw(J,K,bi,bj)=-Uinflow
133       & *sqrt(2.0*PI/obTimeScale*2.0*PI/obTimeScale - f0*f0)       & *sqrt(2.0 _d 0*PI/obTimeScale*2.0 _d 0*PI/obTimeScale - f0*f0)
134       & /sqrt(strat*strat - 2.0*PI/obTimeScale*2.0*PI/obTimeScale)       & /sqrt(strat*strat -
135       & *sin(mz*PI*(float(k)-0.5)/float(Nr))       &          2.0 _d 0*PI/obTimeScale*2.0 _d 0*PI/obTimeScale)
136       &       *cos(2.*PI*futureTime/obTimeScale)       & *sin(mz*PI*(float(k)-0.5 _d 0)/float(Nr))
137       &       *(exp(futureTime/rampTime2)       &       *cos(2. _d 0*PI*futureTime/obTimeScale)
138       &   - exp(-futureTime/rampTime2))  c    &       *(exp(futureTime/rampTime2)
139       &   /(exp(futureTime/rampTime2)  c    &   - exp(-futureTime/rampTime2))
140       &  + exp(-futureTime/rampTime2))  c    &   /(exp(futureTime/rampTime2)
141    c    &  + exp(-futureTime/rampTime2))
142  #endif  #endif
143            ENDDO            ENDDO
144          ENDDO          ENDDO

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

  ViewVC Help
Powered by ViewVC 1.1.22