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

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/DOM/domvvl.F90 @ 2281

Last change on this file since 2281 was 2281, checked in by smasson, 13 years ago

set proper svn properties to all files...

  • Property svn:keywords set to Id
File size: 8.7 KB
Line 
1MODULE domvvl
2   !!======================================================================
3   !!                       ***  MODULE domvvl   ***
4   !! Ocean :
5   !!======================================================================
6   !! History :  2.0  !  2006-06  (B. Levier, L. Marie)  original code
7   !!            3.1  !  2009-02  (G. Madec, M. Leclair, R. Benshila)  pure z* coordinate
8   !!----------------------------------------------------------------------
9#if defined key_vvl
10   !!----------------------------------------------------------------------
11   !!   'key_vvl'                              variable volume
12   !!----------------------------------------------------------------------
13   !!   dom_vvl     : defined coefficients to distribute ssh on each layers
14   !!----------------------------------------------------------------------
15   USE oce             ! ocean dynamics and tracers
16   USE dom_oce         ! ocean space and time domain
17   USE sbc_oce         ! surface boundary condition: ocean
18   USE phycst          ! physical constants
19   USE in_out_manager  ! I/O manager
20   USE lib_mpp         ! distributed memory computing library
21   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
22
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC   dom_vvl    ! called by domain.F90
27
28   REAL(wp), PUBLIC, DIMENSION(jpi,jpj)     ::   ee_t, ee_u, ee_v, ee_f   !: ???
29   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   mut, muu, muv, muf       !: ???
30
31   REAL(wp), DIMENSION(jpk) ::   r2dt   ! vertical profile time-step, = 2 rdttra
32      !                                 ! except at nit000 (=rdttra) if neuler=0
33
34   !! * Substitutions
35#  include "domzgr_substitute.h90"
36#  include "vectopt_loop_substitute.h90"
37   !!----------------------------------------------------------------------
38   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)
39   !! $Id$
40   !! Software governed by the CeCILL licence  (NEMOGCM/License_CeCILL.txt)
41   !!----------------------------------------------------------------------
42
43CONTAINS       
44
45   SUBROUTINE dom_vvl
46      !!----------------------------------------------------------------------
47      !!                ***  ROUTINE dom_vvl  ***
48      !!                   
49      !! ** Purpose :  compute coefficients muX at T-U-V-F points to spread
50      !!               ssh over the whole water column (scale factors)
51      !!----------------------------------------------------------------------
52      INTEGER  ::   ji, jj, jk
53      REAL(wp) ::   zcoefu , zcoefv   , zcoeff                   ! temporary scalars
54      REAL(wp) ::   zv_t_ij, zv_t_ip1j, zv_t_ijp1, zv_t_ip1jp1   !     -        -
55      REAL(wp), DIMENSION(jpi,jpj) ::  zs_t, zs_u_1, zs_v_1      !     -     2D workspace
56      !!----------------------------------------------------------------------
57
58      IF(lwp)   THEN
59         WRITE(numout,*)
60         WRITE(numout,*) 'dom_vvl : Variable volume activated'
61         WRITE(numout,*) '~~~~~~~~  compute coef. used to spread ssh over each layers'
62      ENDIF
63
64
65      fsdept(:,:,:) = gdept (:,:,:)
66      fsdepw(:,:,:) = gdepw (:,:,:)
67      fsde3w(:,:,:) = gdep3w(:,:,:)
68      fse3t (:,:,:) = e3t   (:,:,:)
69      fse3u (:,:,:) = e3u   (:,:,:)
70      fse3v (:,:,:) = e3v   (:,:,:)
71      fse3f (:,:,:) = e3f   (:,:,:)
72      fse3w (:,:,:) = e3w   (:,:,:)
73      fse3uw(:,:,:) = e3uw  (:,:,:)
74      fse3vw(:,:,:) = e3vw  (:,:,:)
75
76      !                                 !==  mu computation  ==!
77      ee_t(:,:) = fse3t_0(:,:,1)                ! Lower bound : thickness of the first model level
78      ee_u(:,:) = fse3u_0(:,:,1)
79      ee_v(:,:) = fse3v_0(:,:,1)
80      ee_f(:,:) = fse3f_0(:,:,1)
81      DO jk = 2, jpkm1                          ! Sum of the masked vertical scale factors
82         ee_t(:,:) = ee_t(:,:) + fse3t_0(:,:,jk) * tmask(:,:,jk)
83         ee_u(:,:) = ee_u(:,:) + fse3u_0(:,:,jk) * umask(:,:,jk)
84         ee_v(:,:) = ee_v(:,:) + fse3v_0(:,:,jk) * vmask(:,:,jk)
85         DO jj = 1, jpjm1                      ! f-point : fmask=shlat at coasts, use the product of umask
86            ee_f(:,jj) = ee_f(:,jj) + fse3f_0(:,jj,jk) *  umask(:,jj,jk) * umask(:,jj+1,jk)
87         END DO
88      END DO 
89      !                                         ! Compute and mask the inverse of the local depth at T, U, V and F points
90      ee_t(:,:) = 1. / ee_t(:,:) * tmask(:,:,1)
91      ee_u(:,:) = 1. / ee_u(:,:) * umask(:,:,1)
92      ee_v(:,:) = 1. / ee_v(:,:) * vmask(:,:,1)
93      DO jj = 1, jpjm1                               ! f-point case fmask cannot be used
94         ee_f(:,jj) = 1. / ee_f(:,jj) * umask(:,jj,1) * umask(:,jj+1,1)
95      END DO
96      CALL lbc_lnk( ee_f, 'F', 1. )                  ! lateral boundary condition on ee_f
97      !
98      DO jk = 1, jpk                            ! mu coefficients
99         mut(:,:,jk) = ee_t(:,:) * tmask(:,:,jk)     ! T-point at T levels
100         muu(:,:,jk) = ee_u(:,:) * umask(:,:,jk)     ! U-point at T levels
101         muv(:,:,jk) = ee_v(:,:) * vmask(:,:,jk)     ! V-point at T levels
102      END DO
103      DO jk = 1, jpk                                 ! F-point : fmask=shlat at coasts, use the product of umask
104         DO jj = 1, jpjm1
105               muf(:,jj,jk) = ee_f(:,jj) * umask(:,jj,jk) * umask(:,jj+1,jk)   ! at T levels
106         END DO
107         muf(:,jpj,jk) = 0.e0
108      END DO
109      CALL lbc_lnk( muf, 'F', 1. )                   ! lateral boundary condition
110
111
112      hu_0(:,:) = 0.e0                          ! Reference ocean depth at U- and V-points
113      hv_0(:,:) = 0.e0
114      DO jk = 1, jpk
115         hu_0(:,:) = hu_0(:,:) + fse3u_0(:,:,jk) * umask(:,:,jk)
116         hv_0(:,:) = hv_0(:,:) + fse3v_0(:,:,jk) * vmask(:,:,jk)
117      END DO
118     
119      ! surface at t-points and inverse surface at (u/v)-points used in surface averaging computations
120      ! for ssh and scale factors
121      zs_t  (:,:) =       e1t(:,:) * e2t(:,:)
122      zs_u_1(:,:) = 0.5 / e1u(:,:) * e2u(:,:)
123      zs_v_1(:,:) = 0.5 / e1v(:,:) * e2v(:,:)
124
125      DO jj = 1, jpjm1                          ! initialise before and now Sea Surface Height at u-, v-, f-points
126         DO ji = 1, jpim1   ! NO vector opt.
127            zcoefu = umask(ji,jj,1) * zs_u_1(ji,jj)
128            zcoefv = vmask(ji,jj,1) * zs_v_1(ji,jj)
129            zcoeff = 0.5 * umask(ji,jj,1) * umask(ji,jj+1,1) / ( e1f(ji,jj) * e2f(ji,jj) )
130            ! before fields
131            zv_t_ij       = zs_t(ji  ,jj  ) * sshb(ji  ,jj  )
132            zv_t_ip1j     = zs_t(ji+1,jj  ) * sshb(ji+1,jj  )
133            zv_t_ijp1     = zs_t(ji  ,jj+1) * sshb(ji  ,jj+1)
134            sshu_b(ji,jj) = zcoefu * ( zv_t_ij + zv_t_ip1j )
135            sshv_b(ji,jj) = zcoefv * ( zv_t_ij + zv_t_ijp1 )
136            ! now fields
137            zv_t_ij       = zs_t(ji  ,jj  ) * sshn(ji  ,jj  )
138            zv_t_ip1j     = zs_t(ji+1,jj  ) * sshn(ji+1,jj  )
139            zv_t_ijp1     = zs_t(ji  ,jj+1) * sshn(ji  ,jj+1)
140            zv_t_ip1jp1   = zs_t(ji  ,jj+1) * sshn(ji  ,jj+1)
141            sshu_n(ji,jj) = zcoefu * ( zv_t_ij + zv_t_ip1j )
142            sshv_n(ji,jj) = zcoefv * ( zv_t_ij + zv_t_ijp1 )
143            sshf_n(ji,jj) = zcoeff * ( zv_t_ij + zv_t_ip1j + zv_t_ijp1 + zv_t_ip1jp1 )
144         END DO
145      END DO
146      CALL lbc_lnk( sshu_n, 'U', 1. )   ;   CALL lbc_lnk( sshu_b, 'U', 1. )      ! lateral boundary conditions
147      CALL lbc_lnk( sshv_n, 'V', 1. )   ;   CALL lbc_lnk( sshv_b, 'V', 1. )
148      CALL lbc_lnk( sshf_n, 'F', 1. )
149
150                                                ! initialise before scale factors at (u/v)-points
151      ! Scale factor anomaly at (u/v)-points: surface averaging of scale factor at t-points
152      DO jk = 1, jpkm1
153         DO jj = 1, jpjm1
154            DO ji = 1, jpim1
155               zv_t_ij           = zs_t(ji  ,jj  ) * fse3t_b(ji  ,jj  ,jk)
156               zv_t_ip1j         = zs_t(ji+1,jj  ) * fse3t_b(ji+1,jj  ,jk)
157               zv_t_ijp1         = zs_t(ji  ,jj+1) * fse3t_b(ji  ,jj+1,jk)
158               fse3u_b(ji,jj,jk) = umask(ji,jj,jk) * ( zs_u_1(ji,jj) * ( zv_t_ij + zv_t_ip1j ) - fse3u_0(ji,jj,jk) )
159               fse3v_b(ji,jj,jk) = vmask(ji,jj,jk) * ( zs_v_1(ji,jj) * ( zv_t_ij + zv_t_ijp1 ) - fse3v_0(ji,jj,jk) )
160            END DO
161         END DO
162      END DO
163      CALL lbc_lnk( fse3u_b(:,:,:), 'U', 1. )               ! lateral boundary conditions
164      CALL lbc_lnk( fse3v_b(:,:,:), 'V', 1. )
165      ! Add initial scale factor to scale factor anomaly
166      fse3u_b(:,:,:) = fse3u_b(:,:,:) + fse3u_0(:,:,:)
167      fse3v_b(:,:,:) = fse3v_b(:,:,:) + fse3v_0(:,:,:)
168      !
169   END SUBROUTINE dom_vvl
170
171#else
172   !!----------------------------------------------------------------------
173   !!   Default option :                                      Empty routine
174   !!----------------------------------------------------------------------
175CONTAINS
176   SUBROUTINE dom_vvl
177   END SUBROUTINE dom_vvl
178#endif
179
180   !!======================================================================
181END MODULE domvvl
Note: See TracBrowser for help on using the repository browser.