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

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/DYN/divcur.F90 @ 2287

Last change on this file since 2287 was 2287, checked in by smasson, 13 years ago

update licence of all NEMO files...

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