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

Last change on this file since 6140 was 6140, checked in by timgraham, 9 years ago

Merge of branches/2015/dev_merge_2015 back into trunk. Merge excludes NEMOGCM/TOOLS/OBSTOOLS/ for now due to issues with the change of file type. Will sort these manually with further commits.

Branch merged as follows:
In the working copy of branch ran:
svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk@HEAD
Small conflicts due to bug fixes applied to trunk since the dev_merge_2015 was copied. Bug fixes were applied to the branch as well so these were easy to resolve.
Branch committed at this stage

In working copy run:
svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
to switch working copy

Run:
svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2015/dev_merge_2015
to merge the branch into the trunk and then commit - no conflicts at this stage.

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