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 branches/dev_005_AWL/NEMO/OPA_SRC/DYN – NEMO

source: branches/dev_005_AWL/NEMO/OPA_SRC/DYN/divcur.F90 @ 1804

Last change on this file since 1804 was 1804, checked in by sga, 14 years ago

merge of trunk changes from r1782 to r1802 into NEMO branch dev_005_AWL

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 17.8 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   !! $Id$
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), DIMENSION(   jpi  ,1:jpj+2) ::   zwu   ! workspace
90      REAL(wp), DIMENSION(-1:jpi+2,  jpj  ) ::   zwv   ! workspace
91      !!----------------------------------------------------------------------
92
93      IF( kt == nit000 ) THEN
94         IF(lwp) WRITE(numout,*)
95         IF(lwp) WRITE(numout,*) 'div_cur : horizontal velocity divergence and relative vorticity'
96         IF(lwp) WRITE(numout,*) '~~~~~~~   NOT optimal for auto-tasking case'
97      ENDIF
98
99      !                                                ! ===============
100      DO jk = 1, jpkm1                                 ! Horizontal slab
101         !                                             ! ===============
102
103         hdivb(:,:,jk) = hdivn(:,:,jk)    ! time swap of div arrays
104         rotb (:,:,jk) = rotn (:,:,jk)    ! time swap of rot arrays
105
106         !                                             ! --------
107         ! Horizontal divergence                       !   div
108         !                                             ! --------
109         DO jj = 2, jpjm1
110            DO ji = fs_2, fs_jpim1   ! vector opt.
111#if defined key_zco
112               hdivn(ji,jj,jk) = (  e2u(ji,jj) * un(ji,jj,jk) - e2u(ji-1,jj  ) * un(ji-1,jj  ,jk)      &
113                  &               + e1v(ji,jj) * vn(ji,jj,jk) - e1v(ji  ,jj-1) * vn(ji  ,jj-1,jk)  )   &
114                  &            / ( e1t(ji,jj) * e2t(ji,jj) )
115#else
116               hdivn(ji,jj,jk) =   &
117                  (  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)       &
118                   + 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)  )    &
119                  / ( e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,jk) )
120#endif
121            END DO
122         END DO
123
124#if defined key_obc
125         IF( Agrif_Root() ) THEN
126            ! open boundaries (div must be zero behind the open boundary)
127            !  mpp remark: The zeroing of hdivn can probably be extended to 1->jpi/jpj for the correct row/column
128            IF( lp_obc_east  )   hdivn(nie0p1:nie1p1,nje0  :nje1  ,jk) = 0.e0      ! east
129            IF( lp_obc_west  )   hdivn(niw0  :niw1  ,njw0  :njw1  ,jk) = 0.e0      ! west
130            IF( lp_obc_north )   hdivn(nin0  :nin1  ,njn0p1:njn1p1,jk) = 0.e0      ! north
131            IF( lp_obc_south )   hdivn(nis0  :nis1  ,njs0  :njs1  ,jk) = 0.e0      ! south
132         ENDIF
133#endif         
134#if defined key_bdy
135         ! unstructured open boundaries (div must be zero behind the open boundary)
136         DO jj = 1, jpj
137            DO ji = 1, jpi
138               hdivn(ji,jj,jk)=hdivn(ji,jj,jk)*bdytmask(ji,jj)
139            END DO
140         END DO
141#endif         
142         IF( .NOT. AGRIF_Root() ) THEN
143            IF ((nbondi ==  1).OR.(nbondi == 2)) hdivn(nlci-1 , :     ,jk) = 0.e0      ! east
144            IF ((nbondi == -1).OR.(nbondi == 2)) hdivn(2      , :     ,jk) = 0.e0      ! west
145            IF ((nbondj ==  1).OR.(nbondj == 2)) hdivn(:      ,nlcj-1 ,jk) = 0.e0      ! north
146            IF ((nbondj == -1).OR.(nbondj == 2)) hdivn(:      ,2      ,jk) = 0.e0      ! south
147         ENDIF
148
149         !                                             ! --------
150         ! relative vorticity                          !   rot
151         !                                             ! --------
152         ! contravariant velocity (extended for lateral b.c.)
153         ! inside the model domain
154         DO jj = 1, jpj
155            DO ji = 1, jpi
156               zwu(ji,jj) = e1u(ji,jj) * un(ji,jj,jk)
157               zwv(ji,jj) = e2v(ji,jj) * vn(ji,jj,jk)
158            END DO 
159         END DO 
160 
161         ! East-West boundary conditions
162         IF( nperio == 1 .OR. nperio == 4 .OR. nperio == 6) THEN
163            zwv(  0  ,:) = zwv(jpi-2,:)
164            zwv( -1  ,:) = zwv(jpi-3,:)
165            zwv(jpi+1,:) = zwv(  3  ,:)
166            zwv(jpi+2,:) = zwv(  4  ,:)
167         ELSE
168            zwv(  0  ,:) = 0.e0
169            zwv( -1  ,:) = 0.e0
170            zwv(jpi+1,:) = 0.e0
171            zwv(jpi+2,:) = 0.e0
172         ENDIF
173
174         ! North-South boundary conditions
175         IF( nperio == 3 .OR. nperio == 4 ) THEN
176            ! north fold ( Grid defined with a T-point pivot) ORCA 2 degre
177            zwu(jpi,jpj+1) = 0.e0
178            zwu(jpi,jpj+2) = 0.e0
179            DO ji = 1, jpi-1
180               iju = jpi - ji + 1
181               zwu(ji,jpj+1) = - zwu(iju,jpj-3)
182               zwu(ji,jpj+2) = - zwu(iju,jpj-4)
183            END DO
184         ELSEIF( nperio == 5 .OR. nperio == 6 ) THEN
185            ! north fold ( Grid defined with a F-point pivot) ORCA 0.5 degre\
186            zwu(jpi,jpj+1) = 0.e0
187            zwu(jpi,jpj+2) = 0.e0
188            DO ji = 1, jpi-1
189               iju = jpi - ji
190               zwu(ji,jpj  ) = - zwu(iju,jpj-1)
191               zwu(ji,jpj+1) = - zwu(iju,jpj-2)
192               zwu(ji,jpj+2) = - zwu(iju,jpj-3)
193            END DO
194            DO ji = -1, jpi+2
195               ijt = jpi - ji + 1
196               zwv(ji,jpj) = - zwv(ijt,jpj-2)
197            END DO
198            DO ji = jpi/2+1, jpi+2
199               ijt = jpi - ji + 1
200               zwv(ji,jpjm1) = - zwv(ijt,jpjm1)
201            END DO
202         ELSE
203            ! closed
204            zwu(:,jpj+1) = 0.e0
205            zwu(:,jpj+2) = 0.e0
206         ENDIF
207
208         ! relative vorticity (vertical component of the velocity curl)
209         DO jj = 1, jpjm1
210            DO ji = 1, fs_jpim1   ! vector opt.
211               rotn(ji,jj,jk) = (  zwv(ji+1,jj  ) - zwv(ji,jj)      &
212                                 - zwu(ji  ,jj+1) + zwu(ji,jj)  )   &
213                              * fmask(ji,jj,jk) / ( e1f(ji,jj)*e2f(ji,jj) )
214            END DO
215         END DO
216
217         ! second order accurate scheme along straight coast
218         DO jl = 1, npcoa(1,jk)
219            ii = nicoa(jl,1,jk)
220            ij = njcoa(jl,1,jk)
221            rotn(ii,ij,jk) = 1. / ( e1f(ii,ij) * e2f(ii,ij) )   &
222                           * ( + 4. * zwv(ii+1,ij) - zwv(ii+2,ij) + 0.2 * zwv(ii+3,ij) )
223         END DO
224         DO jl = 1, npcoa(2,jk)
225            ii = nicoa(jl,2,jk)
226            ij = njcoa(jl,2,jk)
227            rotn(ii,ij,jk) = 1./(e1f(ii,ij)*e2f(ii,ij))   &
228               *(-4.*zwv(ii,ij)+zwv(ii-1,ij)-0.2*zwv(ii-2,ij))
229         END DO
230         DO jl = 1, npcoa(3,jk)
231            ii = nicoa(jl,3,jk)
232            ij = njcoa(jl,3,jk)
233            rotn(ii,ij,jk) = -1. / ( e1f(ii,ij)*e2f(ii,ij) )   &
234               * ( +4. * zwu(ii,ij+1) - zwu(ii,ij+2) + 0.2 * zwu(ii,ij+3) )
235         END DO
236         DO jl = 1, npcoa(4,jk)
237            ii = nicoa(jl,4,jk)
238            ij = njcoa(jl,4,jk)
239            rotn(ii,ij,jk) = -1. / ( e1f(ii,ij)*e2f(ii,ij) )   &
240               * ( -4. * zwu(ii,ij) + zwu(ii,ij-1) - 0.2 * zwu(ii,ij-2) )
241         END DO
242
243         !                                             ! ===============
244      END DO                                           !   End of slab
245      !                                                ! ===============
246     
247      ! 4. Lateral boundary conditions on hdivn and rotn
248      ! ---------------------------------=======---======
249      CALL lbc_lnk( hdivn, 'T', 1. )     ! T-point, no sign change
250      CALL lbc_lnk( rotn , 'F', 1. )     ! F-point, no sign change
251
252   END SUBROUTINE div_cur
253   
254#else
255   !!----------------------------------------------------------------------
256   !!   Default option                           2nd order centered schemes
257   !!----------------------------------------------------------------------
258
259   SUBROUTINE div_cur( kt )
260      !!----------------------------------------------------------------------
261      !!                  ***  ROUTINE div_cur  ***
262      !!                   
263      !! ** Purpose :   compute the horizontal divergence and the relative
264      !!      vorticity at before and now time-step
265      !!
266      !! ** Method  : - Divergence:
267      !!      - save the divergence computed at the previous time-step
268      !!      (note that the Asselin filter has not been applied on hdivb)
269      !!      - compute the now divergence given by :
270      !!         hdivn = 1/(e1t*e2t*e3t) ( di[e2u*e3u un] + dj[e1v*e3v vn] )
271      !!      Note: if lk_zco=T, e3u=e3v=e3t, they are simplified in the
272      !!      above expression
273      !!      - apply lateral boundary conditions on hdivn
274      !!              - Relavtive Vorticity :
275      !!      - save the curl computed at the previous time-step (rotb = rotn)
276      !!      (note that the Asselin time filter has not been applied to rotb)
277      !!      - compute the now curl in tensorial formalism:
278      !!            rotn = 1/(e1f*e2f) ( di[e2v vn] - dj[e1u un] )
279      !!      - apply lateral boundary conditions on rotn through a call to
280      !!      routine lbc_lnk routine.
281      !!      Note: Coastal boundary condition: lateral friction set through
282      !!      the value of fmask along the coast (see dommsk.F90) and shlat
283      !!      (namelist parameter)
284      !!
285      !! ** Action  : - update hdivb, hdivn, the before & now hor. divergence
286      !!              - update rotb , rotn , the before & now rel. vorticity
287      !!
288      !! History :
289      !!   1.0  !  87-06  (P. Andrich, D. L Hostis)  Original code
290      !!   4.0  !  91-11  (G. Madec)
291      !!   6.0  !  93-03  (M. Guyon)  symetrical conditions
292      !!   7.0  !  96-01  (G. Madec)  s-coordinates
293      !!   8.0  !  97-06  (G. Madec)  lateral boundary cond., lbc
294      !!   8.1  !  97-08  (J.M. Molines)  Open boundaries
295      !!   9.0  !  02-09  (G. Madec, E. Durand)  Free form, F90
296      !!        !  05-01  (J. Chanut) Unstructured open boundaries
297      !!----------------------------------------------------------------------
298      !! * Arguments
299      INTEGER, INTENT( in ) ::   kt     ! ocean time-step index
300     
301      !! * Local declarations
302      INTEGER  ::   ji, jj, jk          ! dummy loop indices
303      !!----------------------------------------------------------------------
304
305      IF( kt == nit000 ) THEN
306         IF(lwp) WRITE(numout,*)
307         IF(lwp) WRITE(numout,*) 'div_cur : horizontal velocity divergence and'
308         IF(lwp) WRITE(numout,*) '~~~~~~~   relative vorticity'
309      ENDIF
310
311      !                                                ! ===============
312      DO jk = 1, jpkm1                                 ! Horizontal slab
313         !                                             ! ===============
314
315         hdivb(:,:,jk) = hdivn(:,:,jk)    ! time swap of div arrays
316         rotb (:,:,jk) = rotn (:,:,jk)    ! time swap of rot arrays
317
318         !                                             ! --------
319         ! Horizontal divergence                       !   div
320         !                                             ! --------
321         DO jj = 2, jpjm1
322            DO ji = fs_2, fs_jpim1   ! vector opt.
323#if defined key_zco
324               hdivn(ji,jj,jk) = (  e2u(ji,jj) * un(ji,jj,jk) - e2u(ji-1,jj  ) * un(ji-1,jj  ,jk)      &
325                  &               + e1v(ji,jj) * vn(ji,jj,jk) - e1v(ji  ,jj-1) * vn(ji  ,jj-1,jk)  )   & 
326                  / ( e1t(ji,jj) * e2t(ji,jj) )
327#else
328               hdivn(ji,jj,jk) =   &
329                  (  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)       &
330                   + 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)  )    &
331                  / ( e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,jk) )
332#endif
333            END DO 
334         END DO 
335
336#if defined key_obc
337         IF( Agrif_Root() ) THEN
338            ! open boundaries (div must be zero behind the open boundary)
339            !  mpp remark: The zeroing of hdivn can probably be extended to 1->jpi/jpj for the correct row/column
340            IF( lp_obc_east  )   hdivn(nie0p1:nie1p1,nje0  :nje1  ,jk) = 0.e0      ! east
341            IF( lp_obc_west  )   hdivn(niw0  :niw1  ,njw0  :njw1  ,jk) = 0.e0      ! west
342            IF( lp_obc_north )   hdivn(nin0  :nin1  ,njn0p1:njn1p1,jk) = 0.e0      ! north
343            IF( lp_obc_south )   hdivn(nis0  :nis1  ,njs0  :njs1  ,jk) = 0.e0      ! south
344         ENDIF
345#endif         
346#if defined key_bdy
347         ! unstructured open boundaries (div must be zero behind the open boundary)
348         DO jj = 1, jpj
349           DO ji = 1, jpi
350             hdivn(ji,jj,jk)=hdivn(ji,jj,jk)*bdytmask(ji,jj)
351           END DO
352         END DO
353#endif       
354         IF( .NOT. AGRIF_Root() ) THEN
355            IF ((nbondi ==  1).OR.(nbondi == 2)) hdivn(nlci-1 , :     ,jk) = 0.e0      ! east
356            IF ((nbondi == -1).OR.(nbondi == 2)) hdivn(2      , :     ,jk) = 0.e0      ! west
357            IF ((nbondj ==  1).OR.(nbondj == 2)) hdivn(:      ,nlcj-1 ,jk) = 0.e0      ! north
358            IF ((nbondj == -1).OR.(nbondj == 2)) hdivn(:      ,2      ,jk) = 0.e0      ! south
359         ENDIF
360
361         !                                             ! --------
362         ! relative vorticity                          !   rot
363         !                                             ! --------
364         DO jj = 1, jpjm1
365            DO ji = 1, fs_jpim1   ! vector opt.
366               rotn(ji,jj,jk) = (  e2v(ji+1,jj  ) * vn(ji+1,jj  ,jk) - e2v(ji,jj) * vn(ji,jj,jk)    &
367                  &              - e1u(ji  ,jj+1) * un(ji  ,jj+1,jk) + e1u(ji,jj) * un(ji,jj,jk)  ) &
368                  &           * fmask(ji,jj,jk) / ( e1f(ji,jj) * e2f(ji,jj) )
369            END DO
370         END DO
371         !                                             ! ===============
372      END DO                                           !   End of slab
373      !                                                ! ===============
374     
375      ! 4. Lateral boundary conditions on hdivn and rotn
376      ! ---------------------------------=======---======
377      CALL lbc_lnk( hdivn, 'T', 1. )       ! T-point, no sign change
378      CALL lbc_lnk( rotn , 'F', 1. )       ! F-point, no sign change
379
380   END SUBROUTINE div_cur
381   
382#endif
383   !!======================================================================
384END MODULE divcur
Note: See TracBrowser for help on using the repository browser.