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

source: trunk/NEMOGCM/NEMO/OPA_SRC/BDY/bdyvol.F90 @ 7753

Last change on this file since 7753 was 7646, checked in by timgraham, 7 years ago

Merge of dev_merge_2016 into trunk. UPDATE TO ARCHFILES NEEDED for XIOS2.
LIM_SRC_s/limrhg.F90 to follow in next commit due to change of kind (I'm unable to do it in this commit).
Merged using the following steps:

1) svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk .
2) Resolve minor conflicts in sette.sh and namelist_cfg for ORCA2LIM3 (due to a change in trunk after branch was created)
3) svn commit
4) svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
5) svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2016/dev_merge_2016 .
6) At this stage I checked out a clean copy of the branch to compare against what is about to be committed to the trunk.
6) svn commit #Commit code to the trunk

In this commit I have also reverted a change to Fcheck_archfile.sh which was causing problems on the Paris machine.

  • Property svn:keywords set to Id
File size: 8.1 KB
Line 
1MODULE bdyvol
2   !!======================================================================
3   !!                       ***  MODULE  bdyvol  ***
4   !! Ocean dynamic :  Volume constraint when unstructured boundary
5   !!                  and filtered 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   !!            3.4  !  2011     (D. Storkey) rewrite in preparation for OBC-BDY merge
11   !!----------------------------------------------------------------------
12   USE oce            ! ocean dynamics and tracers
13   USE bdy_oce        ! ocean open boundary conditions
14   USE sbc_oce        ! ocean surface boundary conditions
15   USE dom_oce        ! ocean space and time domain
16   USE phycst         ! physical constants
17   USE sbcisf         ! ice shelf
18   !
19   USE in_out_manager ! I/O manager
20   USE lib_mpp        ! for mppsum
21   USE timing         ! Timing
22   USE lib_fortran    ! Fortran routines library
23
24   IMPLICIT NONE
25   PRIVATE
26
27   PUBLIC   bdy_vol    ! called by ???
28
29   !!----------------------------------------------------------------------
30   !! NEMO/OPA 3.7 , NEMO Consortium (2015)
31   !! $Id$
32   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
33   !!----------------------------------------------------------------------
34CONTAINS
35
36   SUBROUTINE bdy_vol( kt )
37      !!----------------------------------------------------------------------
38      !!                      ***  ROUTINE bdyvol  ***
39      !!
40      !! ** Purpose :   This routine controls the volume of the system.
41      !!      A correction velocity is calculated to correct the total transport
42      !!      through the unstructured OBC.
43      !!      The total depth used is constant (H0) to be consistent with the
44      !!      linear free surface coded in OPA 8.2    <<<=== !!gm  ???? true ????
45      !!
46      !! ** Method  :   The correction velocity (zubtpecor here) is defined calculating
47      !!      the total transport through all open boundaries (trans_bdy) minus
48      !!      the cumulate E-P flux (z_cflxemp) divided by the total lateral
49      !!      surface (bdysurftot) of the unstructured boundary.
50      !!         zubtpecor = [trans_bdy - z_cflxemp ]*(1./bdysurftot)
51      !!      with z_cflxemp => sum of (Evaporation minus Precipitation)
52      !!                       over all the domain in m3/s at each time step.
53      !!      z_cflxemp < 0 when precipitation dominate
54      !!      z_cflxemp > 0 when evaporation dominate
55      !!
56      !!      There are 2 options (user's desiderata):
57      !!         1/ The volume changes according to E-P, this is the default
58      !!            option. In this case the cumulate E-P flux are setting to
59      !!            zero (z_cflxemp=0) to calculate the correction velocity. So
60      !!            it will only balance the flux through open boundaries.
61      !!            (set nn_volctl to 0 in tne namelist for this option)
62      !!         2/ The volume is constant even with E-P flux. In this case
63      !!            the correction velocity must balance both the flux
64      !!            through open boundaries and the ones through the free
65      !!            surface.
66      !!            (set nn_volctl to 1 in tne namelist for this option)
67      !!----------------------------------------------------------------------
68      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
69      !
70      INTEGER  ::   ji, jj, jk, jb, jgrd
71      INTEGER  ::   ib_bdy, ii, ij
72      REAL(wp) ::   zubtpecor, z_cflxemp, ztranst
73      TYPE(OBC_INDEX), POINTER :: idx
74      !!-----------------------------------------------------------------------------
75      !
76      IF( nn_timing == 1 )   CALL timing_start('bdy_vol')
77      !
78      IF( ln_vol ) THEN
79      !
80      IF( kt == nit000 ) THEN
81         IF(lwp) WRITE(numout,*)
82         IF(lwp) WRITE(numout,*)'bdy_vol : Correction of velocities along unstructured OBC'
83         IF(lwp) WRITE(numout,*)'~~~~~~~'
84      END IF 
85
86      ! Calculate the cumulate surface Flux z_cflxemp (m3/s) over all the domain
87      ! -----------------------------------------------------------------------
88!!gm replace these lines :
89      z_cflxemp = SUM ( ( emp(:,:) - rnf(:,:) + fwfisf(:,:) ) * bdytmask(:,:) * e1e2t(:,:) ) / rau0
90      IF( lk_mpp )   CALL mpp_sum( z_cflxemp )     ! sum over the global domain
91!!gm   by :
92!!gm      z_cflxemp = glob_sum(  ( emp(:,:)-rnf(:,:)+fwfisf(:,:) ) * bdytmask(:,:) * e1e2t(:,:)  ) / rau0
93!!gm
94
95      ! Transport through the unstructured open boundary
96      ! ------------------------------------------------
97      zubtpecor = 0._wp
98      DO ib_bdy = 1, nb_bdy
99         idx => idx_bdy(ib_bdy)
100         !
101         jgrd = 2                               ! cumulate u component contribution first
102         DO jb = 1, idx%nblenrim(jgrd)
103            DO jk = 1, jpkm1
104               ii = idx%nbi(jb,jgrd)
105               ij = idx%nbj(jb,jgrd)
106               zubtpecor = zubtpecor + idx%flagu(jb,jgrd) * ua(ii,ij, jk) * e2u(ii,ij) * e3u_n(ii,ij,jk)
107            END DO
108         END DO
109         jgrd = 3                               ! then add v component contribution
110         DO jb = 1, idx%nblenrim(jgrd)
111            DO jk = 1, jpkm1
112               ii = idx%nbi(jb,jgrd)
113               ij = idx%nbj(jb,jgrd)
114               zubtpecor = zubtpecor + idx%flagv(jb,jgrd) * va(ii,ij, jk) * e1v(ii,ij) * e3v_n(ii,ij,jk) 
115            END DO
116         END DO
117         !
118      END DO
119      IF( lk_mpp )   CALL mpp_sum( zubtpecor )   ! sum over the global domain
120
121      ! The normal velocity correction
122      ! ------------------------------
123      IF( nn_volctl==1 ) THEN   ;   zubtpecor = ( zubtpecor - z_cflxemp ) / bdysurftot 
124      ELSE                      ;   zubtpecor =   zubtpecor               / bdysurftot
125      END IF
126
127      ! Correction of the total velocity on the unstructured boundary to respect the mass flux conservation
128      ! -------------------------------------------------------------
129      ztranst = 0._wp
130      DO ib_bdy = 1, nb_bdy
131         idx => idx_bdy(ib_bdy)
132         !
133         jgrd = 2                               ! correct u component
134         DO jb = 1, idx%nblenrim(jgrd)
135            DO jk = 1, jpkm1
136               ii = idx%nbi(jb,jgrd)
137               ij = idx%nbj(jb,jgrd)
138               ua(ii,ij,jk) = ua(ii,ij,jk) - idx%flagu(jb,jgrd) * zubtpecor * umask(ii,ij,jk)
139               ztranst = ztranst + idx%flagu(jb,jgrd) * ua(ii,ij,jk) * e2u(ii,ij) * e3u_n(ii,ij,jk)
140            END DO
141         END DO
142         jgrd = 3                              ! correct v component
143         DO jb = 1, idx%nblenrim(jgrd)
144            DO jk = 1, jpkm1
145               ii = idx%nbi(jb,jgrd)
146               ij = idx%nbj(jb,jgrd)
147               va(ii,ij,jk) = va(ii,ij,jk) -idx%flagv(jb,jgrd) * zubtpecor * vmask(ii,ij,jk)
148               ztranst = ztranst + idx%flagv(jb,jgrd) * va(ii,ij,jk) * e1v(ii,ij) * e3v_n(ii,ij,jk)
149            END DO
150         END DO
151         !
152      END DO
153      IF( lk_mpp )   CALL mpp_sum( ztranst )   ! sum over the global domain
154 
155      ! Check the cumulated transport through unstructured OBC once barotropic velocities corrected
156      ! ------------------------------------------------------
157      IF( lwp .AND. MOD( kt, nwrite ) == 0 ) THEN
158         IF(lwp) WRITE(numout,*)
159         IF(lwp) WRITE(numout,*)'bdy_vol : time step :', kt
160         IF(lwp) WRITE(numout,*)'~~~~~~~ '
161         IF(lwp) WRITE(numout,*)'          cumulate flux EMP             =', z_cflxemp  , ' (m3/s)'
162         IF(lwp) WRITE(numout,*)'          total lateral surface of OBC  =', bdysurftot, '(m2)'
163         IF(lwp) WRITE(numout,*)'          correction velocity zubtpecor =', zubtpecor , '(m/s)'
164         IF(lwp) WRITE(numout,*)'          cumulated transport ztranst   =', ztranst   , '(m3/s)'
165      END IF 
166      !
167      IF( nn_timing == 1 )   CALL timing_stop('bdy_vol')
168      !
169      END IF ! ln_vol
170      !
171   END SUBROUTINE bdy_vol
172
173   !!======================================================================
174END MODULE bdyvol
Note: See TracBrowser for help on using the repository browser.