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.
domvvl.F90 in branches/dev_004_VVL/NEMO/OPA_SRC/DOM – NEMO

source: branches/dev_004_VVL/NEMO/OPA_SRC/DOM/domvvl.F90 @ 1385

Last change on this file since 1385 was 1385, checked in by rblod, 15 years ago

Correct a mistake in previous commit for scale factors initialisation

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 10.3 KB
Line 
1MODULE domvvl
2   !!======================================================================
3   !!                       ***  MODULE domvvl   ***
4   !! Ocean :
5   !!======================================================================
6   !! History :   9.0  !  06-06  (B. Levier, L. Marie)  original code
7   !!              "   !  07-07  (D. Storkey) Bug fixes and code for BDY option.
8   !!----------------------------------------------------------------------
9
10   !!----------------------------------------------------------------------
11   !!   'key_vvl'                              variable volume
12   !!----------------------------------------------------------------------
13   !!----------------------------------------------------------------------
14   !!   dom_vvl         : defined scale factors & depths at each time step
15   !!   dom_vvl_ini     : defined coefficients to distribute ssh on each layers
16   !!----------------------------------------------------------------------
17   !! * Modules used
18   USE oce             ! ocean dynamics and tracers
19   USE dom_oce         ! ocean space and time domain
20   USE sbc_oce         ! surface boundary condition: ocean
21   USE dynspg_oce      ! surface pressure gradient variables
22   USE phycst          ! physical constants
23   USE in_out_manager  ! I/O manager
24   USE lib_mpp         ! distributed memory computing library
25   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
26   USE bdy_oce         ! unstructured open boundary conditions
27
28   IMPLICIT NONE
29   PRIVATE
30
31   !! * Routine accessibility
32   PUBLIC dom_vvl_ini    ! called by dom_init.F90
33   PUBLIC dom_vvl        ! called by istate.F90 and step.F90
34
35   !! * Module variables
36   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   hu_0, hv_0
37   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   ee_t, ee_u, ee_v, ee_f   !:
38
39   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   &  !:
40      mut, muu, muv, muf                            !:
41
42   REAL(wp), DIMENSION(jpk) ::   r2dt               ! vertical profile time-step, = 2 rdttra
43      !                                             ! except at nit000 (=rdttra) if neuler=0
44
45   !! * Substitutions
46#  include "domzgr_substitute.h90"
47#  include "vectopt_loop_substitute.h90"
48   !!----------------------------------------------------------------------
49   !!   OPA 9.0 , LOCEAN-IPSL (2005)
50   !! $Id$
51   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
52   !!----------------------------------------------------------------------
53
54CONTAINS       
55
56#if defined key_vvl
57
58   SUBROUTINE dom_vvl_ini
59      !!----------------------------------------------------------------------
60      !!                ***  ROUTINE dom_vvl_ini  ***
61      !!                   
62      !! ** Purpose :  compute coefficients muX at T-U-V-F points to spread
63      !!               ssh over the whole water column (scale factors)
64      !!
65      !!----------------------------------------------------------------------
66      INTEGER  ::   ji, jj, jk
67      REAL(wp) ::   zcoefu, zcoefv, zcoeff
68      !!----------------------------------------------------------------------
69
70      IF(lwp)   THEN
71         WRITE(numout,*)
72         WRITE(numout,*) 'dom_vvl_ini : Variable volume activated'
73         WRITE(numout,*) '~~~~~~~~~~~   compute coef. used to spread ssh over each layers'
74      ENDIF
75
76#if defined key_zco  ||  defined key_dynspg_rl
77      CALL ctl_stop( 'dom_vvl_ini : options key_zco/key_dynspg_rl are incompatible with variable volume option key_vvl')
78#endif
79
80      fsdept(:,:,:) = gdept (:,:,:)
81      fsdepw(:,:,:) = gdepw (:,:,:)
82      fsde3w(:,:,:) = gdep3w(:,:,:)
83      fse3t (:,:,:) = e3t   (:,:,:)
84      fse3u (:,:,:) = e3u   (:,:,:)
85      fse3v (:,:,:) = e3v   (:,:,:)
86      fse3f (:,:,:) = e3f   (:,:,:)
87      fse3w (:,:,:) = e3w   (:,:,:)
88      fse3uw(:,:,:) = e3uw  (:,:,:)
89      fse3vw(:,:,:) = e3vw  (:,:,:)
90
91      ! mu computation
92      ! --------------
93      ! define ee_t, u, v and f as in sigma coordinate (ee_t = 1/ht, ...)
94      ee_t(:,:) = fse3t_0(:,:,1)        ! Lower bound : thickness of the first model level
95      ee_u(:,:) = fse3u_0(:,:,1)
96      ee_v(:,:) = fse3v_0(:,:,1)
97      ee_f(:,:) = fse3f_0(:,:,1)
98      DO jk = 2, jpkm1                   ! Sum of the masked vertical scale factors
99         ee_t(:,:) = ee_t(:,:) + fse3t_0(:,:,jk) * tmask(:,:,jk)
100         ee_u(:,:) = ee_u(:,:) + fse3u_0(:,:,jk) * umask(:,:,jk)
101         ee_v(:,:) = ee_v(:,:) + fse3v_0(:,:,jk) * vmask(:,:,jk)
102         DO jj = 1, jpjm1                      ! f-point : fmask=shlat at coasts, use the product of umask
103            ee_f(:,jj) = ee_f(:,jj) + fse3f_0(:,jj,jk) *  umask(:,jj,jk) * umask(:,jj+1,jk)
104         END DO
105      END DO 
106      !                                  ! Compute and mask the inverse of the local depth at T, U, V and F points
107      ee_t(:,:) = 1. / ee_t(:,:) * tmask(:,:,1)
108      ee_u(:,:) = 1. / ee_u(:,:) * umask(:,:,1)
109      ee_v(:,:) = 1. / ee_v(:,:) * vmask(:,:,1)
110      DO jj = 1, jpjm1                         ! f-point case fmask cannot be used
111         ee_f(:,jj) = 1. / ee_f(:,jj) * umask(:,jj,1) * umask(:,jj+1,1)
112      END DO
113      CALL lbc_lnk( ee_f, 'F', 1. )       ! lateral boundary condition on ee_f
114      !
115      DO jk = 1, jpk
116         mut(:,:,jk) = ee_t(:,:) * tmask(:,:,jk)   ! at T levels
117         muu(:,:,jk) = ee_u(:,:) * umask(:,:,jk)   ! at T levels
118         muv(:,:,jk) = ee_v(:,:) * vmask(:,:,jk)   ! at T levels
119      END DO
120      DO jk = 1, jpk
121         DO jj = 1, jpjm1                      ! f-point : fmask=shlat at coasts, use the product of umask
122               muf(:,jj,jk) = ee_f(:,jj) * umask(:,jj,jk) * umask(:,jj+1,jk)   ! at T levels
123         END DO
124         muf(:,jpj,jk) = 0.e0
125      END DO
126      CALL lbc_lnk( muf, 'F', 1. )       ! lateral boundary condition on ee_f
127
128
129!!debug print
130!         ii=50   ;   ij = 50
131!         do jk= 1, jpk
132!         WRITE(numout,*) 'domvvl GM  : h0=', SUM( fse3t_0(ii,ij,1:jk) * tmask(ii,ij,1:jk) ), 'e3t0=', fse3t_0(ii,ij,jk),   &
133!            &            'e3t =', fse3t_0(ii,ij,jk) * ( 1 +  mut(ii,ij,jk) ), 'mut', mut(ii,ij,jk),   &
134!            &            'h =', SUM( fse3t_0(ii,ij,1:jk) * ( 1 +  mut(ii,ij,1:jk) ) * tmask(ii,ij,1:jk) )
135!         end do
136!!end debug print
137
138      ! Reference ocean depth at U- and V-points
139      hu_0(:,:) = 0.e0   
140      hv_0(:,:) = 0.e0
141      DO jk = 1, jpk
142         hu_0(:,:) = hu_0(:,:) + fse3u(:,:,jk) * umask(:,:,jk)
143         hv_0(:,:) = hv_0(:,:) + fse3v(:,:,jk) * vmask(:,:,jk)
144      END DO
145
146      ! before and now Sea Surface Height at u-, v-, f-points
147      DO jj = 1, jpjm1
148         DO ji = 1, jpim1
149            zcoefu = 0.5  * umask(ji,jj,1) / ( e1u(ji,jj) * e2u(ji,jj) )
150            zcoefv = 0.5  * vmask(ji,jj,1) / ( e1v(ji,jj) * e2v(ji,jj) )
151            zcoeff = 0.25 * fmask(ji,jj,1)
152!!gm bug used of fmask, even if thereafter multiplied by muf  which is correctly masked)
153            sshu_b(ji,jj) = zcoefu * ( e1t(ji  ,jj) * e2t(ji  ,jj) * sshb(ji  ,jj)     &
154               &                     + e1t(ji+1,jj) * e2t(ji+1,jj) * sshb(ji+1,jj) )   
155            sshv_b(ji,jj) = zcoefv * ( e1t(ji,jj  ) * e2t(ji,jj  ) * sshb(ji,jj  )     &
156               &                     + e1t(ji,jj+1) * e2t(ji,jj+1) * sshb(ji,jj+1) )   
157            sshf_b(ji,jj) = zcoeff * ( sshb(ji  ,jj) + sshb(ji  ,jj+1)                 &
158               &                     + sshb(ji+1,jj) + sshb(ji+1,jj+1) )               
159            sshu_n(ji,jj) = zcoefu * ( e1t(ji  ,jj) * e2t(ji  ,jj) * sshn(ji  ,jj)     &
160               &                     + e1t(ji+1,jj) * e2t(ji+1,jj) * sshn(ji+1,jj) )   
161            sshv_n(ji,jj) = zcoefv * ( e1t(ji,jj  ) * e2t(ji,jj  ) * sshn(ji,jj  )     & 
162               &                     + e1t(ji,jj+1) * e2t(ji,jj+1) * sshn(ji,jj+1) )     
163            sshf_n(ji,jj) = zcoeff * ( sshn(ji  ,jj) + sshn(ji  ,jj+1)                 &
164               &                     + sshn(ji+1,jj) + sshn(ji+1,jj+1) )               
165         END DO
166      END DO
167      ! Boundaries conditions
168      CALL lbc_lnk( sshu_b, 'U', 1. )   ;   CALL lbc_lnk( sshu_n, 'U', 1. )
169      CALL lbc_lnk( sshv_b, 'V', 1. )   ;   CALL lbc_lnk( sshv_n, 'V', 1. )
170      CALL lbc_lnk( sshf_b, 'F', 1. )   ;   CALL lbc_lnk( sshf_n, 'F', 1. )
171      !
172
173
174   END SUBROUTINE dom_vvl_ini
175
176
177   SUBROUTINE dom_vvl
178      !!----------------------------------------------------------------------
179      !!                ***  ROUTINE dom_vvl  ***
180      !!                   
181      !! ** Purpose :  compute ssh at U-V-F points, T-W scale factors and local
182      !!               depths at each time step.
183      !!----------------------------------------------------------------------
184      !! * Local declarations
185      INTEGER  ::   ji, jj, jk                 ! dummy loop indices
186      !!----------------------------------------------------------------------
187
188 !     IF( kt == nit000 ) THEN
189 !        IF(lwp) WRITE(numout,*)
190 !        IF(lwp) WRITE(numout,*) 'dom_vvl : '
191 !        IF(lwp) WRITE(numout,*) '~~~~~~~ '
192 !     ENDIF
193
194      ! Scale factors at T levels
195      DO jk = 1, jpkm1
196         fse3t (:,:,jk) = fse3t_n (:,:,jk)
197         fse3u (:,:,jk) = fse3u_n (:,:,jk)
198         fse3v (:,:,jk) = fse3v_n (:,:,jk)
199         fse3f (:,:,jk) = fse3f_n (:,:,jk)
200         fse3w (:,:,jk) = fse3w_n (:,:,jk)
201         fse3uw(:,:,jk) = fse3uw_n(:,:,jk)
202         fse3vw(:,:,jk) = fse3vw_n(:,:,jk)
203      END DO
204
205      DO jk = 1, jpkm1
206         DO jj = 1, jpj
207            DO ji = 1, jpi
208               fsdept(ji,jj,jk) = fsdept_n(ji,jj,jk)
209               fsdepw(ji,jj,jk) = fsdepw_n(ji,jj,jk)
210               fsde3w(ji,jj,jk) = fsde3w_n(ji,jj,jk)
211            END DO
212         END DO
213      END DO
214
215      ! Local depth or Inverse of the local depth of the water column at u- and v-points
216      ! ------------------------------
217      hu(:,:) = hu_0(:,:) + sshu_n(:,:)
218      hv(:,:) = hv_0(:,:) + sshv_n(:,:)
219
220      ! masked  inverse of the local depth
221      hur(:,:) = 1. / MAX( hu(:,:), fse3u_0(:,:,1) ) * umask(:,:,1)
222      hvr(:,:) = 1. / MAX( hv(:,:), fse3v_0(:,:,1) ) * vmask(:,:,1)
223
224   END SUBROUTINE dom_vvl
225
226#else
227   !!----------------------------------------------------------------------
228   !!   Default option :                                      Empty routine
229   !!----------------------------------------------------------------------
230   SUBROUTINE dom_vvl_ini
231   END SUBROUTINE dom_vvl_ini
232   SUBROUTINE dom_vvl
233   END SUBROUTINE dom_vvl
234#endif
235
236   !!======================================================================
237END MODULE domvvl
Note: See TracBrowser for help on using the repository browser.