bdyvol.F90 8.6 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185
  1. MODULE 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. #if defined key_bdy && defined key_dynspg_flt
  13. !!----------------------------------------------------------------------
  14. !! 'key_bdy' AND unstructured open boundary conditions
  15. !! 'key_dynspg_flt' filtered free surface
  16. !!----------------------------------------------------------------------
  17. USE timing ! Timing
  18. USE oce ! ocean dynamics and tracers
  19. USE sbcisf ! ice shelf
  20. USE dom_oce ! ocean space and time domain
  21. USE phycst ! physical constants
  22. USE bdy_oce ! ocean open boundary conditions
  23. USE lib_mpp ! for mppsum
  24. USE in_out_manager ! I/O manager
  25. USE sbc_oce ! ocean surface boundary conditions
  26. IMPLICIT NONE
  27. PRIVATE
  28. PUBLIC bdy_vol ! routine called by dynspg_flt.h90
  29. !! * Substitutions
  30. # include "domzgr_substitute.h90"
  31. !!----------------------------------------------------------------------
  32. !! NEMO/OPA 3.3 , NEMO Consortium (2010)
  33. !! $Id: bdyvol.F90 5628 2015-07-22 20:26:35Z mathiot $
  34. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  35. !!----------------------------------------------------------------------
  36. CONTAINS
  37. SUBROUTINE bdy_vol( kt )
  38. !!----------------------------------------------------------------------
  39. !! *** ROUTINE bdyvol ***
  40. !!
  41. !! ** Purpose : This routine is called in dynspg_flt to control
  42. !! the volume of the system. A correction velocity is calculated
  43. !! to correct the total transport through the unstructured OBC.
  44. !! The total depth used is constant (H0) to be consistent with the
  45. !! linear free surface coded in OPA 8.2
  46. !!
  47. !! ** Method : The correction velocity (zubtpecor here) is defined calculating
  48. !! the total transport through all open boundaries (trans_bdy) minus
  49. !! the cumulate E-P flux (z_cflxemp) divided by the total lateral
  50. !! surface (bdysurftot) of the unstructured boundary.
  51. !! zubtpecor = [trans_bdy - z_cflxemp ]*(1./bdysurftot)
  52. !! with z_cflxemp => sum of (Evaporation minus Precipitation)
  53. !! over all the domain in m3/s at each time step.
  54. !! z_cflxemp < 0 when precipitation dominate
  55. !! z_cflxemp > 0 when evaporation dominate
  56. !!
  57. !! There are 2 options (user's desiderata):
  58. !! 1/ The volume changes according to E-P, this is the default
  59. !! option. In this case the cumulate E-P flux are setting to
  60. !! zero (z_cflxemp=0) to calculate the correction velocity. So
  61. !! it will only balance the flux through open boundaries.
  62. !! (set nn_volctl to 0 in tne namelist for this option)
  63. !! 2/ The volume is constant even with E-P flux. In this case
  64. !! the correction velocity must balance both the flux
  65. !! through open boundaries and the ones through the free
  66. !! surface.
  67. !! (set nn_volctl to 1 in tne namelist for this option)
  68. !!----------------------------------------------------------------------
  69. INTEGER, INTENT( in ) :: kt ! ocean time-step index
  70. !!
  71. INTEGER :: ji, jj, jk, jb, jgrd
  72. INTEGER :: ib_bdy, ii, ij
  73. REAL(wp) :: zubtpecor, z_cflxemp, ztranst
  74. TYPE(OBC_INDEX), POINTER :: idx
  75. !!-----------------------------------------------------------------------------
  76. IF( nn_timing == 1 ) CALL timing_start('bdy_vol')
  77. IF( ln_vol ) THEN
  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. ! Calculate the cumulate surface Flux z_cflxemp (m3/s) over all the domain
  84. ! -----------------------------------------------------------------------
  85. z_cflxemp = SUM ( ( emp(:,:)-rnf(:,:)+fwfisf(:,:) ) * bdytmask(:,:) * e1t(:,:) * e2t(:,:) ) / rau0
  86. IF( lk_mpp ) CALL mpp_sum( z_cflxemp ) ! sum over the global domain
  87. ! Transport through the unstructured open boundary
  88. ! ------------------------------------------------
  89. zubtpecor = 0.e0
  90. DO ib_bdy = 1, nb_bdy
  91. idx => idx_bdy(ib_bdy)
  92. jgrd = 2 ! cumulate u component contribution first
  93. DO jb = 1, idx%nblenrim(jgrd)
  94. DO jk = 1, jpkm1
  95. ii = idx%nbi(jb,jgrd)
  96. ij = idx%nbj(jb,jgrd)
  97. zubtpecor = zubtpecor + idx%flagu(jb,jgrd) * ua(ii,ij, jk) * e2u(ii,ij) * fse3u(ii,ij,jk)
  98. END DO
  99. END DO
  100. jgrd = 3 ! then add v component contribution
  101. DO jb = 1, idx%nblenrim(jgrd)
  102. DO jk = 1, jpkm1
  103. ii = idx%nbi(jb,jgrd)
  104. ij = idx%nbj(jb,jgrd)
  105. zubtpecor = zubtpecor + idx%flagv(jb,jgrd) * va(ii,ij, jk) * e1v(ii,ij) * fse3v(ii,ij,jk)
  106. END DO
  107. END DO
  108. END DO
  109. IF( lk_mpp ) CALL mpp_sum( zubtpecor ) ! sum over the global domain
  110. ! The normal velocity correction
  111. ! ------------------------------
  112. IF( nn_volctl==1 ) THEN ; zubtpecor = ( zubtpecor - z_cflxemp) / bdysurftot
  113. ELSE ; zubtpecor = zubtpecor / bdysurftot
  114. END IF
  115. ! Correction of the total velocity on the unstructured boundary to respect the mass flux conservation
  116. ! -------------------------------------------------------------
  117. ztranst = 0.e0
  118. DO ib_bdy = 1, nb_bdy
  119. idx => idx_bdy(ib_bdy)
  120. jgrd = 2 ! correct u component
  121. DO jb = 1, idx%nblenrim(jgrd)
  122. DO jk = 1, jpkm1
  123. ii = idx%nbi(jb,jgrd)
  124. ij = idx%nbj(jb,jgrd)
  125. ua(ii,ij,jk) = ua(ii,ij,jk) - idx%flagu(jb,jgrd) * zubtpecor * umask(ii,ij,jk)
  126. ztranst = ztranst + idx%flagu(jb,jgrd) * ua(ii,ij,jk) * e2u(ii,ij) * fse3u(ii,ij,jk)
  127. END DO
  128. END DO
  129. jgrd = 3 ! correct v component
  130. DO jb = 1, idx%nblenrim(jgrd)
  131. DO jk = 1, jpkm1
  132. ii = idx%nbi(jb,jgrd)
  133. ij = idx%nbj(jb,jgrd)
  134. va(ii,ij,jk) = va(ii,ij,jk) -idx%flagv(jb,jgrd) * zubtpecor * vmask(ii,ij,jk)
  135. ztranst = ztranst + idx%flagv(jb,jgrd) * va(ii,ij,jk) * e1v(ii,ij) * fse3v(ii,ij,jk)
  136. END DO
  137. END DO
  138. END DO
  139. IF( lk_mpp ) CALL mpp_sum( ztranst ) ! sum over the global domain
  140. ! Check the cumulated transport through unstructured OBC once barotropic velocities corrected
  141. ! ------------------------------------------------------
  142. IF( lwp .AND. MOD( kt, nwrite ) == 0) THEN
  143. IF(lwp) WRITE(numout,*)
  144. IF(lwp) WRITE(numout,*)'bdy_vol : time step :', kt
  145. IF(lwp) WRITE(numout,*)'~~~~~~~ '
  146. IF(lwp) WRITE(numout,*)' cumulate flux EMP =', z_cflxemp , ' (m3/s)'
  147. IF(lwp) WRITE(numout,*)' total lateral surface of OBC =', bdysurftot, '(m2)'
  148. IF(lwp) WRITE(numout,*)' correction velocity zubtpecor =', zubtpecor , '(m/s)'
  149. IF(lwp) WRITE(numout,*)' cumulated transport ztranst =', ztranst , '(m3/s)'
  150. END IF
  151. !
  152. IF( nn_timing == 1 ) CALL timing_stop('bdy_vol')
  153. !
  154. END IF ! ln_vol
  155. END SUBROUTINE bdy_vol
  156. #else
  157. !!----------------------------------------------------------------------
  158. !! Dummy module NO Unstruct Open Boundary Conditions
  159. !!----------------------------------------------------------------------
  160. CONTAINS
  161. SUBROUTINE bdy_vol( kt ) ! Empty routine
  162. WRITE(*,*) 'bdy_vol: You should not have seen this print! error?', kt
  163. END SUBROUTINE bdy_vol
  164. #endif
  165. !!======================================================================
  166. END MODULE bdyvol