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.
bdydyn2d.F90 in branches/2013/dev_MERGE_2013/NEMOGCM/NEMO/OPA_SRC/BDY – NEMO

source: branches/2013/dev_MERGE_2013/NEMOGCM/NEMO/OPA_SRC/BDY/bdydyn2d.F90 @ 4291

Last change on this file since 4291 was 3680, checked in by rblod, 11 years ago

First commit of the final branch for 2012 (future nemo_3_5), see ticket #1028

File size: 8.9 KB
Line 
1MODULE bdydyn2d
2   !!======================================================================
3   !!                       ***  MODULE  bdydyn  ***
4   !! Unstructured Open Boundary Cond. :   Apply boundary conditions to barotropic solution
5   !!======================================================================
6   !! History :  3.4  !  2011     (D. Storkey) new module as part of BDY rewrite
7   !!            3.5  !  2012     (S. Mocavero, I. Epicoco) Optimization of BDY communications
8   !!----------------------------------------------------------------------
9#if defined key_bdy 
10   !!----------------------------------------------------------------------
11   !!   'key_bdy' :                    Unstructured Open Boundary Condition
12   !!----------------------------------------------------------------------
13   !!   bdy_dyn2d      : Apply open boundary conditions to barotropic variables.
14   !!   bdy_dyn2d_fla    : Apply Flather condition
15   !!----------------------------------------------------------------------
16   USE timing          ! Timing
17   USE oce             ! ocean dynamics and tracers
18   USE dom_oce         ! ocean space and time domain
19   USE bdy_oce         ! ocean open boundary conditions
20   USE dynspg_oce      ! for barotropic variables
21   USE phycst          ! physical constants
22   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
23   USE in_out_manager  !
24
25   IMPLICIT NONE
26   PRIVATE
27
28   PUBLIC   bdy_dyn2d     ! routine called in dynspg_ts and bdy_dyn
29
30   !!----------------------------------------------------------------------
31   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
32   !! $Id: bdydyn.F90 2528 2010-12-27 17:33:53Z rblod $
33   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
34   !!----------------------------------------------------------------------
35CONTAINS
36
37   SUBROUTINE bdy_dyn2d( kt )
38      !!----------------------------------------------------------------------
39      !!                  ***  SUBROUTINE bdy_dyn2d  ***
40      !!
41      !! ** Purpose : - Apply open boundary conditions for barotropic variables
42      !!
43      !!----------------------------------------------------------------------
44      INTEGER,                      INTENT(in) ::   kt   ! Main time step counter
45      !!
46      INTEGER                                  ::   ib_bdy ! Loop counter
47
48      DO ib_bdy=1, nb_bdy
49
50         SELECT CASE( nn_dyn2d(ib_bdy) )
51         CASE(jp_none)
52            CYCLE
53         CASE(jp_frs)
54            CALL bdy_dyn2d_frs( idx_bdy(ib_bdy), dta_bdy(ib_bdy), ib_bdy )
55         CASE(jp_flather)
56            CALL bdy_dyn2d_fla( idx_bdy(ib_bdy), dta_bdy(ib_bdy), ib_bdy )
57         CASE DEFAULT
58            CALL ctl_stop( 'bdy_dyn2d : unrecognised option for open boundaries for barotropic variables' )
59         END SELECT
60      ENDDO
61
62   END SUBROUTINE bdy_dyn2d
63
64   SUBROUTINE bdy_dyn2d_frs( idx, dta, ib_bdy )
65      !!----------------------------------------------------------------------
66      !!                  ***  SUBROUTINE bdy_dyn2d_frs  ***
67      !!
68      !! ** Purpose : - Apply the Flow Relaxation Scheme for barotropic velocities
69      !!                at open boundaries.
70      !!
71      !! References :- Engedahl H., 1995: Use of the flow relaxation scheme in
72      !!               a three-dimensional baroclinic ocean model with realistic
73      !!               topography. Tellus, 365-382.
74      !!----------------------------------------------------------------------
75      TYPE(OBC_INDEX), INTENT(in) ::   idx  ! OBC indices
76      TYPE(OBC_DATA),  INTENT(in) ::   dta  ! OBC external data
77      INTEGER,         INTENT(in) ::   ib_bdy  ! BDY set index
78      !!
79      INTEGER  ::   jb, jk         ! dummy loop indices
80      INTEGER  ::   ii, ij, igrd   ! local integers
81      REAL(wp) ::   zwgt           ! boundary weight
82      !!----------------------------------------------------------------------
83      !
84      IF( nn_timing == 1 ) CALL timing_start('bdy_dyn2d_frs')
85      !
86      igrd = 2                      ! Relaxation of zonal velocity
87      DO jb = 1, idx%nblen(igrd)
88         ii   = idx%nbi(jb,igrd)
89         ij   = idx%nbj(jb,igrd)
90         zwgt = idx%nbw(jb,igrd)
91         pu2d(ii,ij) = ( pu2d(ii,ij) + zwgt * ( dta%u2d(jb) - pu2d(ii,ij) ) ) * umask(ii,ij,1)
92      END DO
93      !
94      igrd = 3                      ! Relaxation of meridional velocity
95      DO jb = 1, idx%nblen(igrd)
96         ii   = idx%nbi(jb,igrd)
97         ij   = idx%nbj(jb,igrd)
98         zwgt = idx%nbw(jb,igrd)
99         pv2d(ii,ij) = ( pv2d(ii,ij) + zwgt * ( dta%v2d(jb) - pv2d(ii,ij) ) ) * vmask(ii,ij,1)
100      END DO
101      CALL lbc_bdy_lnk( pu2d, 'U', -1., ib_bdy ) 
102      CALL lbc_bdy_lnk( pv2d, 'V', -1., ib_bdy)   ! Boundary points should be updated
103      !
104      IF( nn_timing == 1 ) CALL timing_stop('bdy_dyn2d_frs')
105      !
106
107   END SUBROUTINE bdy_dyn2d_frs
108
109
110   SUBROUTINE bdy_dyn2d_fla( idx, dta, ib_bdy )
111      !!----------------------------------------------------------------------
112      !!                 ***  SUBROUTINE bdy_dyn2d_fla  ***
113      !!             
114      !!              - Apply Flather boundary conditions on normal barotropic velocities
115      !!
116      !! ** WARNINGS about FLATHER implementation:
117      !!1. According to Palma and Matano, 1998 "after ssh" is used.
118      !!   In ROMS and POM implementations, it is "now ssh". In the current
119      !!   implementation (tested only in the EEL-R5 conf.), both cases were unstable.
120      !!   So I use "before ssh" in the following.
121      !!
122      !!2. We assume that the normal ssh gradient at the bdy is zero. As a matter of
123      !!   fact, the model ssh just inside the dynamical boundary is used (the outside 
124      !!   ssh in the code is not updated).
125      !!
126      !! References:  Flather, R. A., 1976: A tidal model of the northwest European
127      !!              continental shelf. Mem. Soc. R. Sci. Liege, Ser. 6,10, 141-164.     
128      !!----------------------------------------------------------------------
129      TYPE(OBC_INDEX),              INTENT(in) ::   idx  ! OBC indices
130      TYPE(OBC_DATA),               INTENT(in) ::   dta  ! OBC external data
131      INTEGER,                      INTENT(in) ::   ib_bdy  ! BDY set index
132
133      INTEGER  ::   jb, igrd                         ! dummy loop indices
134      INTEGER  ::   ii, ij, iim1, iip1, ijm1, ijp1   ! 2D addresses
135      REAL(wp) ::   zcorr                            ! Flather correction
136      REAL(wp) ::   zforc                            ! temporary scalar
137      !!----------------------------------------------------------------------
138
139      IF( nn_timing == 1 ) CALL timing_start('bdy_dyn2d_fla')
140
141      ! ---------------------------------!
142      ! Flather boundary conditions     :!
143      ! ---------------------------------!
144     
145!!! REPLACE spgu with nemo_wrk work space
146
147      ! Fill temporary array with ssh data (here spgu):
148      igrd = 1
149      spgu(:,:) = 0.0
150      DO jb = 1, idx%nblenrim(igrd)
151         ii = idx%nbi(jb,igrd)
152         ij = idx%nbj(jb,igrd)
153         spgu(ii, ij) = dta%ssh(jb)
154      END DO
155      !
156      igrd = 2      ! Flather bc on u-velocity;
157      !             ! remember that flagu=-1 if normal velocity direction is outward
158      !             ! I think we should rather use after ssh ?
159      DO jb = 1, idx%nblenrim(igrd)
160         ii  = idx%nbi(jb,igrd)
161         ij  = idx%nbj(jb,igrd) 
162         iim1 = ii + MAX( 0, INT( idx%flagu(jb) ) )   ! T pts i-indice inside the boundary
163         iip1 = ii - MIN( 0, INT( idx%flagu(jb) ) )   ! T pts i-indice outside the boundary
164         !
165         zcorr = - idx%flagu(jb) * SQRT( grav * phur(ii, ij) ) * ( pssh(iim1, ij) - spgu(iip1,ij) )
166         zforc = dta%u2d(jb)
167         pu2d(ii,ij) = zforc + zcorr * umask(ii,ij,1) 
168      END DO
169      !
170      igrd = 3      ! Flather bc on v-velocity
171      !             ! remember that flagv=-1 if normal velocity direction is outward
172      DO jb = 1, idx%nblenrim(igrd)
173         ii  = idx%nbi(jb,igrd)
174         ij  = idx%nbj(jb,igrd) 
175         ijm1 = ij + MAX( 0, INT( idx%flagv(jb) ) )   ! T pts j-indice inside the boundary
176         ijp1 = ij - MIN( 0, INT( idx%flagv(jb) ) )   ! T pts j-indice outside the boundary
177         !
178         zcorr = - idx%flagv(jb) * SQRT( grav * phvr(ii, ij) ) * ( pssh(ii, ijm1) - spgu(ii,ijp1) )
179         zforc = dta%v2d(jb)
180         pv2d(ii,ij) = zforc + zcorr * vmask(ii,ij,1)
181      END DO
182      CALL lbc_bdy_lnk( pu2d, 'U', -1., ib_bdy )   ! Boundary points should be updated
183      CALL lbc_bdy_lnk( pv2d, 'V', -1., ib_bdy )   !
184      !
185      IF( nn_timing == 1 ) CALL timing_stop('bdy_dyn2d_fla')
186      !
187   END SUBROUTINE bdy_dyn2d_fla
188#else
189   !!----------------------------------------------------------------------
190   !!   Dummy module                   NO Unstruct Open Boundary Conditions
191   !!----------------------------------------------------------------------
192CONTAINS
193   SUBROUTINE bdy_dyn2d( kt )      ! Empty routine
194      WRITE(*,*) 'bdy_dyn_frs: You should not have seen this print! error?', kt
195   END SUBROUTINE bdy_dyn2d
196#endif
197
198   !!======================================================================
199END MODULE bdydyn2d
Note: See TracBrowser for help on using the repository browser.