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

source: trunk/NEMO/OPA_SRC/BDY/bdyvol.F90 @ 1409

Last change on this file since 1409 was 1146, checked in by rblod, 16 years ago

Add svn Id (first try), see ticket #210

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