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/UKMO/dev_r5107_hadgem3_cplseq/NEMOGCM/NEMO/OPA_SRC/BDY – NEMO

source: branches/UKMO/dev_r5107_hadgem3_cplseq/NEMOGCM/NEMO/OPA_SRC/BDY/bdydyn.F90 @ 5591

Last change on this file since 5591 was 5477, checked in by cguiavarch, 9 years ago

Clear svn keywords from UKMO/dev_r5107_hadgem3_cplseq

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