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.
bdydyn3d.F90 in branches/2012/dev_CMCC_2012/NEMOGCM/NEMO/OPA_SRC/BDY – NEMO

source: branches/2012/dev_CMCC_2012/NEMOGCM/NEMO/OPA_SRC/BDY/bdydyn3d.F90 @ 3593

Last change on this file since 3593 was 3593, checked in by vichi, 11 years ago

Add in branch 2012/dev_CMCC_2012 changes from dev_r3365_CMCC1_BDYOBCopt & dev_r3379_CMCC6_topbfm, see ticket 1002

File size: 5.3 KB
Line 
1MODULE bdydyn3d
2   !!======================================================================
3   !!                       ***  MODULE  bdydyn3d  ***
4   !! Unstructured Open Boundary Cond. :   Flow relaxation scheme on baroclinic velocities
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_dyn3d        : apply open boundary conditions to baroclinic velocities
14   !!   bdy_dyn3d_frs    : apply Flow Relaxation Scheme
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 lbclnk          ! ocean lateral boundary conditions (or mpp link)
21   USE in_out_manager  !
22
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC   bdy_dyn3d     ! routine called by bdy_dyn
27
28   !!----------------------------------------------------------------------
29   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
30   !! $Id: bdydyn.F90 2528 2010-12-27 17:33:53Z rblod $
31   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
32   !!----------------------------------------------------------------------
33CONTAINS
34
35   SUBROUTINE bdy_dyn3d( kt )
36      !!----------------------------------------------------------------------
37      !!                  ***  SUBROUTINE bdy_dyn3d  ***
38      !!
39      !! ** Purpose : - Apply open boundary conditions for baroclinic velocities
40      !!
41      !!----------------------------------------------------------------------
42      INTEGER, INTENT( in ) :: kt     ! Main time step counter
43      !!
44      INTEGER               :: ib_bdy ! loop index
45      !!
46
47      DO ib_bdy=1, nb_bdy
48
49!!$         IF ( using Orlanski radiation conditions ) THEN
50!!$            CALL bdy_rad( kt,  bdyidx(ib_bdy) )
51!!$         ENDIF
52
53         SELECT CASE( nn_dyn3d(ib_bdy) )
54         CASE(jp_none)
55            CYCLE
56         CASE(jp_frs)
57            CALL bdy_dyn3d_frs( idx_bdy(ib_bdy), dta_bdy(ib_bdy), kt, ib_bdy )
58         CASE DEFAULT
59            CALL ctl_stop( 'bdy_dyn3d : unrecognised option for open boundaries for baroclinic velocities' )
60         END SELECT
61      ENDDO
62
63   END SUBROUTINE bdy_dyn3d
64
65   SUBROUTINE bdy_dyn3d_frs( idx, dta, kt, ib_bdy )
66      !!----------------------------------------------------------------------
67      !!                  ***  SUBROUTINE bdy_dyn3d_frs  ***
68      !!
69      !! ** Purpose : - Apply the Flow Relaxation Scheme for baroclinic velocities
70      !!                at open boundaries.
71      !!
72      !! References :- Engedahl H., 1995: Use of the flow relaxation scheme in
73      !!               a three-dimensional baroclinic ocean model with realistic
74      !!               topography. Tellus, 365-382.
75      !!----------------------------------------------------------------------
76      INTEGER                     ::   kt
77      TYPE(OBC_INDEX), INTENT(in) ::   idx  ! OBC indices
78      TYPE(OBC_DATA),  INTENT(in) ::   dta  ! OBC external data
79      INTEGER,         INTENT(in) ::   ib_bdy  ! BDY set index
80      !!
81      INTEGER  ::   jb, jk         ! dummy loop indices
82      INTEGER  ::   ii, ij, igrd   ! local integers
83      REAL(wp) ::   zwgt           ! boundary weight
84      !!----------------------------------------------------------------------
85      !
86      IF( nn_timing == 1 ) CALL timing_start('bdy_dyn3d_frs')
87      !
88      igrd = 2                      ! Relaxation of zonal velocity
89      DO jb = 1, idx%nblen(igrd)
90         DO jk = 1, jpkm1
91            ii   = idx%nbi(jb,igrd)
92            ij   = idx%nbj(jb,igrd)
93            zwgt = idx%nbw(jb,igrd)
94            ua(ii,ij,jk) = ( ua(ii,ij,jk) + zwgt * ( dta%u3d(jb,jk) - ua(ii,ij,jk) ) ) * umask(ii,ij,jk)
95         END DO
96      END DO
97      !
98      igrd = 3                      ! Relaxation of meridional velocity
99      DO jb = 1, idx%nblen(igrd)
100         DO jk = 1, jpkm1
101            ii   = idx%nbi(jb,igrd)
102            ij   = idx%nbj(jb,igrd)
103            zwgt = idx%nbw(jb,igrd)
104            va(ii,ij,jk) = ( va(ii,ij,jk) + zwgt * ( dta%v3d(jb,jk) - va(ii,ij,jk) ) ) * vmask(ii,ij,jk)
105         END DO
106      END DO
107      CALL lbc_bdy_lnk( ua, 'U', -1., ib_bdy )   ;   CALL lbc_bdy_lnk( va, 'V', -1.,ib_bdy )   ! Boundary points should be updated
108      !
109      IF( kt .eq. nit000 ) CLOSE( unit = 102 )
110
111      IF( nn_timing == 1 ) CALL timing_stop('bdy_dyn3d_frs')
112
113   END SUBROUTINE bdy_dyn3d_frs
114
115
116#else
117   !!----------------------------------------------------------------------
118   !!   Dummy module                   NO Unstruct Open Boundary Conditions
119   !!----------------------------------------------------------------------
120CONTAINS
121   SUBROUTINE bdy_dyn3d( kt )      ! Empty routine
122      WRITE(*,*) 'bdy_dyn_frs: You should not have seen this print! error?', kt
123   END SUBROUTINE bdy_dyn3d
124#endif
125
126   !!======================================================================
127END MODULE bdydyn3d
Note: See TracBrowser for help on using the repository browser.