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/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/BDY – NEMO

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/BDY/bdyvol.F90 @ 4409

Last change on this file since 4409 was 3211, checked in by spickles2, 13 years ago

Stephen Pickles, 11 Dec 2011

Commit to bring the rest of the DCSE NEMO development branch
in line with the latest development version. This includes
array index re-ordering of all OPA_SRC/.

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