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 @ 3

Last change on this file since 3 was 3, checked in by opalod, 20 years ago

Initial revision

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 5.6 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, LODYC-IPSL (2003)
58      !!----------------------------------------------------------------------
59
60      IF( kt == nit000 ) THEN
61         IF(lwp) WRITE(numout,*)
62         IF(lwp) WRITE(numout,*) 'wzv     : vertical velocity from continuity eq.'
63         IF(lwp) WRITE(numout,*) '~~~~~~~   auto-tasking case : j-k-i loop '
64
65         ! bottom boundary condition: w=0 (set once for all)
66         wn(:,:,jpk) = 0.e0
67      ENDIF
68
69      !                                                ! ===============
70      DO jj = 1, jpj                                   !  Vertical slab
71         !                                             ! ===============
72         ! Computation from the bottom
73         DO jk = jpkm1, 1, -1
74            wn(:,jj,jk) = wn(:,jj,jk+1) - fse3t(:,jj,jk) * hdivn(:,jj,jk)
75         END DO
76         !                                             ! ===============
77      END DO                                           !   End of slab
78      !                                                ! ===============
79
80      IF(l_ctl) THEN                ! print mean trends (used for debugging)
81         WRITE(numout,*) ' w**2 -   : ', SUM( wn(:,:,:) * wn   (:,:,:) )
82      ENDIF
83
84   END SUBROUTINE wzv
85
86#else
87   !!----------------------------------------------------------------------
88   !!   Default option                                           k-j-i loop
89   !!----------------------------------------------------------------------
90
91   SUBROUTINE wzv( kt )
92      !!----------------------------------------------------------------------
93      !!                    ***  ROUTINE wzv  ***
94      !!
95      !! ** Purpose :   Compute the now vertical velocity after the array swap
96      !!
97      !! ** Method  :   Using the incompressibility hypothesis, the vertical
98      !!      velocity is computed by integrating the horizontal divergence
99      !!      from the bottom to the surface.
100      !!        The boundary conditions are w=0 at the bottom (no flux) and,
101      !!      in regid-lid case, w=0 at the sea surface.
102      !!
103      !! ** action  :   wn array : the now vertical velocity
104      !!
105      !! History :
106      !!   9.0  !  02-07  (G. Madec)  Vector optimization
107      !!----------------------------------------------------------------------
108      !! * Arguments
109      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
110
111      !! * Local declarations
112      INTEGER ::   jk          ! dummy loop indices
113      !!----------------------------------------------------------------------
114      !!  OPA 8.5, LODYC-IPSL (2002)
115      !!----------------------------------------------------------------------
116
117      IF( kt == nit000 ) THEN
118         IF(lwp) WRITE(numout,*)
119         IF(lwp) WRITE(numout,*) 'wzv     : vertical velocity from continuity eq.'
120         IF(lwp) WRITE(numout,*) '~~~~~~~ ' 
121
122         ! bottom boundary condition: w=0 (set once for all)
123         wn(:,:,jpk) = 0.e0
124      ENDIF
125
126      ! Computation from the bottom
127      DO jk = jpkm1, 1, -1
128         wn(:,:,jk) = wn(:,:,jk+1) - fse3t(:,:,jk) * hdivn(:,:,jk)
129      END DO
130
131      IF(l_ctl) THEN                ! print mean trends (used for debugging)
132         WRITE(numout,*) ' w**2 -   : ', SUM( wn(:,:,:) * wn   (:,:,:) )
133      ENDIF
134
135   END SUBROUTINE wzv
136#endif
137
138   !!======================================================================
139END MODULE wzvmod
Note: See TracBrowser for help on using the repository browser.