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.
bdyvol.F90 in branches/devukmo2010/NEMO/OPA_SRC/BDY – NEMO

source: branches/devukmo2010/NEMO/OPA_SRC/BDY/bdyvol.F90 @ 2128

Last change on this file since 2128 was 2128, checked in by rfurner, 14 years ago

merged branches OBS, ASM, Rivers, BDY & mixed_dynldf ready for vn3.3 merge

  • Property svn:executable set to *
  • Property svn:keywords set to Id
File size: 7.9 KB
RevLine 
[911]1MODULE bdyvol
[1125]2   !!======================================================================
[911]3   !!                       ***  MODULE  bdyvol  ***
4   !! Ocean dynamic :  Volume constraint when unstructured boundary
5   !!                  and Free surface are used
[1125]6   !!======================================================================
7   !! History :  1.0  !  2005-01  (J. Chanut, A. Sellar)  Original code
8   !!             -   !  2006-01  (J. Chanut) Bug correction
9   !!            3.0  !  2008-04  (NEMO team)  add in the reference version
10   !!----------------------------------------------------------------------
[911]11#if   defined key_bdy   &&   defined key_dynspg_flt
[1125]12   !!----------------------------------------------------------------------
13   !!   'key_bdy'            and      unstructured open boundary conditions
14   !!   'key_dynspg_flt'                              filtered free surface
15   !!----------------------------------------------------------------------
[911]16   USE oce             ! ocean dynamics and tracers
17   USE dom_oce         ! ocean space and time domain
18   USE phycst          ! physical constants
19   USE bdy_oce         ! ocean open boundary conditions
20   USE lib_mpp         ! for mppsum
21   USE in_out_manager  ! I/O manager
22   USE sbc_oce         ! ocean surface boundary conditions
23
24   IMPLICIT NONE
25   PRIVATE
26
27   PUBLIC bdy_vol        ! routine called by dynspg_flt.h90
28
29   !! * Substitutions
30#  include "domzgr_substitute.h90"
[1125]31   !!----------------------------------------------------------------------
32   !! NEMO/OPA 3.0 , LOCEAN-IPSL (2008)
[1146]33   !! $Id$
[1125]34   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
35   !!----------------------------------------------------------------------
[911]36
37CONTAINS
38
[1125]39   SUBROUTINE bdy_vol( kt )
40      !!----------------------------------------------------------------------
[911]41      !!                      ***  ROUTINE bdyvol  ***
42      !!
[1125]43      !! ** Purpose :   This routine is called in dynspg_flt to control
[911]44      !!      the volume of the system. A correction velocity is calculated
45      !!      to correct the total transport through the unstructured OBC.
46      !!      The total depth used is constant (H0) to be consistent with the
47      !!      linear free surface coded in OPA 8.2
48      !!
[1125]49      !! ** Method  :   The correction velocity (zubtpecor here) is defined calculating
[911]50      !!      the total transport through all open boundaries (trans_bdy) minus
[1125]51      !!      the cumulate E-P flux (z_cflxemp) divided by the total lateral
[911]52      !!      surface (bdysurftot) of the unstructured boundary.
[1125]53      !!         zubtpecor = [trans_bdy - z_cflxemp ]*(1./bdysurftot)
54      !!      with z_cflxemp => sum of (Evaporation minus Precipitation)
[911]55      !!                       over all the domain in m3/s at each time step.
[1125]56      !!      z_cflxemp < 0 when precipitation dominate
57      !!      z_cflxemp > 0 when evaporation dominate
[911]58      !!
59      !!      There are 2 options (user's desiderata):
60      !!         1/ The volume changes according to E-P, this is the default
61      !!            option. In this case the cumulate E-P flux are setting to
[1125]62      !!            zero (z_cflxemp=0) to calculate the correction velocity. So
[911]63      !!            it will only balance the flux through open boundaries.
64      !!            (set volbdy to 0 in tne namelist for this option)
65      !!         2/ The volume is constant even with E-P flux. In this case
66      !!            the correction velocity must balance both the flux
67      !!            through open boundaries and the ones through the free
68      !!            surface.
69      !!            (set volbdy to 1 in tne namelist for this option)
[1125]70      !!----------------------------------------------------------------------
71      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
[911]72      !!
[1125]73      INTEGER  ::   ji, jj, jk, jb, jgrd
74      INTEGER  ::   ii, ij
[1521]75      REAL(wp) ::   zubtpecor, z_cflxemp, ztranst, zraur
[911]76      !!-----------------------------------------------------------------------------
77
78      IF( kt == nit000 ) THEN
[1125]79         IF(lwp) WRITE(numout,*)
[911]80         IF(lwp) WRITE(numout,*)'bdy_vol : Correction of velocities along unstructured OBC'
81         IF(lwp) WRITE(numout,*)'~~~~~~~'
82      END IF 
83
[1125]84      ! Calculate the cumulate surface Flux z_cflxemp (m3/s) over all the domain
85      ! -----------------------------------------------------------------------
86      z_cflxemp = 0.e0
[1739]87      zraur = 1.e0 / rau0
[2128]88      z_cflxemp = SUM ( ( emp(:,:)-rnf(:,:) ) * bdytmask(:,:) * e1t(:,:) * e2t(:,:) * zraur ) 
[1125]89      IF( lk_mpp )   CALL mpp_sum( z_cflxemp )   ! sum over the global domain
[911]90
[1125]91      ! Barotropic velocity through the unstructured open boundary
92      ! ----------------------------------------------------------
[911]93      zubtpecor = 0.e0
[1125]94      jgrd = 2                               ! cumulate u component contribution first
[911]95      DO jb = 1, nblenrim(jgrd)
[1125]96         DO jk = 1, jpkm1
97            ii = nbi(jb,jgrd)
98            ij = nbj(jb,jgrd)
99            zubtpecor = zubtpecor + flagu(jb) * ua(ii,ij, jk) * e2u(ii,ij) * fse3u(ii,ij,jk)
100         END DO
[911]101      END DO
[1125]102      jgrd = 3                               ! then add v component contribution
103      DO jb = 1, nblenrim(jgrd)
104         DO jk = 1, jpkm1
105            ii = nbi(jb,jgrd)
106            ij = nbj(jb,jgrd)
107            zubtpecor = zubtpecor + flagv(jb) * va(ii,ij, jk) * e1v(ii,ij) * fse3v(ii,ij,jk) 
108         END DO
[911]109      END DO
110      IF( lk_mpp )   CALL mpp_sum( zubtpecor )   ! sum over the global domain
111
[1125]112      ! The normal velocity correction
113      ! ------------------------------
114      IF (volbdy==1) THEN   ;   zubtpecor = ( zubtpecor - z_cflxemp) / bdysurftot 
115      ELSE                  ;   zubtpecor =   zubtpecor             / bdysurftot
[911]116      END IF
117
[1125]118      ! Correction of the total velocity on the unstructured boundary to respect the mass flux conservation
119      ! -------------------------------------------------------------
[911]120      ztranst = 0.e0
[1125]121      jgrd = 2                               ! correct u component
[911]122      DO jb = 1, nblenrim(jgrd)
[1125]123         DO jk = 1, jpkm1
124            ii = nbi(jb,jgrd)
125            ij = nbj(jb,jgrd)
126            ua(ii,ij,jk) = ua(ii,ij,jk) - flagu(jb) * zubtpecor * umask(ii,ij,jk)
127            ztranst = ztranst + flagu(jb) * ua(ii,ij,jk) * e2u(ii,ij) * fse3u(ii,ij,jk)
128         END DO
[911]129      END DO
[1125]130      jgrd = 3                              ! correct v component
131      DO jb = 1, nblenrim(jgrd)
132         DO jk = 1, jpkm1
133            ii = nbi(jb,jgrd)
134            ij = nbj(jb,jgrd)
135            va(ii,ij,jk) = va(ii,ij,jk) -flagv(jb) * zubtpecor * vmask(ii,ij,jk)
136            ztranst = ztranst + flagv(jb) * va(ii,ij,jk) * e1v(ii,ij) * fse3v(ii,ij,jk)
137         END DO
[911]138      END DO
139      IF( lk_mpp )   CALL mpp_sum( ztranst )   ! sum over the global domain
140 
[1125]141      ! Check the cumulated transport through unstructured OBC once barotropic velocities corrected
142      ! ------------------------------------------------------
[911]143
144      IF( lwp .AND. MOD( kt, nwrite ) == 0) THEN
[1125]145         IF(lwp) WRITE(numout,*)
146         IF(lwp) WRITE(numout,*)'bdy_vol : time step :', kt
147         IF(lwp) WRITE(numout,*)'~~~~~~~ '
148         IF(lwp) WRITE(numout,*)'          cumulate flux EMP             =', z_cflxemp  , ' (m3/s)'
149         IF(lwp) WRITE(numout,*)'          total lateral surface of OBC  =', bdysurftot, '(m2)'
150         IF(lwp) WRITE(numout,*)'          correction velocity zubtpecor =', zubtpecor , '(m/s)'
151         IF(lwp) WRITE(numout,*)'          cumulated transport ztranst   =', ztranst   , '(m3/s)'
[911]152      END IF 
[1125]153      !
[911]154   END SUBROUTINE bdy_vol
155
156#else
[1125]157   !!----------------------------------------------------------------------
158   !!   Dummy module                   NO Unstruct Open Boundary Conditions
159   !!----------------------------------------------------------------------
[911]160CONTAINS
[1125]161   SUBROUTINE bdy_vol( kt )        ! Empty routine
162      WRITE(*,*) 'bdy_vol: You should not have seen this print! error?', kt
[911]163   END SUBROUTINE bdy_vol
164#endif
165
[1125]166   !!======================================================================
[911]167END MODULE bdyvol
Note: See TracBrowser for help on using the repository browser.