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 @ 10068

Last change on this file since 10068 was 10068, checked in by nicolasmartin, 6 years ago

First part of modifications to have a common default header : fix typos and SVN keywords properties

  • Property svn:keywords set to Id
File size: 5.2 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
[3294]39   SUBROUTINE bdy_dyn( kt, 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      !!----------------------------------------------------------------------
[6140]46      INTEGER, INTENT(in)           ::   kt           ! Main time step counter
47      LOGICAL, INTENT(in), OPTIONAL ::   dyn3d_only   ! T => only update baroclinic velocities
48      !
49      INTEGER ::   jk, ii, ij, ib_bdy, ib, igrd     ! Loop counter
50      LOGICAL ::   ll_dyn2d, ll_dyn3d, ll_orlanski
[9125]51      REAL(wp), DIMENSION(jpi,jpj) :: pua2d, pva2d     ! after barotropic velocities
[6140]52      !!----------------------------------------------------------------------
53      !
[3294]54      ll_dyn2d = .true.
55      ll_dyn3d = .true.
[6140]56      !
[3294]57      IF( PRESENT(dyn3d_only) ) THEN
[6140]58         IF( dyn3d_only )   ll_dyn2d = .false.
[3294]59      ENDIF
[6140]60      !
[4292]61      ll_orlanski = .false.
62      DO ib_bdy = 1, nb_bdy
[6140]63         IF ( cn_dyn2d(ib_bdy) == 'orlanski' .OR. cn_dyn2d(ib_bdy) == 'orlanski_npo' &
64     &   .OR. cn_dyn3d(ib_bdy) == 'orlanski' .OR. cn_dyn3d(ib_bdy) == 'orlanski_npo')   ll_orlanski = .true.
65      END DO
[4292]66
[3294]67      !-------------------------------------------------------
68      ! Split velocities into barotropic and baroclinic parts
69      !-------------------------------------------------------
[911]70
[6140]71      !                          ! "After" velocities:
72      pua2d(:,:) = 0._wp
73      pva2d(:,:) = 0._wp     
[4370]74      DO jk = 1, jpkm1
[6140]75         pua2d(:,:) = pua2d(:,:) + e3u_a(:,:,jk) * ua(:,:,jk) * umask(:,:,jk)
76         pva2d(:,:) = pva2d(:,:) + e3v_a(:,:,jk) * va(:,:,jk) * vmask(:,:,jk)
[4370]77      END DO
[6140]78      pua2d(:,:) = pua2d(:,:) * r1_hu_a(:,:)
79      pva2d(:,:) = pva2d(:,:) * r1_hv_a(:,:)
[4292]80
[3294]81      DO jk = 1 , jpkm1
[6140]82         ua(:,:,jk) = ( ua(:,:,jk) - pua2d(:,:) ) * umask(:,:,jk)
83         va(:,:,jk) = ( va(:,:,jk) - pva2d(:,:) ) * vmask(:,:,jk)
[3294]84      END DO
85
[4292]86
[6140]87      IF( ll_orlanski ) THEN     ! "Before" velocities (Orlanski condition only)
[4292]88         DO jk = 1 , jpkm1
[6140]89            ub(:,:,jk) = ( ub(:,:,jk) - ub_b(:,:) ) * umask(:,:,jk)
90            vb(:,:,jk) = ( vb(:,:,jk) - vb_b(:,:) ) * vmask(:,:,jk)
[4292]91         END DO
[6140]92      ENDIF
[4292]93
[3294]94      !-------------------------------------------------------
95      ! Apply boundary conditions to barotropic and baroclinic
96      ! parts separately
97      !-------------------------------------------------------
98
[6140]99      IF( ll_dyn2d )   CALL bdy_dyn2d( kt, pua2d, pva2d, ub_b, vb_b, r1_hu_a(:,:), r1_hv_a(:,:), ssha )
[3294]100
[6140]101      IF( ll_dyn3d )   CALL bdy_dyn3d( kt )
[3294]102
103      !-------------------------------------------------------
104      ! Recombine velocities
105      !-------------------------------------------------------
[6140]106      !
[3294]107      DO jk = 1 , jpkm1
[4292]108         ua(:,:,jk) = ( ua(:,:,jk) + pua2d(:,:) ) * umask(:,:,jk)
109         va(:,:,jk) = ( va(:,:,jk) + pva2d(:,:) ) * vmask(:,:,jk)
[3294]110      END DO
[6140]111      !
[4292]112      IF ( ll_orlanski ) THEN
113         DO jk = 1 , jpkm1
[4354]114            ub(:,:,jk) = ( ub(:,:,jk) + ub_b(:,:) ) * umask(:,:,jk)
115            vb(:,:,jk) = ( vb(:,:,jk) + vb_b(:,:) ) * vmask(:,:,jk)
[4292]116         END DO
117      END IF
[6140]118      !
[3294]119   END SUBROUTINE bdy_dyn
120
[1125]121   !!======================================================================
[911]122END MODULE bdydyn
Note: See TracBrowser for help on using the repository browser.