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

source: trunk/NEMO/OPA_SRC/DYN/dynspg_exp_jki.F90 @ 719

Last change on this file since 719 was 719, checked in by ctlod, 17 years ago

get back to the nemo_v2_3 version for trunk

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 9.7 KB
Line 
1MODULE dynspg_exp_jki
2   !!======================================================================
3   !!                   ***  MODULE  dynspg_exp_jki  ***
4   !! Ocean dynamics:  surface pressure gradient trend
5   !!======================================================================
6#if defined key_dynspg_exp   ||   defined key_esopa
7   !!----------------------------------------------------------------------
8   !!   'key_dynspg_exp'                              explicit free surface
9   !!----------------------------------------------------------------------
10   !!   dyn_spg_exp_jki  : update the momentum trend with the surface
11   !!                      pressure gradient in the free surface constant 
12   !!                      volume case with vector optimization
13   !!----------------------------------------------------------------------
14   !! * Modules used
15   USE oce             ! ocean dynamics and tracers
16   USE dom_oce         ! ocean space and time domain
17   USE in_out_manager  ! I/O manager
18   USE phycst          ! physical constants
19   USE ocesbc          ! ocean surface boundary condition
20   USE obc_oce         ! Lateral open boundary condition
21   USE obc_par         ! open boundary condition parameters
22   USE obcdta          ! open boundary condition data     (obc_dta_bt routine)
23   USE lib_mpp         ! distributed memory computing library
24   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
25   USE prtctl          ! Print control
26   USE dynspg_exp      ! surface pressure gradient
27   USE restart         ! only for lrst_oce
28
29   IMPLICIT NONE
30   PRIVATE
31
32   !! * Accessibility
33   PUBLIC dyn_spg_exp_jki  ! routine called by step.F90
34
35   !! * Substitutions
36#  include "domzgr_substitute.h90"
37#  include "vectopt_loop_substitute.h90"
38   !!----------------------------------------------------------------------
39   !!  OPA 9.0 , LOCEAN-IPSL (2005)
40   !! $Header$
41   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
42   !!----------------------------------------------------------------------
43
44CONTAINS
45
46   SUBROUTINE dyn_spg_exp_jki( kt )
47      !!----------------------------------------------------------------------
48      !!                  ***  routine dyn_spg_exp_jki  ***
49      !!
50      !! ** Purpose :   Compute the now trend due to the surface pressure
51      !!      gradient in case of explicit free surface formulation and
52      !!      add it to the general trend of momentum equation. Compute
53      !!      the free surface.
54      !!
55      !! ** Method  :   Explicit free surface formulation. The surface pressure
56      !!      gradient is given by:
57      !!         spgu = 1/rau0 d/dx(ps) =  g/e1u di( sshn )
58      !!         spgv = 1/rau0 d/dy(ps) =  g/e2v dj( sshn )
59      !!      -1- Compute the now surface pressure gradient
60      !!      -2- Add it to the general trend
61      !!      -3- Compute the horizontal divergence of velocities
62      !!      - the now divergence is given by :
63      !!         zhdivn = 1/(e1t*e2t*e3t) ( di[e2u*e3u un] + dj[e1v*e3v vn] )
64      !!      - integrate the horizontal divergence from the bottom
65      !!         to the surface
66      !!      - apply lateral boundary conditions on zhdivn
67      !!      -4- Estimate the after sea surface elevation from the kinematic
68      !!         surface boundary condition:
69      !!         zssha = sshb - 2 rdt ( zhdiv + emp )
70      !!      - Time filter applied on now sea surface elevation to avoid
71      !!         the divergence of two consecutive time-steps and swap of free
72      !!         surface arrays to start the next time step:
73      !!         sshb = sshn + atfp * [ sshb + zssha - 2 sshn ]
74      !!         sshn = zssha
75      !!      - apply lateral boundary conditions on sshn
76      !!
77      !! ** Action : - Update (ua,va) with the surf. pressure gradient trend
78      !!
79      !! References :
80      !!
81      !! History :
82      !!   9.0  !  05-11  (V. Garnier, G. Madec, L. Bessieres) Original code
83      !!
84      !!---------------------------------------------------------------------
85      !! * Arguments
86      INTEGER, INTENT( in )  ::   kt         ! ocean time-step index
87
88      !! * Local declarations
89      INTEGER  ::   ji, jj, jk               ! dummy loop indices
90      REAL(wp) ::   z2dt, zraur, zssha       ! temporary scalars
91      REAL(wp), DIMENSION(jpi,jpj)    ::  &  ! temporary arrays
92         &         zhdiv
93      !!----------------------------------------------------------------------
94
95      IF( kt == nit000 ) THEN
96         IF(lwp) WRITE(numout,*)
97         IF(lwp) WRITE(numout,*) 'dyn_spg_exp_jki : surface pressure gradient trend'
98         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~~   (explicit free surface, j-k-i loop)'
99
100         ! set to zero free surface specific arrays
101         spgu(:,:) = 0.e0                     ! surface pressure gradient (i-direction)
102         spgv(:,:) = 0.e0                     ! surface pressure gradient (j-direction)
103
104         CALL exp_rst( nit000, 'READ' )       ! read or initialize the following fields:
105         !                                    ! sshb, sshn
106
107      ENDIF
108
109      ! 0. Local constant initialization
110      ! --------------------------------
111      ! read or estimate sea surface height and vertically integrated velocities
112      IF( lk_obc )   CALL obc_dta_bt( kt, 0 )
113      z2dt = 2. * rdt                                       ! time step: leap-frog
114      IF( neuler == 0 .AND. kt == nit000 ) z2dt = rdt       ! time step: Euler if restart from rest
115      zraur = 1.e0 / rauw
116
117!CDIR PARALLEL DO
118!$OMP PARALLEL DO
119      !                                                ! =============== !
120      DO jj = 2, jpjm1                                 !  Vertical slab  !
121         !                                             ! =============== !
122
123         ! Surface pressure gradient (now)
124         DO ji = 2, jpim1
125            spgu(ji,jj) = - grav * ( sshn(ji+1,jj) - sshn(ji,jj) ) / e1u(ji,jj)
126            spgv(ji,jj) = - grav * ( sshn(ji,jj+1) - sshn(ji,jj) ) / e2v(ji,jj)
127         END DO
128
129         ! Add the surface pressure trend to the general trend
130         DO jk = 1, jpkm1
131            DO ji = 2, jpim1
132               ua(ji,jj,jk) = ua(ji,jj,jk) + spgu(ji,jj)
133               va(ji,jj,jk) = va(ji,jj,jk) + spgv(ji,jj)
134            END DO
135         END DO
136     
137         !  Vertical integration of horizontal divergence of velocities
138         zhdiv(:,jj) = 0.e0
139         DO jk = jpkm1, 1, -1
140            DO ji = 2, jpim1
141               zhdiv(ji,jj) = zhdiv(ji,jj) + (  e2u(ji  ,jj  ) * fse3u(ji  ,jj  ,jk) * un(ji  ,jj  ,jk)      &
142                  &                           - e2u(ji-1,jj  ) * fse3u(ji-1,jj  ,jk) * un(ji-1,jj  ,jk)      &
143                  &                           + e1v(ji  ,jj  ) * fse3v(ji  ,jj  ,jk) * vn(ji  ,jj  ,jk)      &
144                  &                           - e1v(ji  ,jj-1) * fse3v(ji  ,jj-1,jk) * vn(ji  ,jj-1,jk)  )   &
145                  &                        / ( e1t(ji,jj) * e2t(ji,jj) )
146            END DO
147         END DO
148
149#if defined key_obc
150         ! open boundaries (div must be zero behind the open boundary)
151         !  mpp remark: The zeroing of zhdiv can probably be extended to 1->jpi/jpj for the correct row/column
152         IF( lp_obc_east  ) THEN
153            IF( nje0   <= jj .AND. jj <= nje1   )   zhdiv(nie0p1:nie1p1,jj) = 0.e0      ! east
154         ENDIF
155         IF( lp_obc_west  ) THEN
156            IF( njw0   <= jj .AND. jj <= njw1   )   zhdiv(niw0  :niw1  ,jj) = 0.e0      ! west
157         ENDIF
158         IF( lp_obc_north ) THEN
159            IF( njn0p1 <= jj .AND. jj <= njn1p1 )   zhdiv(nin0  :nin1  ,jj) = 0.e0      ! north
160         ENDIF
161         IF( lp_obc_south ) THEN
162            IF( njs0   <= jj .AND. jj <= njs1   )   zhdiv(nis0  :nis1  ,jj) = 0.e0      ! south
163         ENDIF
164#endif
165
166         ! Sea surface elevation time stepping
167         IF( neuler == 0 .AND. kt == nit000 ) THEN       ! Euler (forward) time stepping, no time filter
168            DO ji = 2, jpim1
169               ! after free surface elevation
170               zssha = sshb(ji,jj) - rdt * ( zraur * emp(ji,jj) + zhdiv(ji,jj) ) * tmask(ji,jj,1)
171               ! swap of arrays
172               sshb(ji,jj) = sshn(ji,jj)
173               sshn(ji,jj) = zssha
174            END DO
175         ELSE                                            ! Leap-frog time stepping and time filter
176            DO ji = 2, jpim1
177               ! after free surface elevation
178               zssha = sshb(ji,jj) - z2dt * ( zraur * emp(ji,jj) + zhdiv(ji,jj) ) * tmask(ji,jj,1)
179               ! time filter and array swap
180               sshb(ji,jj) = atfp * ( sshb(ji,jj) + zssha ) + atfp1 * sshn(ji,jj)
181               sshn(ji,jj) = zssha
182            END DO
183         ENDIF
184         !                                             ! =============== !
185      END DO                                           !     end slab    !
186      !                                                ! =============== !
187
188      ! Boundary conditions on sshn
189      IF( .NOT. lk_obc ) CALL lbc_lnk( sshn, 'T', 1. )
190
191      ! write filtered free surface arrays in restart file
192      ! --------------------------------------------------
193      IF( lrst_oce )   CALL exp_rst( kt, 'WRITE' )
194 
195      IF(ln_ctl) THEN         ! print sum trends (used for debugging)
196         CALL prt_ctl(tab2d_1=sshn, clinfo1=' ssh      : ', mask1=tmask)
197      ENDIF
198     
199   END SUBROUTINE dyn_spg_exp_jki
200
201#else
202   !!----------------------------------------------------------------------
203   !!   Default case :   Empty module   No standart explicit free surface
204   !!----------------------------------------------------------------------
205CONTAINS
206   SUBROUTINE dyn_spg_exp_jki( kt )       ! Empty routine
207      WRITE(*,*) 'dyn_spg_exp_jki: You should not have seen this print! error?', kt
208   END SUBROUTINE dyn_spg_exp_jki
209#endif
210   
211   !!======================================================================
212END MODULE dynspg_exp_jki
Note: See TracBrowser for help on using the repository browser.