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/2013/dev_r3891_METO1_MERCATOR6_OBC_BDY_merge/NEMOGCM/NEMO/OPA_SRC/BDY – NEMO

source: branches/2013/dev_r3891_METO1_MERCATOR6_OBC_BDY_merge/NEMOGCM/NEMO/OPA_SRC/BDY/bdydyn.F90 @ 3900

Last change on this file since 3900 was 3900, checked in by davestorkey, 11 years ago

First sketch of Orlanski implementation (untested).

  • Property svn:keywords set to Id
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  !
[911]32
33   IMPLICIT NONE
34   PRIVATE
35
[3294]36   PUBLIC   bdy_dyn     ! routine called in dynspg_flt (if lk_dynspg_flt) or
37                        ! dyn_nxt (if lk_dynspg_ts or lk_dynspg_exp)
[911]38
[3294]39#  include "domzgr_substitute.h90"
[1125]40   !!----------------------------------------------------------------------
[2528]41   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
[1146]42   !! $Id$
[2528]43   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[1125]44   !!----------------------------------------------------------------------
[911]45CONTAINS
46
[3294]47   SUBROUTINE bdy_dyn( kt, dyn3d_only )
[1125]48      !!----------------------------------------------------------------------
[3294]49      !!                  ***  SUBROUTINE bdy_dyn  ***
[1125]50      !!
[3294]51      !! ** Purpose : - Wrapper routine for bdy_dyn2d and bdy_dyn3d.
[911]52      !!
[1125]53      !!----------------------------------------------------------------------
[911]54      !!
[3294]55      INTEGER, INTENT( in )           :: kt               ! Main time step counter
56      LOGICAL, INTENT( in ), OPTIONAL :: dyn3d_only       ! T => only update baroclinic velocities
57      !!
58      INTEGER               :: jk,ii,ij,ib,igrd     ! Loop counter
59      LOGICAL               :: ll_dyn2d, ll_dyn3d 
60      !!
[911]61
[3294]62      IF( nn_timing == 1 ) CALL timing_start('bdy_dyn')
[911]63
[3294]64      ll_dyn2d = .true.
65      ll_dyn3d = .true.
[2528]66
[3294]67      IF( PRESENT(dyn3d_only) ) THEN
68         IF( dyn3d_only ) ll_dyn2d = .false.
69      ENDIF
[1502]70
[3294]71      !-------------------------------------------------------
72      ! Set pointers
73      !-------------------------------------------------------
[911]74
[3294]75      pssh => sshn
76      phur => hur
77      phvr => hvr
[3900]78      CALL wrk_alloc(jpi,jpj,pua2d,pva2d) 
79      IF ( nn_dyn2d == 3 .or. nn_dyn3d == 3 ) CALL wrk_alloc(jpi,jpj,pub2d,pvb2d) 
[1125]80
[3294]81      !-------------------------------------------------------
82      ! Split velocities into barotropic and baroclinic parts
83      !-------------------------------------------------------
[911]84
[3900]85      ! "After" velocities:
86
87      pua2d(:,:) = 0.e0
88      pva2d(:,:) = 0.e0
[3294]89      DO jk = 1, jpkm1   !! Vertically integrated momentum trends
[3900]90          pua2d(:,:) = pua2d(:,:) + fse3u(:,:,jk) * umask(:,:,jk) * ua(:,:,jk)
91          pva2d(:,:) = pva2d(:,:) + fse3v(:,:,jk) * vmask(:,:,jk) * va(:,:,jk)
[3294]92      END DO
[3900]93      pua2d(:,:) = pua2d(:,:) * phur(:,:)
94      pva2d(:,:) = pva2d(:,:) * phvr(:,:)
[3294]95      DO jk = 1 , jpkm1
[3900]96         ua(:,:,jk) = ua(:,:,jk) - pua2d(:,:)
97         va(:,:,jk) = va(:,:,jk) - pva2d(:,:)
[3294]98      END DO
99
[3900]100      ! "Before" velocities (required for Orlanski condition):
101
102      IF ( nn_dyn2d == 3 .or. nn_dyn3d == 3 ) THEN
103         pub2d(:,:) = 0.e0
104         pvb2d(:,:) = 0.e0
105         DO jk = 1, jpkm1   !! Vertically integrated momentum trends
106             pub2d(:,:) = pub2d(:,:) + fse3u(:,:,jk) * umask(:,:,jk) * ub(:,:,jk)
107             pvb2d(:,:) = pvb2d(:,:) + fse3v(:,:,jk) * vmask(:,:,jk) * vb(:,:,jk)
108         END DO
109         pub2d(:,:) = pub2d(:,:) * phur(:,:)
110         pvb2d(:,:) = pvb2d(:,:) * phvr(:,:)
111         DO jk = 1 , jpkm1
112            ub(:,:,jk) = ub(:,:,jk) - pub2d(:,:)
113            vb(:,:,jk) = vb(:,:,jk) - pvb2d(:,:)
114         END DO
115      END IF
116
[3294]117      !-------------------------------------------------------
118      ! Apply boundary conditions to barotropic and baroclinic
119      ! parts separately
120      !-------------------------------------------------------
121
122      IF( ll_dyn2d ) CALL bdy_dyn2d( kt )
123
124      IF( ll_dyn3d ) CALL bdy_dyn3d( kt )
125
126      !-------------------------------------------------------
127      ! Recombine velocities
128      !-------------------------------------------------------
129
130      DO jk = 1 , jpkm1
[3900]131         ua(:,:,jk) = ( ua(:,:,jk) + pua2d(:,:) ) * umask(:,:,jk)
132         va(:,:,jk) = ( va(:,:,jk) + pva2d(:,:) ) * vmask(:,:,jk)
[3294]133      END DO
134
[3900]135      IF ( nn_dyn2d == 3 .or. nn_dyn3d == 3 ) THEN
136         DO jk = 1 , jpkm1
137            ub(:,:,jk) = ( ub(:,:,jk) + pub2d(:,:) ) * umask(:,:,jk)
138            vb(:,:,jk) = ( vb(:,:,jk) + pvb2d(:,:) ) * vmask(:,:,jk)
139         END DO
140      END IF
141
[3294]142      CALL wrk_dealloc(jpi,jpj,pu2d,pv2d) 
143
144      IF( nn_timing == 1 ) CALL timing_stop('bdy_dyn')
145
146   END SUBROUTINE bdy_dyn
147
[911]148#else
[1125]149   !!----------------------------------------------------------------------
150   !!   Dummy module                   NO Unstruct Open Boundary Conditions
151   !!----------------------------------------------------------------------
[911]152CONTAINS
[3294]153   SUBROUTINE bdy_dyn( kt )      ! Empty routine
154      WRITE(*,*) 'bdy_dyn: You should not have seen this print! error?', kt
155   END SUBROUTINE bdy_dyn
[911]156#endif
157
[1125]158   !!======================================================================
[911]159END MODULE bdydyn
Note: See TracBrowser for help on using the repository browser.