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

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/BDY/bdydyn.F90 @ 3211

Last change on this file since 3211 was 3211, checked in by spickles2, 12 years ago

Stephen Pickles, 11 Dec 2011

Commit to bring the rest of the DCSE NEMO development branch
in line with the latest development version. This includes
array index re-ordering of all OPA_SRC/.

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