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/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/OPA_SRC/BDY – NEMO

source: branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/OPA_SRC/BDY/bdydyn.F90 @ 7351

Last change on this file since 7351 was 7351, checked in by emanuelaclementi, 7 years ago

ticket #1805 step 3: /2016/dev_INGV_UKMO_2016 aligned to the trunk at revision 7161

  • Property svn:keywords set to Id
File size: 6.3 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   !!----------------------------------------------------------------------
14#if defined key_bdy 
15   !!----------------------------------------------------------------------
16   !!   'key_bdy' :                    Unstructured Open Boundary Condition
17   !!----------------------------------------------------------------------
[3294]18   !!   bdy_dyn        : split velocities into barotropic and baroclinic parts
19   !!                    and call bdy_dyn2d and bdy_dyn3d to apply boundary
20   !!                    conditions
[1125]21   !!----------------------------------------------------------------------
[3294]22   USE wrk_nemo        ! Memory Allocation
23   USE timing          ! Timing
[911]24   USE oce             ! ocean dynamics and tracers
25   USE dom_oce         ! ocean space and time domain
26   USE bdy_oce         ! ocean open boundary conditions
[3294]27   USE bdydyn2d        ! open boundary conditions for barotropic solution
28   USE bdydyn3d        ! open boundary conditions for baroclinic velocities
[911]29   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
[1125]30   USE in_out_manager  !
[4689]31   USE domvvl          ! variable volume
[911]32
33   IMPLICIT NONE
34   PRIVATE
35
[5930]36   PUBLIC   bdy_dyn    ! routine called in dyn_nxt
[911]37
[1125]38   !!----------------------------------------------------------------------
[2528]39   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
[1146]40   !! $Id$
[2528]41   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[1125]42   !!----------------------------------------------------------------------
[911]43CONTAINS
44
[3294]45   SUBROUTINE bdy_dyn( kt, dyn3d_only )
[1125]46      !!----------------------------------------------------------------------
[3294]47      !!                  ***  SUBROUTINE bdy_dyn  ***
[1125]48      !!
[3294]49      !! ** Purpose : - Wrapper routine for bdy_dyn2d and bdy_dyn3d.
[911]50      !!
[1125]51      !!----------------------------------------------------------------------
[7351]52      INTEGER, INTENT(in)           ::   kt           ! Main time step counter
53      LOGICAL, INTENT(in), OPTIONAL ::   dyn3d_only   ! T => only update baroclinic velocities
54      !
55      INTEGER ::   jk, ii, ij, ib_bdy, ib, igrd     ! Loop counter
56      LOGICAL ::   ll_dyn2d, ll_dyn3d, ll_orlanski
[4354]57      REAL(wp), POINTER, DIMENSION(:,:) :: pua2d, pva2d     ! after barotropic velocities
[7351]58      !!----------------------------------------------------------------------
59      !
60      IF( nn_timing == 1 )   CALL timing_start('bdy_dyn')
61      !
[3294]62      ll_dyn2d = .true.
63      ll_dyn3d = .true.
[7351]64      !
[3294]65      IF( PRESENT(dyn3d_only) ) THEN
[7351]66         IF( dyn3d_only )   ll_dyn2d = .false.
[3294]67      ENDIF
[7351]68      !
[4292]69      ll_orlanski = .false.
70      DO ib_bdy = 1, nb_bdy
[7351]71         IF ( cn_dyn2d(ib_bdy) == 'orlanski' .OR. cn_dyn2d(ib_bdy) == 'orlanski_npo' &
72     &   .OR. cn_dyn3d(ib_bdy) == 'orlanski' .OR. cn_dyn3d(ib_bdy) == 'orlanski_npo')   ll_orlanski = .true.
73      END DO
[4292]74
[3294]75      !-------------------------------------------------------
76      ! Set pointers
77      !-------------------------------------------------------
[911]78
[7351]79      CALL wrk_alloc( jpi,jpj,   pua2d, pva2d ) 
[1125]80
[3294]81      !-------------------------------------------------------
82      ! Split velocities into barotropic and baroclinic parts
83      !-------------------------------------------------------
[911]84
[7351]85      !                          ! "After" velocities:
86      pua2d(:,:) = 0._wp
87      pva2d(:,:) = 0._wp     
[4370]88      DO jk = 1, jpkm1
[7351]89         pua2d(:,:) = pua2d(:,:) + e3u_a(:,:,jk) * ua(:,:,jk) * umask(:,:,jk)
90         pva2d(:,:) = pva2d(:,:) + e3v_a(:,:,jk) * va(:,:,jk) * vmask(:,:,jk)
[4370]91      END DO
[7351]92      pua2d(:,:) = pua2d(:,:) * r1_hu_a(:,:)
93      pva2d(:,:) = pva2d(:,:) * r1_hv_a(:,:)
[4292]94
[3294]95      DO jk = 1 , jpkm1
[7351]96         ua(:,:,jk) = ( ua(:,:,jk) - pua2d(:,:) ) * umask(:,:,jk)
97         va(:,:,jk) = ( va(:,:,jk) - pva2d(:,:) ) * vmask(:,:,jk)
[3294]98      END DO
99
[4292]100
[7351]101      IF( ll_orlanski ) THEN     ! "Before" velocities (Orlanski condition only)
[4292]102         DO jk = 1 , jpkm1
[7351]103            ub(:,:,jk) = ( ub(:,:,jk) - ub_b(:,:) ) * umask(:,:,jk)
104            vb(:,:,jk) = ( vb(:,:,jk) - vb_b(:,:) ) * vmask(:,:,jk)
[4292]105         END DO
[7351]106      ENDIF
[4292]107
[3294]108      !-------------------------------------------------------
109      ! Apply boundary conditions to barotropic and baroclinic
110      ! parts separately
111      !-------------------------------------------------------
112
[7351]113      IF( ll_dyn2d )   CALL bdy_dyn2d( kt, pua2d, pva2d, ub_b, vb_b, r1_hu_a(:,:), r1_hv_a(:,:), ssha )
[3294]114
[7351]115      IF( ll_dyn3d )   CALL bdy_dyn3d( kt )
[3294]116
117      !-------------------------------------------------------
118      ! Recombine velocities
119      !-------------------------------------------------------
[7351]120      !
[3294]121      DO jk = 1 , jpkm1
[4292]122         ua(:,:,jk) = ( ua(:,:,jk) + pua2d(:,:) ) * umask(:,:,jk)
123         va(:,:,jk) = ( va(:,:,jk) + pva2d(:,:) ) * vmask(:,:,jk)
[3294]124      END DO
[7351]125      !
[4292]126      IF ( ll_orlanski ) THEN
127         DO jk = 1 , jpkm1
[4354]128            ub(:,:,jk) = ( ub(:,:,jk) + ub_b(:,:) ) * umask(:,:,jk)
129            vb(:,:,jk) = ( vb(:,:,jk) + vb_b(:,:) ) * vmask(:,:,jk)
[4292]130         END DO
131      END IF
[7351]132      !
133      CALL wrk_dealloc( jpi,jpj,  pua2d, pva2d ) 
134      !
135      IF( nn_timing == 1 )   CALL timing_stop('bdy_dyn')
136      !
[3294]137   END SUBROUTINE bdy_dyn
138
[911]139#else
[1125]140   !!----------------------------------------------------------------------
141   !!   Dummy module                   NO Unstruct Open Boundary Conditions
142   !!----------------------------------------------------------------------
[911]143CONTAINS
[3294]144   SUBROUTINE bdy_dyn( kt )      ! Empty routine
145      WRITE(*,*) 'bdy_dyn: You should not have seen this print! error?', kt
146   END SUBROUTINE bdy_dyn
[911]147#endif
148
[1125]149   !!======================================================================
[911]150END MODULE bdydyn
Note: See TracBrowser for help on using the repository browser.