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 in trunk/NEMO/OPA_SRC/DYN – NEMO

source: trunk/NEMO/OPA_SRC/DYN/wzvmod.F90 @ 247

Last change on this file since 247 was 247, checked in by opalod, 19 years ago

CL : Add CVS Header and CeCILL licence information

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 5.8 KB
Line 
1MODULE wzvmod
2   !!==============================================================================
3   !!                       ***  MODULE  wzvmod  ***
4   !! Ocean diagnostic variable : vertical velocity
5   !!==============================================================================
6
7   !!----------------------------------------------------------------------
8   !!   wzv        : Compute the vertical velocity
9   !!----------------------------------------------------------------------
10   !! * Modules used
11   USE oce             ! ocean dynamics and tracers variables
12   USE dom_oce         ! ocean space and time domain variables
13   USE in_out_manager  ! I/O manager
14
15   IMPLICIT NONE
16   PRIVATE
17
18   !! * Routine accessibility
19   PUBLIC wzv       ! routine called by step.F90 and inidtr.F90
20
21   !! * Substitutions
22#  include "domzgr_substitute.h90"
23   !!----------------------------------------------------------------------
24
25CONTAINS
26
27#if defined key_autotasking
28   !!----------------------------------------------------------------------
29   !!   'key_autotasking'                               j-k-i loop (j-slab)
30   !!----------------------------------------------------------------------
31
32   SUBROUTINE wzv( kt )
33      !!----------------------------------------------------------------------
34      !!                    ***  ROUTINE wzv  ***
35      !!                     
36      !! ** Purpose :   Compute the now vertical velocity after the array swap
37      !!
38      !! ** Method  :   Using the incompressibility hypothesis, the vertical
39      !!     velocity is computed by integrating the horizontal divergence
40      !!     from the bottom to the surface.
41      !!       The boundary conditions are w=0 at the bottom (no flux) and,
42      !!     in regid-lid case, w=0 at the sea surface.
43      !!
44      !! ** action  :    wn array : the now vertical velocity
45      !!
46      !! History :
47      !!   5.0  !  90-10  (C. Levy, G. Madec)  Original code
48      !!   7.0  !  96-01  (G. Madec)  Statement function for e3
49      !!   8.5  !  02-07  (G. Madec)  Free form, F90
50      !!----------------------------------------------------------------------
51      !! * Arguments
52      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
53
54      !! * Local declarations
55      INTEGER ::   jj, jk      ! dummy loop indices
56      !!----------------------------------------------------------------------
57      !!  OPA 9.0 , LOCEAN-IPSL (2005)
58      !! $Header$
59      !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
60      !!----------------------------------------------------------------------
61
62      IF( kt == nit000 ) THEN
63         IF(lwp) WRITE(numout,*)
64         IF(lwp) WRITE(numout,*) 'wzv     : vertical velocity from continuity eq.'
65         IF(lwp) WRITE(numout,*) '~~~~~~~   auto-tasking case : j-k-i loop '
66
67         ! bottom boundary condition: w=0 (set once for all)
68         wn(:,:,jpk) = 0.e0
69      ENDIF
70
71      !                                                ! ===============
72      DO jj = 1, jpj                                   !  Vertical slab
73         !                                             ! ===============
74         ! Computation from the bottom
75         DO jk = jpkm1, 1, -1
76            wn(:,jj,jk) = wn(:,jj,jk+1) - fse3t(:,jj,jk) * hdivn(:,jj,jk)
77         END DO
78         !                                             ! ===============
79      END DO                                           !   End of slab
80      !                                                ! ===============
81
82      IF(l_ctl) THEN                ! print mean trends (used for debugging)
83         WRITE(numout,*) ' w**2 -   : ', SUM( wn(2:nictl,2:njctl,1:jpkm1) * wn   (2:nictl,2:njctl,1:jpkm1) )
84      ENDIF
85
86   END SUBROUTINE wzv
87
88#else
89   !!----------------------------------------------------------------------
90   !!   Default option                                           k-j-i loop
91   !!----------------------------------------------------------------------
92
93   SUBROUTINE wzv( kt )
94      !!----------------------------------------------------------------------
95      !!                    ***  ROUTINE wzv  ***
96      !!
97      !! ** Purpose :   Compute the now vertical velocity after the array swap
98      !!
99      !! ** Method  :   Using the incompressibility hypothesis, the vertical
100      !!      velocity is computed by integrating the horizontal divergence
101      !!      from the bottom to the surface.
102      !!        The boundary conditions are w=0 at the bottom (no flux) and,
103      !!      in regid-lid case, w=0 at the sea surface.
104      !!
105      !! ** action  :   wn array : the now vertical velocity
106      !!
107      !! History :
108      !!   9.0  !  02-07  (G. Madec)  Vector optimization
109      !!----------------------------------------------------------------------
110      !! * Arguments
111      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
112
113      !! * Local declarations
114      INTEGER ::   jk          ! dummy loop indices
115      !!----------------------------------------------------------------------
116      !!  OPA 8.5, LODYC-IPSL (2002)
117      !!----------------------------------------------------------------------
118
119      IF( kt == nit000 ) THEN
120         IF(lwp) WRITE(numout,*)
121         IF(lwp) WRITE(numout,*) 'wzv     : vertical velocity from continuity eq.'
122         IF(lwp) WRITE(numout,*) '~~~~~~~ ' 
123
124         ! bottom boundary condition: w=0 (set once for all)
125         wn(:,:,jpk) = 0.e0
126      ENDIF
127
128      ! Computation from the bottom
129      DO jk = jpkm1, 1, -1
130         wn(:,:,jk) = wn(:,:,jk+1) - fse3t(:,:,jk) * hdivn(:,:,jk)
131      END DO
132
133      IF(l_ctl) THEN                ! print mean trends (used for debugging)
134         WRITE(numout,*) ' w**2 -   : ', SUM( wn(2:nictl,2:njctl,1:jpkm1) * wn   (2:nictl,2:njctl,1:jpkm1) )
135      ENDIF
136
137   END SUBROUTINE wzv
138#endif
139
140   !!======================================================================
141END MODULE wzvmod
Note: See TracBrowser for help on using the repository browser.