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

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

adding updates from bdy branch, revision 2100:2168

  • 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   !!----------------------------------------------------------------------
[2185]13   !!   'key_bdy'            AND      unstructured open boundary conditions
[1125]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   !!----------------------------------------------------------------------
[2185]32   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
[1146]33   !! $Id$
[1125]34   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
35   !!----------------------------------------------------------------------
[911]36CONTAINS
37
[1125]38   SUBROUTINE bdy_vol( kt )
39      !!----------------------------------------------------------------------
[911]40      !!                      ***  ROUTINE bdyvol  ***
41      !!
[1125]42      !! ** Purpose :   This routine is called in dynspg_flt to control
[911]43      !!      the volume of the system. A correction velocity is calculated
44      !!      to correct the total transport through the unstructured OBC.
45      !!      The total depth used is constant (H0) to be consistent with the
46      !!      linear free surface coded in OPA 8.2
47      !!
[1125]48      !! ** Method  :   The correction velocity (zubtpecor here) is defined calculating
[911]49      !!      the total transport through all open boundaries (trans_bdy) minus
[1125]50      !!      the cumulate E-P flux (z_cflxemp) divided by the total lateral
[911]51      !!      surface (bdysurftot) of the unstructured boundary.
[1125]52      !!         zubtpecor = [trans_bdy - z_cflxemp ]*(1./bdysurftot)
53      !!      with z_cflxemp => sum of (Evaporation minus Precipitation)
[911]54      !!                       over all the domain in m3/s at each time step.
[1125]55      !!      z_cflxemp < 0 when precipitation dominate
56      !!      z_cflxemp > 0 when evaporation dominate
[911]57      !!
58      !!      There are 2 options (user's desiderata):
59      !!         1/ The volume changes according to E-P, this is the default
60      !!            option. In this case the cumulate E-P flux are setting to
[1125]61      !!            zero (z_cflxemp=0) to calculate the correction velocity. So
[911]62      !!            it will only balance the flux through open boundaries.
63      !!            (set volbdy to 0 in tne namelist for this option)
64      !!         2/ The volume is constant even with E-P flux. In this case
65      !!            the correction velocity must balance both the flux
66      !!            through open boundaries and the ones through the free
67      !!            surface.
68      !!            (set volbdy to 1 in tne namelist for this option)
[1125]69      !!----------------------------------------------------------------------
70      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
[911]71      !!
[1125]72      INTEGER  ::   ji, jj, jk, jb, jgrd
73      INTEGER  ::   ii, ij
[2185]74      REAL(wp) ::   zubtpecor, z_cflxemp, ztranst
[911]75      !!-----------------------------------------------------------------------------
76
77      IF( kt == nit000 ) THEN
[1125]78         IF(lwp) WRITE(numout,*)
[911]79         IF(lwp) WRITE(numout,*)'bdy_vol : Correction of velocities along unstructured OBC'
80         IF(lwp) WRITE(numout,*)'~~~~~~~'
81      END IF 
82
[1125]83      ! Calculate the cumulate surface Flux z_cflxemp (m3/s) over all the domain
84      ! -----------------------------------------------------------------------
85      z_cflxemp = 0.e0
[2185]86      z_cflxemp = SUM ( ( emp(:,:)-rnf(:,:) ) * bdytmask(:,:) * e1t(:,:) * e2t(:,:) ) / rau0
87      IF( lk_mpp )   CALL mpp_sum( z_cflxemp )     ! sum over the global domain
[911]88
[2185]89      ! Transport through the unstructured open boundary
90      ! ------------------------------------------------
[911]91      zubtpecor = 0.e0
[1125]92      jgrd = 2                               ! cumulate u component contribution first
[911]93      DO jb = 1, nblenrim(jgrd)
[1125]94         DO jk = 1, jpkm1
95            ii = nbi(jb,jgrd)
96            ij = nbj(jb,jgrd)
97            zubtpecor = zubtpecor + flagu(jb) * ua(ii,ij, jk) * e2u(ii,ij) * fse3u(ii,ij,jk)
98         END DO
[911]99      END DO
[1125]100      jgrd = 3                               ! then add v component contribution
101      DO jb = 1, nblenrim(jgrd)
102         DO jk = 1, jpkm1
103            ii = nbi(jb,jgrd)
104            ij = nbj(jb,jgrd)
105            zubtpecor = zubtpecor + flagv(jb) * va(ii,ij, jk) * e1v(ii,ij) * fse3v(ii,ij,jk) 
106         END DO
[911]107      END DO
108      IF( lk_mpp )   CALL mpp_sum( zubtpecor )   ! sum over the global domain
109
[1125]110      ! The normal velocity correction
111      ! ------------------------------
[2185]112      IF( volbdy==1 ) THEN   ;   zubtpecor = ( zubtpecor - z_cflxemp) / bdysurftot 
113      ELSE                   ;   zubtpecor =   zubtpecor             / bdysurftot
[911]114      END IF
115
[1125]116      ! Correction of the total velocity on the unstructured boundary to respect the mass flux conservation
117      ! -------------------------------------------------------------
[911]118      ztranst = 0.e0
[1125]119      jgrd = 2                               ! correct u component
[911]120      DO jb = 1, nblenrim(jgrd)
[1125]121         DO jk = 1, jpkm1
122            ii = nbi(jb,jgrd)
123            ij = nbj(jb,jgrd)
124            ua(ii,ij,jk) = ua(ii,ij,jk) - flagu(jb) * zubtpecor * umask(ii,ij,jk)
125            ztranst = ztranst + flagu(jb) * ua(ii,ij,jk) * e2u(ii,ij) * fse3u(ii,ij,jk)
126         END DO
[911]127      END DO
[1125]128      jgrd = 3                              ! correct v component
129      DO jb = 1, nblenrim(jgrd)
130         DO jk = 1, jpkm1
131            ii = nbi(jb,jgrd)
132            ij = nbj(jb,jgrd)
133            va(ii,ij,jk) = va(ii,ij,jk) -flagv(jb) * zubtpecor * vmask(ii,ij,jk)
134            ztranst = ztranst + flagv(jb) * va(ii,ij,jk) * e1v(ii,ij) * fse3v(ii,ij,jk)
135         END DO
[911]136      END DO
137      IF( lk_mpp )   CALL mpp_sum( ztranst )   ! sum over the global domain
138 
[1125]139      ! Check the cumulated transport through unstructured OBC once barotropic velocities corrected
140      ! ------------------------------------------------------
[911]141      IF( lwp .AND. MOD( kt, nwrite ) == 0) THEN
[1125]142         IF(lwp) WRITE(numout,*)
143         IF(lwp) WRITE(numout,*)'bdy_vol : time step :', kt
144         IF(lwp) WRITE(numout,*)'~~~~~~~ '
145         IF(lwp) WRITE(numout,*)'          cumulate flux EMP             =', z_cflxemp  , ' (m3/s)'
146         IF(lwp) WRITE(numout,*)'          total lateral surface of OBC  =', bdysurftot, '(m2)'
147         IF(lwp) WRITE(numout,*)'          correction velocity zubtpecor =', zubtpecor , '(m/s)'
148         IF(lwp) WRITE(numout,*)'          cumulated transport ztranst   =', ztranst   , '(m3/s)'
[911]149      END IF 
[1125]150      !
[911]151   END SUBROUTINE bdy_vol
152
153#else
[1125]154   !!----------------------------------------------------------------------
155   !!   Dummy module                   NO Unstruct Open Boundary Conditions
156   !!----------------------------------------------------------------------
[911]157CONTAINS
[1125]158   SUBROUTINE bdy_vol( kt )        ! Empty routine
159      WRITE(*,*) 'bdy_vol: You should not have seen this print! error?', kt
[911]160   END SUBROUTINE bdy_vol
161#endif
162
[1125]163   !!======================================================================
[911]164END MODULE bdyvol
Note: See TracBrowser for help on using the repository browser.