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

source: trunk/NEMO/OPA_SRC/DYN/dynspg_flt.F90 @ 371

Last change on this file since 371 was 358, checked in by opalod, 18 years ago

nemo_v1_update_033 : RB + CT : Add new surface pressure gradient algorithms

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 14.9 KB
Line 
1MODULE dynspg_flt
2   !!======================================================================
3   !!                   ***  MODULE  dynspg_flt  ***
4   !! Ocean dynamics:  surface pressure gradient trend
5   !!======================================================================
6#if ( defined key_dynspg_flt && ! defined key_autotasking )   ||   defined key_esopa
7   !!----------------------------------------------------------------------
8   !!   'key_dynspg_flt'                              filtered free surface
9   !!   NOT 'key_autotasking'                      k-j-i loop (vector opt.)
10   !!----------------------------------------------------------------------
11   !!   dyn_spg_flt  : update the momentum trend with the surface pressure
12   !!                  gradient in the filtered free surface case with
13   !!                  vector optimization
14   !!----------------------------------------------------------------------
15   !! * Modules used
16   USE oce             ! ocean dynamics and tracers
17   USE dom_oce         ! ocean space and time domain
18   USE zdf_oce         ! ocean vertical physics
19   USE phycst          ! physical constants
20   USE ocesbc          ! ocean surface boundary condition
21   USE flxrnf          ! ocean runoffs
22   USE sol_oce         ! ocean elliptic solver
23   USE solpcg          ! preconditionned conjugate gradient solver
24   USE solsor          ! Successive Over-relaxation solver
25   USE solfet          ! FETI solver
26   USE solsor_e        ! Successive Over-relaxation solver with MPP optimization
27   USE obc_oce         ! Lateral open boundary condition
28   USE obcdyn          ! ocean open boundary condition (obc_dyn routines)
29   USE obcvol          ! ocean open boundary condition (obc_vol routines)
30   USE lib_mpp         ! distributed memory computing library
31   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
32   USE cla_dynspg      ! cross land advection
33   USE prtctl          ! Print control
34   USE in_out_manager  ! I/O manager
35
36   IMPLICIT NONE
37   PRIVATE
38
39   !! * Accessibility
40   PUBLIC dyn_spg_flt  ! routine called by step.F90
41
42   !! * Substitutions
43#  include "domzgr_substitute.h90"
44#  include "vectopt_loop_substitute.h90"
45   !!----------------------------------------------------------------------
46   !!   OPA 9.0 , LOCEAN-IPSL (2005)
47   !! $Header$
48   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
49   !!----------------------------------------------------------------------
50
51CONTAINS
52
53   SUBROUTINE dyn_spg_flt( kt, kindic )
54      !!----------------------------------------------------------------------
55      !!                  ***  routine dyn_spg_flt  ***
56      !!
57      !! ** Purpose :   Compute the now trend due to the surface pressure
58      !!      gradient in case of filtered free surface formulation  and add
59      !!      it to the general trend of momentum equation.
60      !!
61      !! ** Method  :   Filtered free surface formulation. The surface
62      !!      pressure gradient is given by:
63      !!         spgu = 1/rau0 d/dx(ps) =  1/e1u di( sshn + rnu btda )
64      !!         spgv = 1/rau0 d/dy(ps) =  1/e2v dj( sshn + rnu btda )
65      !!      where sshn is the free surface elevation and btda is the after
66      !!      of the free surface elevation
67      !!       -1- compute the after sea surface elevation from the kinematic
68      !!      surface boundary condition:
69      !!              zssha = sshb + 2 rdt ( wn - 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      !!       -2- evaluate the surface presure trend (including the addi-
76      !!      tional force) in three steps:
77      !!        a- compute the right hand side of the elliptic equation:
78      !!            gcb = 1/(e1t e2t) [ di(e2u spgu) + dj(e1v spgv) ]
79      !!         where (spgu,spgv) are given by:
80      !!            spgu = vertical sum[ e3u (ub+ 2 rdt ua ) ]
81      !!                 - grav 2 rdt hu /e1u di[sshn + emp]
82      !!            spgv = vertical sum[ e3v (vb+ 2 rdt va) ]
83      !!                 - grav 2 rdt hv /e2v dj[sshn + emp]
84      !!         and define the first guess from previous computation :
85      !!            zbtd = btda
86      !!            btda = 2 zbtd - btdb
87      !!            btdb = zbtd
88      !!        b- compute the relative accuracy to be reached by the
89      !!         iterative solver
90      !!        c- apply the solver by a call to sol... routine
91      !!       -3- compute and add the free surface pressure gradient inclu-
92      !!      ding the additional force used to stabilize the equation.
93      !!
94      !! ** Action : - Update (ua,va) with the surf. pressure gradient trend
95      !!
96      !! References :
97      !!      Roullet and Madec 1999, JGR.
98      !!
99      !! History :
100      !!        !  98-05 (G. Roullet)  Original code
101      !!        !  98-10 (G. Madec, M. Imbard)  release 8.2
102      !!   8.5  !  02-08 (G. Madec)  F90: Free form and module
103      !!        !  02-11 (C. Talandier, A-M Treguier) Open boundaries
104      !!   9.0  !  04-08 (C. Talandier) New trends organization
105      !!    "   !  05-11  (V. Garnier) Surface pressure gradient organization
106      !!---------------------------------------------------------------------
107      !! * Arguments
108      INTEGER, INTENT( in )  ::   kt         ! ocean time-step index
109      INTEGER, INTENT( out ) ::   kindic     ! solver convergence flag
110                                             ! if the solver doesn t converge
111                                             ! the flag is < 0
112      !! * Local declarations
113      INTEGER  ::   ji, jj, jk               ! dummy loop indices
114      REAL(wp) ::                         & 
115         z2dt, z2dtg, zraur, znugdt,      &  ! temporary scalars
116         znurau, zssha, zgcb, zbtd,       &  !   "          "
117         ztdgu, ztdgv                        !   "          "
118      !!----------------------------------------------------------------------
119
120      IF( kt == nit000 ) THEN
121         IF(lwp) WRITE(numout,*)
122         IF(lwp) WRITE(numout,*) 'dyn_spg_flt : surface pressure gradient trend'
123         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~   (free surface constant volume case)'
124       
125         ! set to zero free surface specific arrays
126         spgu(:,:) = 0.e0                     ! surface pressure gradient (i-direction)
127         spgv(:,:) = 0.e0                     ! surface pressure gradient (j-direction)
128      ENDIF
129
130      ! Local constant initialization
131      z2dt = 2. * rdt                                       ! time step: leap-frog
132      IF( neuler == 0 .AND. kt == nit000 ) z2dt = rdt       ! time step: Euler if restart from rest
133      z2dtg  = grav * z2dt
134      zraur  = 1. / rauw
135      znugdt =  rnu * grav * z2dt
136      znurau =  znugdt * zraur
137
138      ! Surface pressure gradient (now)
139      DO jj = 2, jpjm1
140         DO ji = fs_2, fs_jpim1   ! vector opt.
141            spgu(ji,jj) = - grav * ( sshn(ji+1,jj) - sshn(ji,jj) ) / e1u(ji,jj)
142            spgv(ji,jj) = - grav * ( sshn(ji,jj+1) - sshn(ji,jj) ) / e2v(ji,jj)
143         END DO
144      END DO 
145
146      ! Add the surface pressure trend to the general trend
147      DO jk = 1, jpkm1
148         DO jj = 2, jpjm1
149            DO ji = fs_2, fs_jpim1   ! vector opt.
150               ua(ji,jj,jk) = ua(ji,jj,jk) + spgu(ji,jj)
151               va(ji,jj,jk) = va(ji,jj,jk) + spgv(ji,jj)
152            END DO
153         END DO
154      END DO
155
156      ! Evaluate the masked next velocity (effect of the additional force not included)
157      DO jk = 1, jpkm1
158         DO jj = 2, jpjm1
159            DO ji = fs_2, fs_jpim1   ! vector opt.
160               ua(ji,jj,jk) = ( ub(ji,jj,jk) + z2dt * ua(ji,jj,jk) ) * umask(ji,jj,jk)
161               va(ji,jj,jk) = ( vb(ji,jj,jk) + z2dt * va(ji,jj,jk) ) * vmask(ji,jj,jk)
162            END DO
163         END DO
164      END DO
165#if defined key_obc
166      ! Update velocities on each open boundary with the radiation algorithm
167      CALL obc_dyn( kt )
168      ! Correction of the barotropic componant velocity to control the volume of the system
169      CALL obc_vol( kt )
170#endif
171#if defined key_orca_r2
172      IF( n_cla == 1 )   CALL dyn_spg_cla( kt )      ! Cross Land Advection (update (ua,va))
173#endif
174
175      ! compute the next vertically averaged velocity (effect of the additional force not included)
176      ! ---------------------------------------------
177      DO jj = 2, jpjm1
178         DO ji = fs_2, fs_jpim1   ! vector opt.
179            spgu(ji,jj) = 0.e0
180            spgv(ji,jj) = 0.e0
181         END DO
182      END DO
183
184      ! vertical sum
185!CDIR NOLOOPCHG
186      IF( lk_vopt_loop ) THEN          ! vector opt., forced unroll
187         DO jk = 1, jpkm1
188            DO ji = 1, jpij
189               spgu(ji,1) = spgu(ji,1) + fse3u(ji,1,jk) * ua(ji,1,jk)
190               spgv(ji,1) = spgv(ji,1) + fse3v(ji,1,jk) * va(ji,1,jk)
191            END DO
192         END DO
193      ELSE                        ! No  vector opt.
194         DO jk = 1, jpkm1
195            DO jj = 2, jpjm1
196               DO ji = 2, jpim1
197                  spgu(ji,jj) = spgu(ji,jj) + fse3u(ji,jj,jk) * ua(ji,jj,jk)
198                  spgv(ji,jj) = spgv(ji,jj) + fse3v(ji,jj,jk) * va(ji,jj,jk)
199               END DO
200            END DO
201         END DO
202      ENDIF
203
204      ! transport: multiplied by the horizontal scale factor
205      DO jj = 2, jpjm1
206         DO ji = fs_2, fs_jpim1   ! vector opt.
207            spgu(ji,jj) = spgu(ji,jj) * e2u(ji,jj)
208            spgv(ji,jj) = spgv(ji,jj) * e1v(ji,jj)
209         END DO
210      END DO
211
212      ! Boundary conditions on (spgu,spgv)
213      CALL lbc_lnk( spgu, 'U', -1. )
214      CALL lbc_lnk( spgv, 'V', -1. )
215
216      ! Right hand side of the elliptic equation and first guess
217      ! -----------------------------------------------------------
218      DO jj = 2, jpjm1
219         DO ji = fs_2, fs_jpim1   ! vector opt.
220            ! Divergence of the after vertically averaged velocity
221            zgcb =  spgu(ji,jj) - spgu(ji-1,jj)   &
222                  + spgv(ji,jj) - spgv(ji,jj-1)
223            gcb(ji,jj) = gcdprc(ji,jj) * zgcb
224            ! First guess of the after barotropic transport divergence
225            zbtd = gcx(ji,jj)
226            gcx (ji,jj) = 2. * zbtd   - gcxb(ji,jj)
227            gcxb(ji,jj) =      zbtd
228         END DO
229      END DO
230      ! applied the lateral boundary conditions
231      IF( nsolv == 4 )   CALL lbc_lnk_e( gcb, c_solver_pt, 1. )   
232
233      ! Relative precision (computation on one processor)
234      ! ------------------
235      rnorme =0.
236      rnorme = SUM( gcb(1:jpi,1:jpj) * gcdmat(1:jpi,1:jpj) * gcb(1:jpi,1:jpj) * bmask(:,:) )
237      IF( lk_mpp )   CALL mpp_sum( rnorme )   ! sum over the global domain
238
239      epsr = eps * eps * rnorme
240      ncut = 0
241      ! if rnorme is 0, the solution is 0, the solver isn't called
242      IF( rnorme == 0.e0 ) THEN
243         gcx(:,:) = 0.e0
244         res   = 0.e0
245         niter = 0
246         ncut  = 999
247      ENDIF
248
249      ! Evaluate the next transport divergence
250      ! --------------------------------------
251      !    Iterarive solver for the elliptic equation (except IF sol.=0)
252      !    (output in gcx with boundary conditions applied)
253      kindic = 0
254      IF( ncut == 0 ) THEN
255         IF( nsolv == 1 ) THEN         ! diagonal preconditioned conjuguate gradient
256            CALL sol_pcg( kindic )
257         ELSEIF( nsolv == 2 ) THEN     ! successive-over-relaxation
258            CALL sol_sor( kindic )
259         ELSEIF( nsolv == 3 ) THEN     ! FETI solver
260            CALL sol_fet( kindic )
261         ELSEIF( nsolv == 4 ) THEN     ! successive-over-relaxation with extra outer halo
262            CALL sol_sor_e( kindic )
263         ELSE                          ! e r r o r in nsolv namelist parameter
264            IF(lwp) WRITE(numout,cform_err)
265            IF(lwp) WRITE(numout,*) ' dyn_spg_flt : e r r o r, nsolv = 1, 2 ,3 or 4'
266            IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~                not = ', nsolv
267            nstop = nstop + 1
268         ENDIF
269      ENDIF
270
271      ! Transport divergence gradient multiplied by z2dt
272      ! --------------------------------------------====
273      DO jj = 2, jpjm1
274         DO ji = fs_2, fs_jpim1   ! vector opt.
275            ! trend of Transport divergence gradient
276            ztdgu = znugdt * (gcx(ji+1,jj  ) - gcx(ji,jj) ) / e1u(ji,jj)
277            ztdgv = znugdt * (gcx(ji  ,jj+1) - gcx(ji,jj) ) / e2v(ji,jj)
278            ! multiplied by z2dt
279#if defined key_obc
280            ! caution : grad D = 0 along open boundaries
281            spgu(ji,jj) = z2dt * ztdgu * obcumask(ji,jj)
282            spgv(ji,jj) = z2dt * ztdgv * obcvmask(ji,jj)
283#else
284            spgu(ji,jj) = z2dt * ztdgu
285            spgv(ji,jj) = z2dt * ztdgv
286#endif
287         END DO
288      END DO
289
290      ! Add the trends multiplied by z2dt to the after velocity
291      ! -------------------------------------------------------
292      !     ( c a u t i o n : (ua,va) here are the after velocity not the
293      !                       trend, the leap-frog time stepping will not
294      !                       be done in dynnxt.F routine)
295      DO jk = 1, jpkm1
296         DO jj = 2, jpjm1
297            DO ji = fs_2, fs_jpim1   ! vector opt.
298               ua(ji,jj,jk) = (ua(ji,jj,jk) + spgu(ji,jj)) * umask(ji,jj,jk)
299               va(ji,jj,jk) = (va(ji,jj,jk) + spgv(ji,jj)) * vmask(ji,jj,jk)
300            END DO
301         END DO
302      END DO
303
304
305      ! Sea surface elevation time stepping
306      ! -----------------------------------
307      IF( neuler == 0 .AND. kt == nit000 ) THEN      ! Euler (forward) time stepping, no time filter
308         DO jj = 1, jpj
309            DO ji = 1, jpi
310               ! after free surface elevation
311               zssha = sshb(ji,jj) + rdt * ( wn(ji,jj,1) - emp(ji,jj) * zraur ) * tmask(ji,jj,1)
312               ! swap of arrays
313               sshb(ji,jj) = sshn(ji,jj)
314               sshn(ji,jj) = zssha
315            END DO
316         END DO
317      ELSE                                           ! Leap-frog time stepping and time filter
318         DO jj = 1, jpj
319            DO ji = 1, jpi
320               ! after free surface elevation
321               zssha = sshb(ji,jj) + z2dt * ( wn(ji,jj,1) - emp(ji,jj) * zraur ) * tmask(ji,jj,1)
322               ! time filter and array swap
323               sshb(ji,jj) = atfp * ( sshb(ji,jj) + zssha ) + atfp1 * sshn(ji,jj)
324               sshn(ji,jj) = zssha
325            END DO
326         END DO
327      ENDIF
328
329      !                       ! print sum trends (used for debugging)
330      IF(ln_ctl)   CALL prt_ctl( tab2d_1=sshn, clinfo1=' spg  - ssh: ', mask1=tmask )
331
332   END SUBROUTINE dyn_spg_flt
333
334#else
335   !!----------------------------------------------------------------------
336   !!   Default case :   Empty module   No standart free surface cst volume
337   !!----------------------------------------------------------------------
338CONTAINS
339   SUBROUTINE dyn_spg_flt( kt, kindic )       ! Empty routine
340      WRITE(*,*) 'dyn_spg_flt: You should not have seen this print! error?', kt, kindic
341   END SUBROUTINE dyn_spg_flt
342#endif
343   
344   !!======================================================================
345END MODULE dynspg_flt
Note: See TracBrowser for help on using the repository browser.