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/DEV_r2106_LOCEAN2010/NEMO/OPA_SRC/BDY – NEMO

source: branches/DEV_r2106_LOCEAN2010/NEMO/OPA_SRC/BDY/bdyvol.F90 @ 2236

Last change on this file since 2236 was 2236, checked in by cetlod, 14 years ago

First guess of NEMO_v3.3

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