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

source: branches/devukmo2010/NEMO/OPA_SRC/DYN/divcur.F90 @ 2128

Last change on this file since 2128 was 2128, checked in by rfurner, 14 years ago

merged branches OBS, ASM, Rivers, BDY & mixed_dynldf ready for vn3.3 merge

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