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 NEMO/trunk/src/OCE/BDY – NEMO

source: NEMO/trunk/src/OCE/BDY/bdydyn.F90 @ 12560

Last change on this file since 12560 was 12377, checked in by acc, 4 years ago

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

  • Property svn:keywords set to Id
File size: 5.7 KB
RevLine 
[911]1MODULE bdydyn
[1125]2   !!======================================================================
[911]3   !!                       ***  MODULE  bdydyn  ***
[3294]4   !! Unstructured Open Boundary Cond. :   Apply boundary conditions to velocities
[1125]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
[2528]10   !!            3.3  !  2010-09  (E.O'Dea) modifications for Shelf configurations
11   !!            3.3  !  2010-09  (D.Storkey) add ice boundary conditions
[3294]12   !!            3.4  !  2011     (D. Storkey) rewrite in preparation for OBC-BDY merge
[1125]13   !!----------------------------------------------------------------------
[3294]14   !!   bdy_dyn        : split velocities into barotropic and baroclinic parts
15   !!                    and call bdy_dyn2d and bdy_dyn3d to apply boundary
16   !!                    conditions
[1125]17   !!----------------------------------------------------------------------
[911]18   USE oce             ! ocean dynamics and tracers
19   USE dom_oce         ! ocean space and time domain
20   USE bdy_oce         ! ocean open boundary conditions
[3294]21   USE bdydyn2d        ! open boundary conditions for barotropic solution
22   USE bdydyn3d        ! open boundary conditions for baroclinic velocities
[911]23   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
[1125]24   USE in_out_manager  !
[4689]25   USE domvvl          ! variable volume
[911]26
27   IMPLICIT NONE
28   PRIVATE
29
[5930]30   PUBLIC   bdy_dyn    ! routine called in dyn_nxt
[911]31
[1125]32   !!----------------------------------------------------------------------
[9598]33   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[1146]34   !! $Id$
[10068]35   !! Software governed by the CeCILL license (see ./LICENSE)
[1125]36   !!----------------------------------------------------------------------
[911]37CONTAINS
38
[12377]39   SUBROUTINE bdy_dyn( kt, Kbb, puu, pvv, Kaa, dyn3d_only )
[1125]40      !!----------------------------------------------------------------------
[3294]41      !!                  ***  SUBROUTINE bdy_dyn  ***
[1125]42      !!
[3294]43      !! ** Purpose : - Wrapper routine for bdy_dyn2d and bdy_dyn3d.
[911]44      !!
[1125]45      !!----------------------------------------------------------------------
[12377]46      INTEGER                             , INTENT(in)    ::   kt           ! Main time step counter
47      INTEGER                             , INTENT(in)    ::   Kbb, Kaa     ! Ocean time level indices
48      REAL(wp), DIMENSION(jpi,jpj,jpk,jpt), INTENT(inout) ::   puu, pvv     ! Ocean velocities (to be updated at open boundaries)
49      LOGICAL, OPTIONAL                   , INTENT(in)    ::   dyn3d_only   ! T => only update baroclinic velocities
[6140]50      !
51      INTEGER ::   jk, ii, ij, ib_bdy, ib, igrd     ! Loop counter
52      LOGICAL ::   ll_dyn2d, ll_dyn3d, ll_orlanski
[12377]53      REAL(wp), DIMENSION(jpi,jpj) :: zua2d, zva2d     ! after barotropic velocities
[6140]54      !!----------------------------------------------------------------------
55      !
[3294]56      ll_dyn2d = .true.
57      ll_dyn3d = .true.
[6140]58      !
[3294]59      IF( PRESENT(dyn3d_only) ) THEN
[6140]60         IF( dyn3d_only )   ll_dyn2d = .false.
[3294]61      ENDIF
[6140]62      !
[4292]63      ll_orlanski = .false.
64      DO ib_bdy = 1, nb_bdy
[6140]65         IF ( cn_dyn2d(ib_bdy) == 'orlanski' .OR. cn_dyn2d(ib_bdy) == 'orlanski_npo' &
66     &   .OR. cn_dyn3d(ib_bdy) == 'orlanski' .OR. cn_dyn3d(ib_bdy) == 'orlanski_npo')   ll_orlanski = .true.
67      END DO
[4292]68
[3294]69      !-------------------------------------------------------
70      ! Split velocities into barotropic and baroclinic parts
71      !-------------------------------------------------------
[911]72
[6140]73      !                          ! "After" velocities:
[12377]74      zua2d(:,:) = 0._wp
75      zva2d(:,:) = 0._wp     
[4370]76      DO jk = 1, jpkm1
[12377]77         zua2d(:,:) = zua2d(:,:) + e3u(:,:,jk,Kaa) * puu(:,:,jk,Kaa) * umask(:,:,jk)
78         zva2d(:,:) = zva2d(:,:) + e3v(:,:,jk,Kaa) * pvv(:,:,jk,Kaa) * vmask(:,:,jk)
[4370]79      END DO
[12377]80      zua2d(:,:) = zua2d(:,:) * r1_hu(:,:,Kaa)
81      zva2d(:,:) = zva2d(:,:) * r1_hv(:,:,Kaa)
[4292]82
[3294]83      DO jk = 1 , jpkm1
[12377]84         puu(:,:,jk,Kaa) = ( puu(:,:,jk,Kaa) - zua2d(:,:) ) * umask(:,:,jk)
85         pvv(:,:,jk,Kaa) = ( pvv(:,:,jk,Kaa) - zva2d(:,:) ) * vmask(:,:,jk)
[3294]86      END DO
87
[4292]88
[6140]89      IF( ll_orlanski ) THEN     ! "Before" velocities (Orlanski condition only)
[4292]90         DO jk = 1 , jpkm1
[12377]91            puu(:,:,jk,Kbb) = ( puu(:,:,jk,Kbb) - uu_b(:,:,Kbb) ) * umask(:,:,jk)
92            pvv(:,:,jk,Kbb) = ( pvv(:,:,jk,Kbb) - vv_b(:,:,Kbb) ) * vmask(:,:,jk)
[4292]93         END DO
[6140]94      ENDIF
[4292]95
[3294]96      !-------------------------------------------------------
97      ! Apply boundary conditions to barotropic and baroclinic
98      ! parts separately
99      !-------------------------------------------------------
100
[12377]101      IF( ll_dyn2d )   CALL bdy_dyn2d( kt, zua2d, zva2d, uu_b(:,:,Kbb), vv_b(:,:,Kbb), r1_hu(:,:,Kaa), r1_hv(:,:,Kaa), ssh(:,:,Kaa) )
[3294]102
[12377]103      IF( ll_dyn3d )   CALL bdy_dyn3d( kt, Kbb, puu, pvv, Kaa )
[3294]104
105      !-------------------------------------------------------
106      ! Recombine velocities
107      !-------------------------------------------------------
[6140]108      !
[3294]109      DO jk = 1 , jpkm1
[12377]110         puu(:,:,jk,Kaa) = ( puu(:,:,jk,Kaa) + zua2d(:,:) ) * umask(:,:,jk)
111         pvv(:,:,jk,Kaa) = ( pvv(:,:,jk,Kaa) + zva2d(:,:) ) * vmask(:,:,jk)
[3294]112      END DO
[6140]113      !
[4292]114      IF ( ll_orlanski ) THEN
115         DO jk = 1 , jpkm1
[12377]116            puu(:,:,jk,Kbb) = ( puu(:,:,jk,Kbb) + uu_b(:,:,Kbb) ) * umask(:,:,jk)
117            pvv(:,:,jk,Kbb) = ( pvv(:,:,jk,Kbb) + vv_b(:,:,Kbb) ) * vmask(:,:,jk)
[4292]118         END DO
119      END IF
[6140]120      !
[3294]121   END SUBROUTINE bdy_dyn
122
[1125]123   !!======================================================================
[911]124END MODULE bdydyn
Note: See TracBrowser for help on using the repository browser.