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.
wzvmod.F90 on Ticket #209 – Attachment – NEMO

Ticket #209: wzvmod.F90

File wzvmod.F90, 6.5 KB (added by gm, 16 years ago)
Line 
1MODULE wzvmod
2   !!==============================================================================
3   !!                       ***  MODULE  wzvmod  ***
4   !! Ocean diagnostic variable : vertical velocity
5   !!==============================================================================
6   !! History :   OPA  !  1990-10  (C. Levy, G. Madec)  Original code
7   !!             7.0  !  1996-01  (G. Madec)  Statement function for e3
8   !!  NEMO       1.0  !  2002-07  (G. Madec)  Free form, F90
9   !!             3.0  !  2007-07  (D. Storkey)  Zero zhdiv at open boundary (BDY)
10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!   wzv        : Compute the vertical velocity
14   !!----------------------------------------------------------------------
15   USE oce             ! ocean dynamics and tracers variables
16   USE dom_oce         ! ocean space and time domain variables
17   USE sbc_oce         ! surface boundary condition: ocean
18   USE domvvl          ! Variable volume
19   USE in_out_manager  ! I/O manager
20   USE prtctl          ! Print control
21   USE phycst
22   USE bdy_oce         ! unstructured open boundaries
23   USE lbclnk          ! ocean lateral boundary condition (or mpp link)
24
25   IMPLICIT NONE
26   PRIVATE
27
28   PUBLIC   wzv        ! routine called by step.F90 and inidtr.F90
29
30   !! * Substitutions
31#  include "domzgr_substitute.h90"
32   !!----------------------------------------------------------------------
33   !! NEMO/OPA 3.0 , LOCEAN-IPSL (2008)
34   !! $Id: wzvmod.F90 911 2008-04-28 09:31:32Z ctlod $
35   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
36   !!----------------------------------------------------------------------
37
38CONTAINS
39
40   SUBROUTINE wzv( kt )
41      !!----------------------------------------------------------------------
42      !!                    ***  ROUTINE wzv  ***
43      !!
44      !! ** Purpose :   Compute the now vertical velocity after the array swap
45      !!
46      !! ** Method  :   Using the incompressibility hypothesis, the vertical
47      !!      velocity is computed by integrating the horizontal divergence
48      !!      from the bottom to the surface.
49      !!        The boundary conditions are w=0 at the bottom (no flux) and,
50      !!      in regid-lid case, w=0 at the sea surface.
51      !!
52      !! ** action  :   wn array : the now vertical velocity
53      !!----------------------------------------------------------------------
54      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
55      !!
56      INTEGER  ::           jk           ! dummy loop indices
57      INTEGER  ::   ji, jj               ! dummy loop indices
58      REAL(wp) ::   z2dt, zraur          ! temporary scalar
59      REAL(wp), DIMENSION (jpi,jpj) ::   zssha, zun, zvn, zhdiv
60#if defined key_bdy || defined key_bdy_tides
61      INTEGER  ::     jgrd, jb           ! temporary scalars
62#endif
63      !!----------------------------------------------------------------------
64
65      IF( kt == nit000 ) THEN
66         IF(lwp) WRITE(numout,*)
67         IF(lwp) WRITE(numout,*) 'wzv     : vertical velocity from continuity eq.'
68         IF(lwp) WRITE(numout,*) '~~~~~~~ ' 
69         !
70         ! bottom boundary condition: w=0 (set once for all)
71         wn(:,:,jpk) = 0.e0
72      ENDIF
73
74      IF( lk_vvl ) THEN                ! Variable volume
75         !
76         z2dt = 2. * rdt                                       ! time step: leap-frog
77         IF( neuler == 0 .AND. kt == nit000 ) z2dt = rdt       ! time step: Euler if restart from rest
78         zraur  = 1. / rauw
79
80         ! Vertically integrated quantities
81         ! --------------------------------
82         zun(:,:) = 0.e0
83         zvn(:,:) = 0.e0
84         !
85         DO jk = 1, jpkm1             ! Vertically integrated transports (now)
86            zun(:,:) = zun(:,:) + fse3u(:,:,jk) * un(:,:,jk)
87            zvn(:,:) = zvn(:,:) + fse3v(:,:,jk) * vn(:,:,jk)
88         END DO
89
90         ! Horizontal divergence of barotropic transports
91         !--------------------------------------------------
92         zhdiv(:,:) = 0.e0
93         DO jj = 2, jpjm1
94            DO ji = 2, jpim1   ! vector opt.
95               zhdiv(ji,jj) = (  e2u(ji  ,jj  ) * zun(ji  ,jj  )     &
96                  &            - e2u(ji-1,jj  ) * zun(ji-1,jj  )     &
97                  &            + e1v(ji  ,jj  ) * zvn(ji  ,jj  )     &
98                  &            - e1v(ji  ,jj-1) * zvn(ji  ,jj-1) )   &
99                  &           / ( e1t(ji,jj) * e2t(ji,jj) )
100            END DO
101         END DO
102
103#if defined key_obc && ( key_dynspg_exp || key_dynspg_ts )
104         ! open boundaries (div must be zero behind the open boundary)
105         !  mpp remark: The zeroing of hdiv can probably be extended to 1->jpi/jpj for the correct row/column
106         IF( lp_obc_east  )   zhdiv(nie0p1:nie1p1,nje0  :nje1)   = 0.e0    ! east
107         IF( lp_obc_west  )   zhdiv(niw0  :niw1  ,njw0  :njw1)   = 0.e0    ! west
108         IF( lp_obc_north )   zhdiv(nin0  :nin1  ,njn0p1:njn1p1) = 0.e0    ! north
109         IF( lp_obc_south )   zhdiv(nis0  :nis1  ,njs0  :njs1)   = 0.e0    ! south
110#endif
111
112#if defined key_bdy || defined key_bdy_tides
113         jgrd=1 !: tracer grid.
114         DO jb = 1, nblenrim(jgrd)
115           ji = nbi(jb,jgrd)
116           jj = nbj(jb,jgrd)
117           zhdiv(ji, jj) = 0.e0
118         END DO
119#endif
120
121         CALL lbc_lnk( zhdiv, 'T', 1. )
122
123         ! Sea surface elevation time stepping
124         ! -----------------------------------
125         zssha(:,:) = sshb(:,:) - z2dt * ( zraur * emp(:,:) + zhdiv(:,:) ) * tmask(:,:,1)
126
127         ! Vertical velocity computed from bottom
128         ! --------------------------------------
129         DO jk = jpkm1, 1, -1
130!!gm  faster coding but changes the last digit results
131!!gm        zhdiv(:,:) = ( zssha(:,:) - sshb(:,:) ) * ee_t(:,:) / z2dt
132!!gm        wn(:,:,jk) = wn(:,:,jk+1) - fse3t(:,:,jk) * hdivn(:,:,jk) - zhdiv(:,:) * fsve3t(:,:,jk)
133!!gm old coding :
134            wn(:,:,jk) = wn(:,:,jk+1) - fse3t(:,:,jk) * hdivn(:,:,jk)   &
135              &        - ( zssha(:,:) - sshb(:,:) ) * fsve3t(:,:,jk) * ee_t(:,:) / z2dt
136!!gm end
137         END DO
138
139      ELSE                             ! Fixed volume
140
141         ! Vertical velocity computed from bottom
142         ! --------------------------------------
143         DO jk = jpkm1, 1, -1
144            wn(:,:,jk) = wn(:,:,jk+1) - fse3t(:,:,jk) * hdivn(:,:,jk)
145         END DO
146     
147      ENDIF
148
149      IF(ln_ctl)   CALL prt_ctl(tab3d_1=wn, clinfo1=' w**2 -   : ', mask1=wn)
150
151   END SUBROUTINE wzv
152
153   !!======================================================================
154END MODULE wzvmod