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

source: trunk/NEMO/OPA_SRC/DYN/divcur.F90 @ 780

Last change on this file since 780 was 780, checked in by rblod, 16 years ago

Correct a critical bug in divergence computation for AGRIF case, see ticket #40

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 17.4 KB
RevLine 
[3]1MODULE divcur
2   !!==============================================================================
3   !!                       ***  MODULE  divcur  ***
4   !! Ocean diagnostic variable : horizontal divergence and relative vorticity
5   !!==============================================================================
6
7   !!----------------------------------------------------------------------
8   !!   div_cur    : Compute the horizontal divergence and relative
9   !!                vorticity fields
10   !!----------------------------------------------------------------------
11   !! * Modules used
12   USE oce             ! ocean dynamics and tracers
13   USE dom_oce         ! ocean space and time domain
14   USE in_out_manager  ! I/O manager
15   USE obc_oce         ! ocean lateral open boundary condition
16   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
17
18   IMPLICIT NONE
19   PRIVATE
20
21   !! * Accessibility
22   PUBLIC div_cur    ! routine called by step.F90 and istate.F90
23
24   !! * Substitutions
25#  include "domzgr_substitute.h90"
26#  include "vectopt_loop_substitute.h90"
27   !!----------------------------------------------------------------------
[247]28   !!   OPA 9.0 , LOCEAN-IPSL (2005)
[780]29   !! $Header: /home/opalod/NEMOCVSROOT/NEMO/OPA_SRC/DYN/divcur.F90,v 1.7 2006/05/10 16:53:51 opalod Exp $
[247]30   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
[3]31   !!----------------------------------------------------------------------
32
33CONTAINS
34
35#if defined key_noslip_accurate
36   !!----------------------------------------------------------------------
37   !!   'key_noslip_accurate'                     2nd order centered scheme
38   !!                                                4th order at the coast
39   !!----------------------------------------------------------------------
40
41   SUBROUTINE div_cur( kt )
42      !!----------------------------------------------------------------------
43      !!                  ***  ROUTINE div_cur  ***
44      !!
45      !! ** Purpose :   compute the horizontal divergence and the relative
46      !!      vorticity at before and now time-step
47      !!
48      !! ** Method  :
49      !!      I.  divergence :
50      !!         - save the divergence computed at the previous time-step
51      !!      (note that the Asselin filter has not been applied on hdivb)
52      !!         - compute the now divergence given by :
53      !!         hdivn = 1/(e1t*e2t*e3t) ( di[e2u*e3u un] + dj[e1v*e3v vn] )
[455]54      !!      Note: if lk_zco=T, e3u=e3v=e3t, they are simplified in the
55      !!      above expression
[3]56      !!         - apply lateral boundary conditions on hdivn
57      !!      II. vorticity :
58      !!         - save the curl computed at the previous time-step
59      !!            rotb = rotn
60      !!      (note that the Asselin time filter has not been applied to rotb)
61      !!         - compute the now curl in tensorial formalism:
62      !!            rotn = 1/(e1f*e2f) ( di[e2v vn] - dj[e1u un] )
63      !!         - apply lateral boundary conditions on rotn through a call
64      !!      of lbc_lnk routine.
65      !!         - Coastal boundary condition: 'key_noslip_accurate' defined,
66      !!      the no-slip boundary condition is computed using Schchepetkin
67      !!      and O'Brien (1996) scheme (i.e. 4th order at the coast).
68      !!      For example, along east coast, the one-sided finite difference
69      !!      approximation used for di[v] is:
70      !!         di[e2v vn] =  1/(e1f*e2f)
71      !!                    * ( (e2v vn)(i) + (e2v vn)(i-1) + (e2v vn)(i-2) )
72      !!
73      !! ** Action  : - update hdivb, hdivn, the before & now hor. divergence
74      !!              - update rotb , rotn , the before & now rel. vorticity
75      !!
76      !! History :
77      !!   8.2  !  00-03  (G. Madec)  no slip accurate
78      !!   9.0  !  03-08  (G. Madec)  merged of cur and div, free form, F90
79      !!----------------------------------------------------------------------
80      !! * Arguments
81      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
82     
83      !! * Local declarations
84      INTEGER ::   ji, jj, jk     ! dummy loop indices
85      INTEGER ::   ii, ij, jl     ! temporary integer
86      INTEGER ::   ijt, iju       ! temporary integer
87      REAL(wp) ::   zdiv, zdju
88      REAL(wp), DIMENSION(   jpi  ,1:jpj+2) ::   zwu   ! workspace
89      REAL(wp), DIMENSION(-1:jpi+2,  jpj  ) ::   zwv   ! workspace
90      !!----------------------------------------------------------------------
91
92      IF( kt == nit000 ) THEN
93         IF(lwp) WRITE(numout,*)
94         IF(lwp) WRITE(numout,*) 'div_cur : horizontal velocity divergence and relative vorticity'
95         IF(lwp) WRITE(numout,*) '~~~~~~~   NOT optimal for auto-tasking case'
96      ENDIF
97
98      !                                                ! ===============
99      DO jk = 1, jpkm1                                 ! Horizontal slab
100         !                                             ! ===============
101
102         hdivb(:,:,jk) = hdivn(:,:,jk)    ! time swap of div arrays
103         rotb (:,:,jk) = rotn (:,:,jk)    ! time swap of rot arrays
104
105         !                                             ! --------
106         ! Horizontal divergence                       !   div
107         !                                             ! --------
108         DO jj = 2, jpjm1
109            DO ji = fs_2, fs_jpim1   ! vector opt.
[455]110#if defined key_zco
111               hdivn(ji,jj,jk) = (  e2u(ji,jj) * un(ji,jj,jk) - e2u(ji-1,jj  ) * un(ji-1,jj  ,jk)      &
112                  &               + e1v(ji,jj) * vn(ji,jj,jk) - e1v(ji  ,jj-1) * vn(ji  ,jj-1,jk)  )   &
113                  &            / ( e1t(ji,jj) * e2t(ji,jj) )
114#else
[3]115               hdivn(ji,jj,jk) =   &
[455]116                  (  e2u(ji,jj)*fse3u(ji,jj,jk) * un(ji,jj,jk) - e2u(ji-1,jj  )*fse3u(ji-1,jj  ,jk) * un(ji-1,jj  ,jk)       &
117                   + e1v(ji,jj)*fse3v(ji,jj,jk) * vn(ji,jj,jk) - e1v(ji  ,jj-1)*fse3v(ji  ,jj-1,jk) * vn(ji  ,jj-1,jk)  )    &
[3]118                  / ( e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,jk) )
119#endif
120            END DO
121         END DO
122
123#if defined key_obc
[780]124#if defined key_agrif
125         IF (Agrif_Root() ) THEN
126#endif
[3]127         ! open boundaries (div must be zero behind the open boundary)
128         !  mpp remark: The zeroing of hdivn can probably be extended to 1->jpi/jpj for the correct row/column
[78]129         IF( lp_obc_east  )   hdivn(nie0p1:nie1p1,nje0  :nje1  ,jk) = 0.e0      ! east
130         IF( lp_obc_west  )   hdivn(niw0  :niw1  ,njw0  :njw1  ,jk) = 0.e0      ! west
131         IF( lp_obc_north )   hdivn(nin0  :nin1  ,njn0p1:njn1p1,jk) = 0.e0      ! north
132         IF( lp_obc_south )   hdivn(nis0  :nis1  ,njs0  :njs1  ,jk) = 0.e0      ! south
[780]133#if defined key_agrif
134         ENDIF
135#endif
[3]136#endif         
[780]137#if defined key_agrif
138         if ( .NOT. AGRIF_Root() ) then
139           IF ((nbondi ==  1).OR.(nbondi == 2)) hdivn(nlci-1 , :     ,jk) = 0.e0      ! east
140           IF ((nbondi == -1).OR.(nbondi == 2)) hdivn(2      , :     ,jk) = 0.e0      ! west
141           IF ((nbondj ==  1).OR.(nbondj == 2)) hdivn(:      ,nlcj-1 ,jk) = 0.e0      ! north
142           IF ((nbondj == -1).OR.(nbondj == 2)) hdivn(:      ,2      ,jk) = 0.e0      ! south
143         endif
144#endif   
[3]145
146         !                                             ! --------
147         ! relative vorticity                          !   rot
148         !                                             ! --------
149         ! contravariant velocity (extended for lateral b.c.)
150         ! inside the model domain
151         DO jj = 1, jpj
152            DO ji = 1, jpi
153               zwu(ji,jj) = e1u(ji,jj) * un(ji,jj,jk)
154               zwv(ji,jj) = e2v(ji,jj) * vn(ji,jj,jk)
155            END DO 
156         END DO 
157 
158         ! East-West boundary conditions
159         IF( nperio == 1 .OR. nperio == 4 .OR. nperio == 6) THEN
160            zwv(  0  ,:) = zwv(jpi-2,:)
161            zwv( -1  ,:) = zwv(jpi-3,:)
162            zwv(jpi+1,:) = zwv(  3  ,:)
163            zwv(jpi+2,:) = zwv(  4  ,:)
164         ELSE
165            zwv(  0  ,:) = 0.e0
166            zwv( -1  ,:) = 0.e0
167            zwv(jpi+1,:) = 0.e0
168            zwv(jpi+2,:) = 0.e0
169         ENDIF
170
171         ! North-South boundary conditions
172         IF( nperio == 3 .OR. nperio == 4 ) THEN
173            ! north fold ( Grid defined with a T-point pivot) ORCA 2 degre
174            zwu(jpi,jpj+1) = 0.e0
175            zwu(jpi,jpj+2) = 0.e0
176            DO ji = 1, jpi-1
177               iju = jpi - ji + 1
178               zwu(ji,jpj+1) = - zwu(iju,jpj-3)
179               zwu(ji,jpj+2) = - zwu(iju,jpj-4)
180            END DO
181         ELSEIF( nperio == 5 .OR. nperio == 6 ) THEN
182            ! north fold ( Grid defined with a F-point pivot) ORCA 0.5 degre\
183            zwu(jpi,jpj+1) = 0.e0
184            zwu(jpi,jpj+2) = 0.e0
185            DO ji = 1, jpi-1
186               iju = jpi - ji
187               zwu(ji,jpj  ) = - zwu(iju,jpj-1)
188               zwu(ji,jpj+1) = - zwu(iju,jpj-2)
189               zwu(ji,jpj+2) = - zwu(iju,jpj-3)
190            END DO
191            DO ji = -1, jpi+2
192               ijt = jpi - ji + 1
193               zwv(ji,jpj) = - zwv(ijt,jpj-2)
194            END DO
195            DO ji = jpi/2+1, jpi+2
196               ijt = jpi - ji + 1
197               zwv(ji,jpjm1) = - zwv(ijt,jpjm1)
198            END DO
199         ELSE
200            ! closed
201            zwu(:,jpj+1) = 0.e0
202            zwu(:,jpj+2) = 0.e0
203         ENDIF
204
205         ! relative vorticity (vertical component of the velocity curl)
206         DO jj = 1, jpjm1
207            DO ji = 1, fs_jpim1   ! vector opt.
208               rotn(ji,jj,jk) = (  zwv(ji+1,jj  ) - zwv(ji,jj)      &
209                                 - zwu(ji  ,jj+1) + zwu(ji,jj)  )   &
210                              * fmask(ji,jj,jk) / ( e1f(ji,jj)*e2f(ji,jj) )
211            END DO
212         END DO
213
214         ! second order accurate scheme along straight coast
215         DO jl = 1, npcoa(1,jk)
216            ii = nicoa(jl,1,jk)
217            ij = njcoa(jl,1,jk)
218            rotn(ii,ij,jk) = 1. / ( e1f(ii,ij) * e2f(ii,ij) )   &
219                           * ( + 4. * zwv(ii+1,ij) - zwv(ii+2,ij) + 0.2 * zwv(ii+3,ij) )
220         END DO
221         DO jl = 1, npcoa(2,jk)
222            ii = nicoa(jl,2,jk)
223            ij = njcoa(jl,2,jk)
224            rotn(ii,ij,jk) = 1./(e1f(ii,ij)*e2f(ii,ij))   &
225               *(-4.*zwv(ii,ij)+zwv(ii-1,ij)-0.2*zwv(ii-2,ij))
226         END DO
227         DO jl = 1, npcoa(3,jk)
228            ii = nicoa(jl,3,jk)
229            ij = njcoa(jl,3,jk)
230            rotn(ii,ij,jk) = -1. / ( e1f(ii,ij)*e2f(ii,ij) )   &
231               * ( +4. * zwu(ii,ij+1) - zwu(ii,ij+2) + 0.2 * zwu(ii,ij+3) )
232         END DO
233         DO jl = 1, npcoa(4,jk)
234            ii = nicoa(jl,4,jk)
235            ij = njcoa(jl,4,jk)
236            rotn(ii,ij,jk) = -1. / ( e1f(ii,ij)*e2f(ii,ij) )   &
237               * ( -4. * zwu(ii,ij) + zwu(ii,ij-1) - 0.2 * zwu(ii,ij-2) )
238         END DO
239
240         !                                             ! ===============
241      END DO                                           !   End of slab
242      !                                                ! ===============
243     
244      ! 4. Lateral boundary conditions on hdivn and rotn
245      ! ---------------------------------=======---======
[234]246      CALL lbc_lnk( hdivn, 'T', 1. )     ! T-point, no sign change
247      CALL lbc_lnk( rotn , 'F', 1. )     ! F-point, no sign change
[3]248
249   END SUBROUTINE div_cur
250   
251#else
252   !!----------------------------------------------------------------------
253   !!   Default option                           2nd order centered schemes
254   !!----------------------------------------------------------------------
255
256   SUBROUTINE div_cur( kt )
257      !!----------------------------------------------------------------------
258      !!                  ***  ROUTINE div_cur  ***
259      !!                   
260      !! ** Purpose :   compute the horizontal divergence and the relative
261      !!      vorticity at before and now time-step
262      !!
263      !! ** Method  : - Divergence:
264      !!      - save the divergence computed at the previous time-step
265      !!      (note that the Asselin filter has not been applied on hdivb)
266      !!      - compute the now divergence given by :
267      !!         hdivn = 1/(e1t*e2t*e3t) ( di[e2u*e3u un] + dj[e1v*e3v vn] )
[455]268      !!      Note: if lk_zco=T, e3u=e3v=e3t, they are simplified in the
269      !!      above expression
[3]270      !!      - apply lateral boundary conditions on hdivn
271      !!              - Relavtive Vorticity :
272      !!      - save the curl computed at the previous time-step (rotb = rotn)
273      !!      (note that the Asselin time filter has not been applied to rotb)
274      !!      - compute the now curl in tensorial formalism:
275      !!            rotn = 1/(e1f*e2f) ( di[e2v vn] - dj[e1u un] )
276      !!      - apply lateral boundary conditions on rotn through a call to
277      !!      routine lbc_lnk routine.
278      !!      Note: Coastal boundary condition: lateral friction set through
279      !!      the value of fmask along the coast (see dommsk.F90) and shlat
280      !!      (namelist parameter)
281      !!
282      !! ** Action  : - update hdivb, hdivn, the before & now hor. divergence
283      !!              - update rotb , rotn , the before & now rel. vorticity
284      !!
285      !! History :
286      !!   1.0  !  87-06  (P. Andrich, D. L Hostis)  Original code
287      !!   4.0  !  91-11  (G. Madec)
288      !!   6.0  !  93-03  (M. Guyon)  symetrical conditions
289      !!   7.0  !  96-01  (G. Madec)  s-coordinates
290      !!   8.0  !  97-06  (G. Madec)  lateral boundary cond., lbc
291      !!   8.1  !  97-08  (J.M. Molines)  Open boundaries
292      !!   9.0  !  02-09  (G. Madec, E. Durand)  Free form, F90
293      !!----------------------------------------------------------------------
294      !! * Arguments
295      INTEGER, INTENT( in ) ::   kt     ! ocean time-step index
296     
297      !! * Local declarations
298      INTEGER  ::   ji, jj, jk          ! dummy loop indices
299      !!----------------------------------------------------------------------
300
301      IF( kt == nit000 ) THEN
302         IF(lwp) WRITE(numout,*)
303         IF(lwp) WRITE(numout,*) 'div_cur : horizontal velocity divergence and'
304         IF(lwp) WRITE(numout,*) '~~~~~~~   relative vorticity'
305      ENDIF
306
307      !                                                ! ===============
308      DO jk = 1, jpkm1                                 ! Horizontal slab
309         !                                             ! ===============
310
311         hdivb(:,:,jk) = hdivn(:,:,jk)    ! time swap of div arrays
312         rotb (:,:,jk) = rotn (:,:,jk)    ! time swap of rot arrays
313
314         !                                             ! --------
315         ! Horizontal divergence                       !   div
316         !                                             ! --------
317         DO jj = 2, jpjm1
318            DO ji = fs_2, fs_jpim1   ! vector opt.
[455]319#if defined key_zco
[3]320               hdivn(ji,jj,jk) = (  e2u(ji,jj) * un(ji,jj,jk) - e2u(ji-1,jj  ) * un(ji-1,jj  ,jk)      &
321                  &               + e1v(ji,jj) * vn(ji,jj,jk) - e1v(ji  ,jj-1) * vn(ji  ,jj-1,jk)  )   & 
322                  / ( e1t(ji,jj) * e2t(ji,jj) )
[455]323#else
324               hdivn(ji,jj,jk) =   &
325                  (  e2u(ji,jj)*fse3u(ji,jj,jk) * un(ji,jj,jk) - e2u(ji-1,jj  )*fse3u(ji-1,jj  ,jk) * un(ji-1,jj  ,jk)       &
326                   + e1v(ji,jj)*fse3v(ji,jj,jk) * vn(ji,jj,jk) - e1v(ji  ,jj-1)*fse3v(ji  ,jj-1,jk) * vn(ji  ,jj-1,jk)  )    &
327                  / ( e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,jk) )
[3]328#endif
329            END DO 
330         END DO 
331
332#if defined key_obc
[780]333#if defined key_agrif
334         IF ( Agrif_Root() ) THEN
335#endif
[3]336         ! open boundaries (div must be zero behind the open boundary)
337         !  mpp remark: The zeroing of hdivn can probably be extended to 1->jpi/jpj for the correct row/column
[78]338         IF( lp_obc_east  )   hdivn(nie0p1:nie1p1,nje0  :nje1  ,jk) = 0.e0      ! east
339         IF( lp_obc_west  )   hdivn(niw0  :niw1  ,njw0  :njw1  ,jk) = 0.e0      ! west
340         IF( lp_obc_north )   hdivn(nin0  :nin1  ,njn0p1:njn1p1,jk) = 0.e0      ! north
341         IF( lp_obc_south )   hdivn(nis0  :nis1  ,njs0  :njs1  ,jk) = 0.e0      ! south
[780]342#if defined key_agrif
343         ENDIF
344#endif
[3]345#endif         
[780]346#if defined key_agrif
347         if ( .NOT. AGRIF_Root() ) then
348            IF ((nbondi ==  1).OR.(nbondi == 2)) hdivn(nlci-1 , :     ,jk) = 0.e0      ! east
349            IF ((nbondi == -1).OR.(nbondi == 2)) hdivn(2      , :     ,jk) = 0.e0      ! west
350            IF ((nbondj ==  1).OR.(nbondj == 2)) hdivn(:      ,nlcj-1 ,jk) = 0.e0      ! north
351            IF ((nbondj == -1).OR.(nbondj == 2)) hdivn(:      ,2      ,jk) = 0.e0      ! south
352         endif
353#endif   
354
[3]355         !                                             ! --------
356         ! relative vorticity                          !   rot
357         !                                             ! --------
358         DO jj = 1, jpjm1
359            DO ji = 1, fs_jpim1   ! vector opt.
360               rotn(ji,jj,jk) = (  e2v(ji+1,jj  ) * vn(ji+1,jj  ,jk) - e2v(ji,jj) * vn(ji,jj,jk)    &
361                  &              - e1u(ji  ,jj+1) * un(ji  ,jj+1,jk) + e1u(ji,jj) * un(ji,jj,jk)  ) &
362                  &           * fmask(ji,jj,jk) / ( e1f(ji,jj) * e2f(ji,jj) )
363            END DO
364         END DO
365         !                                             ! ===============
366      END DO                                           !   End of slab
367      !                                                ! ===============
368     
369      ! 4. Lateral boundary conditions on hdivn and rotn
370      ! ---------------------------------=======---======
[234]371      CALL lbc_lnk( hdivn, 'T', 1. )       ! T-point, no sign change
372      CALL lbc_lnk( rotn , 'F', 1. )       ! F-point, no sign change
[3]373
374   END SUBROUTINE div_cur
375   
376#endif
377   !!======================================================================
378END MODULE divcur
Note: See TracBrowser for help on using the repository browser.