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/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/BDY – NEMO

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/BDY/bdydyn.F90 @ 2287

Last change on this file since 2287 was 2287, checked in by smasson, 14 years ago

update licence of all NEMO files...

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