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

Last change on this file since 911 was 911, checked in by ctlod, 16 years ago

Implementation of the BDY package, see ticket: #126

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