New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
bdydyn.F90 in branches/devukmo2010/NEMO/OPA_SRC/BDY – NEMO

source: branches/devukmo2010/NEMO/OPA_SRC/BDY/bdydyn.F90 @ 2128

Last change on this file since 2128 was 2128, checked in by rfurner, 14 years ago

merged branches OBS, ASM, Rivers, BDY & mixed_dynldf ready for vn3.3 merge

  • Property svn:executable set to *
  • Property svn:keywords set to Id
File size: 8.9 KB
Line 
1MODULE bdydyn
2   !!======================================================================
3   !!                       ***  MODULE  bdydyn  ***
4   !! Unstructured Open Boundary Cond. :   Flow relaxation scheme on velocities
5   !!======================================================================
6   !! History :  1.0  !  2005-02  (J. Chanut, A. Sellar)  Original code
7   !!             -   !  2007-07  (D. Storkey) Move Flather implementation to separate routine.
8   !!            3.0  !  2008-04  (NEMO team)  add in the reference version
9   !!            3.2  !  2008-04  (R. Benshila) consider velocity instead of transport
10   !!            3.3  !  2010-09  (E.O'Dea) modifications for Shelf configurations
11   !!            3.3  !  2010-09  (D.Storkey) add ice boundary conditions
12   !!----------------------------------------------------------------------
13#if defined key_bdy 
14   !!----------------------------------------------------------------------
15   !!   'key_bdy' :                    Unstructured Open Boundary Condition
16   !!----------------------------------------------------------------------
17   !!   bdy_dyn_frs    : relaxation of velocities on unstructured open boundary
18   !!   bdy_dyn_fla    : Flather condition for barotropic solution
19   !!----------------------------------------------------------------------
20   USE oce             ! ocean dynamics and tracers
21   USE dom_oce         ! ocean space and time domain
22   USE bdy_oce         ! ocean open boundary conditions
23   USE dynspg_oce      ! for barotropic variables
24   USE phycst          ! physical constants
25   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
26   USE bdytides        ! for tidal harmonic forcing at boundary
27   USE in_out_manager  !
28
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC   bdy_dyn_frs   ! routine called in dynspg_flt (free surface case ONLY)
33# if defined key_dynspg_exp || defined key_dynspg_ts
34   PUBLIC   bdy_dyn_fla   ! routine called in dynspg_flt (free surface case ONLY)
35# endif
36
37   !!----------------------------------------------------------------------
38   !! NEMO/OPA 3.0 , LOCEAN-IPSL (2008)
39   !! $Id$
40   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
41   !!----------------------------------------------------------------------
42
43CONTAINS
44
45   SUBROUTINE bdy_dyn_frs( kt )
46      !!----------------------------------------------------------------------
47      !!                  ***  SUBROUTINE bdy_dyn_frs  ***
48      !!
49      !! ** Purpose : - Apply the Flow Relaxation Scheme for dynamic in the 
50      !!                case of unstructured open boundaries.
51      !!
52      !! References :- Engedahl H., 1995: Use of the flow relaxation scheme in
53      !!               a three-dimensional baroclinic ocean model with realistic
54      !!               topography. Tellus, 365-382.
55      !!----------------------------------------------------------------------
56      INTEGER, INTENT( in ) ::   kt   ! Main time step counter
57      !!
58      INTEGER  ::   ib, ik, igrd      ! dummy loop indices
59      INTEGER  ::   ii, ij            ! 2D addresses
60      REAL(wp) ::   zwgt              ! boundary weight
61      !!----------------------------------------------------------------------
62      !
63      IF(ln_bdy_dyn_frs) THEN ! If this is false, then this routine does nothing.
64
65         IF( kt == nit000 ) THEN
66            IF(lwp) WRITE(numout,*)
67            IF(lwp) WRITE(numout,*) 'bdy_dyn : Flow Relaxation Scheme on momentum'
68            IF(lwp) WRITE(numout,*) '~~~~~~~'
69         ENDIF
70         !
71         igrd = 2                      ! Relaxation of zonal velocity
72         DO ib = 1, nblen(igrd)
73            DO ik = 1, jpkm1
74               ii = nbi(ib,igrd)
75               ij = nbj(ib,igrd)
76               zwgt = nbw(ib,igrd)
77               ua(ii,ij,ik) = ( ua(ii,ij,ik) * ( 1.- zwgt ) + ubdy(ib,ik) * zwgt ) * umask(ii,ij,ik)
78            END DO
79         END DO
80         !
81         igrd = 3                      ! Relaxation of meridional velocity
82         DO ib = 1, nblen(igrd)
83            DO ik = 1, jpkm1
84               ii = nbi(ib,igrd)
85               ij = nbj(ib,igrd)
86               zwgt = nbw(ib,igrd)
87               va(ii,ij,ik) = ( va(ii,ij,ik) * ( 1.- zwgt ) + vbdy(ib,ik) * zwgt ) * vmask(ii,ij,ik)
88            END DO
89         END DO 
90         !
91         CALL lbc_lnk( ua, 'U', -1. )   ! Boundary points should be updated
92         CALL lbc_lnk( va, 'V', -1. )   !
93         !
94      ENDIF ! ln_bdy_dyn_frs
95
96   END SUBROUTINE bdy_dyn_frs
97
98
99#if defined key_dynspg_exp || defined key_dynspg_ts
100!! Option to use Flather with dynspg_flt not coded yet...
101   SUBROUTINE bdy_dyn_fla( pssh )
102      !!----------------------------------------------------------------------
103      !!                 ***  SUBROUTINE bdy_dyn_fla  ***
104      !!             
105      !!              - Apply Flather boundary conditions on normal barotropic velocities
106      !!                (ln_bdy_dyn_fla=.true. or ln_bdy_tides=.true.)
107      !!
108      !! ** WARNINGS about FLATHER implementation:
109      !!1. According to Palma and Matano, 1998 "after ssh" is used.
110      !!   In ROMS and POM implementations, it is "now ssh". In the current
111      !!   implementation (tested only in the EEL-R5 conf.), both cases were unstable.
112      !!   So I use "before ssh" in the following.
113      !!
114      !!2. We assume that the normal ssh gradient at the bdy is zero. As a matter of
115      !!   fact, the model ssh just inside the dynamical boundary is used (the outside 
116      !!   ssh in the code is not updated).
117      !!
118      !! References:  Flather, R. A., 1976: A tidal model of the northwest European
119      !!              continental shelf. Mem. Soc. R. Sci. Liege, Ser. 6,10, 141-164.     
120      !!----------------------------------------------------------------------
121      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) ::   pssh
122
123      INTEGER  ::   ib, igrd                         ! dummy loop indices
124      INTEGER  ::   ii, ij, iim1, iip1, ijm1, ijp1   ! 2D addresses
125      REAL(wp) ::   zcorr                            ! Flather correction
126      REAL(wp) ::   zforc                            ! temporary scalar
127      !!----------------------------------------------------------------------
128
129      ! ---------------------------------!
130      ! Flather boundary conditions     :!
131      ! ---------------------------------!
132     
133      IF(ln_bdy_dyn_fla .OR. ln_bdy_tides) THEN ! If these are both false, then this routine does nothing.
134
135         ! Fill temporary array with ssh data (here spgu):
136         igrd = 4
137         spgu(:,:) = 0.0
138         DO ib = 1, nblenrim(igrd)
139            ii = nbi(ib,igrd)
140            ij = nbj(ib,igrd)
141            IF( ln_bdy_dyn_fla ) spgu(ii, ij) = sshbdy(ib)
142            IF( ln_bdy_tides )   spgu(ii, ij) = spgu(ii, ij) + sshtide(ib)
143         END DO
144         !
145         igrd = 5      ! Flather bc on u-velocity;
146         !             ! remember that flagu=-1 if normal velocity direction is outward
147         !             ! I think we should rather use after ssh ?
148         DO ib = 1, nblenrim(igrd)
149            ii  = nbi(ib,igrd)
150            ij  = nbj(ib,igrd) 
151            iim1 = ii + MAX( 0, INT( flagu(ib) ) )   ! T pts i-indice inside the boundary
152            iip1 = ii - MIN( 0, INT( flagu(ib) ) )   ! T pts i-indice outside the boundary
153            !
154            zcorr = - flagu(ib) * SQRT( grav * hur_e(ii, ij) ) * ( pssh(iim1, ij) - spgu(iip1,ij) )
155            zforc = ubtbdy(ib) + utide(ib)
156            ua_e(ii,ij) = zforc + zcorr * umask(ii,ij,1) 
157         END DO
158         !
159         igrd = 6      ! Flather bc on v-velocity
160         !             ! remember that flagv=-1 if normal velocity direction is outward
161         DO ib = 1, nblenrim(igrd)
162            ii  = nbi(ib,igrd)
163            ij  = nbj(ib,igrd) 
164            ijm1 = ij + MAX( 0, INT( flagv(ib) ) )   ! T pts j-indice inside the boundary
165            ijp1 = ij - MIN( 0, INT( flagv(ib) ) )   ! T pts j-indice outside the boundary
166            !
167            zcorr = - flagv(ib) * SQRT( grav * hvr_e(ii, ij) ) * ( pssh(ii, ijm1) - spgu(ii,ijp1) )
168            zforc = vbtbdy(ib) + vtide(ib)
169            va_e(ii,ij) = zforc + zcorr * vmask(ii,ij,1)
170         END DO
171         CALL lbc_lnk( ua_e, 'U', -1. )   ! Boundary points should be updated
172         CALL lbc_lnk( va_e, 'V', -1. )   !
173         !
174      ENDIF ! ln_bdy_dyn_fla .or. ln_bdy_tides
175      !
176   END SUBROUTINE bdy_dyn_fla
177#endif
178
179#else
180   !!----------------------------------------------------------------------
181   !!   Dummy module                   NO Unstruct Open Boundary Conditions
182   !!----------------------------------------------------------------------
183CONTAINS
184   SUBROUTINE bdy_dyn_frs( kt )      ! Empty routine
185      WRITE(*,*) 'bdy_dyn_frs: You should not have seen this print! error?', kt
186   END SUBROUTINE bdy_dyn_frs
187   SUBROUTINE bdy_dyn_fla( pssh )    ! Empty routine
188      REAL :: pssh(:,:)
189      WRITE(*,*) 'bdy_dyn_fla: You should not have seen this print! error?', pssh(1,1)
190   END SUBROUTINE bdy_dyn_fla
191#endif
192
193   !!======================================================================
194END MODULE bdydyn
Note: See TracBrowser for help on using the repository browser.