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

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/DYN/divcur.F90 @ 4456

Last change on this file since 4456 was 4456, checked in by trackstand2, 10 years ago

Add timing to div_cur

  • Property svn:keywords set to Id
File size: 20.0 KB
Line 
1MODULE divcur
2   !!==============================================================================
3   !!                       ***  MODULE  divcur  ***
4   !! Ocean diagnostic variable : horizontal divergence and relative vorticity
5   !!==============================================================================
6   !! History :  OPA  ! 1987-06  (P. Andrich, D. L Hostis)  Original code
7   !!            4.0  ! 1991-11  (G. Madec)
8   !!            6.0  ! 1993-03  (M. Guyon)  symetrical conditions
9   !!            7.0  ! 1996-01  (G. Madec)  s-coordinates
10   !!            8.0  ! 1997-06  (G. Madec)  lateral boundary cond., lbc
11   !!            8.1  ! 1997-08  (J.M. Molines)  Open boundaries
12   !!            8.2  ! 2000-03  (G. Madec)  no slip accurate
13   !!  NEMO      1.0  ! 2002-09  (G. Madec, E. Durand)  Free form, F90
14   !!             -   ! 2005-01  (J. Chanut) Unstructured open boundaries
15   !!             -   ! 2003-08  (G. Madec)  merged of cur and div, free form, F90
16   !!             -   ! 2005-01  (J. Chanut, A. Sellar) unstructured open boundaries
17   !!            3.3  ! 2010-09  (D.Storkey and E.O'Dea) bug fixes for BDY module
18   !!             -   ! 2010-10  (R. Furner, G. Madec) runoff and cla added directly here
19   !!----------------------------------------------------------------------
20
21   !!----------------------------------------------------------------------
22   !!   div_cur    : Compute the horizontal divergence and relative
23   !!                vorticity fields
24   !!----------------------------------------------------------------------
25   USE oce             ! ocean dynamics and tracers
26   USE dom_oce         ! ocean space and time domain
27   USE sbc_oce, ONLY : ln_rnf   ! surface boundary condition: ocean
28   USE sbcrnf          ! river runoff
29   USE obc_oce         ! ocean lateral open boundary condition
30   USE cla             ! cross land advection             (cla_div routine)
31   USE in_out_manager  ! I/O manager
32   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
33   USE lib_mpp         ! MPP library
34   USE timing
35
36   IMPLICIT NONE
37   PRIVATE
38
39   PUBLIC   div_cur    ! routine called by step.F90 and istate.F90
40
41   !! * Control permutation of array indices
42#  include "oce_ftrans.h90"
43#  include "dom_oce_ftrans.h90"
44#  include "obc_oce_ftrans.h90"
45
46   !! * Substitutions
47#  include "domzgr_substitute.h90"
48#  include "vectopt_loop_substitute.h90"
49   !!----------------------------------------------------------------------
50   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
51   !! $Id$
52   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
53   !!----------------------------------------------------------------------
54CONTAINS
55
56#if defined key_noslip_accurate
57   !!----------------------------------------------------------------------
58   !!   'key_noslip_accurate'   2nd order interior + 4th order at the coast
59   !!----------------------------------------------------------------------
60
61   SUBROUTINE div_cur( kt )
62      !!----------------------------------------------------------------------
63      !!                  ***  ROUTINE div_cur  ***
64      !!
65      !! ** Purpose :   compute the horizontal divergence and the relative
66      !!              vorticity at before and now time-step
67      !!
68      !! ** Method  : I.  divergence :
69      !!         - save the divergence computed at the previous time-step
70      !!      (note that the Asselin filter has not been applied on hdivb)
71      !!         - compute the now divergence given by :
72      !!         hdivn = 1/(e1t*e2t*e3t) ( di[e2u*e3u un] + dj[e1v*e3v vn] )
73      !!      correct hdiv with runoff inflow (div_rnf) and cross land flow (div_cla)
74      !!              II. vorticity :
75      !!         - save the curl computed at the previous time-step
76      !!            rotb = rotn
77      !!      (note that the Asselin time filter has not been applied to rotb)
78      !!         - compute the now curl in tensorial formalism:
79      !!            rotn = 1/(e1f*e2f) ( di[e2v vn] - dj[e1u un] )
80      !!         - Coastal boundary condition: 'key_noslip_accurate' defined,
81      !!      the no-slip boundary condition is computed using Schchepetkin
82      !!      and O'Brien (1996) scheme (i.e. 4th order at the coast).
83      !!      For example, along east coast, the one-sided finite difference
84      !!      approximation used for di[v] is:
85      !!         di[e2v vn] =  1/(e1f*e2f) * ( (e2v vn)(i) + (e2v vn)(i-1) + (e2v vn)(i-2) )
86      !!
87      !! ** Action  : - update hdivb, hdivn, the before & now hor. divergence
88      !!              - update rotb , rotn , the before & now rel. vorticity
89      !!----------------------------------------------------------------------
90      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
91      !
92      REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   zwu   ! specific 2D workspace
93      REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   zwv   ! specific 2D workspace
94      !
95      INTEGER ::   ji, jj, jk, jl           ! dummy loop indices
96      INTEGER ::   ii, ij, ijt, iju, ierr   ! local integer
97      REAL(wp) ::  zraur, zdep              ! local scalar
98      !!----------------------------------------------------------------------
99
100      IF( kt == nit000 ) THEN
101         IF(lwp) WRITE(numout,*)
102         IF(lwp) WRITE(numout,*) 'div_cur : horizontal velocity divergence and relative vorticity'
103         IF(lwp) WRITE(numout,*) '~~~~~~~   NOT optimal for auto-tasking case'
104         !
105         ALLOCATE( zwu( jpi, 1:jpj+2) , zwv(-1:jpi+2, jpj) , STAT=ierr )
106         IF( lk_mpp    )   CALL mpp_sum( ierr )
107         IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'div_cur : unable to allocate arrays' )
108      ENDIF
109
110      !                                                ! ===============
111      DO jk = 1, jpkm1                                 ! Horizontal slab
112         !                                             ! ===============
113         !
114         hdivb(:,:,jk) = hdivn(:,:,jk)    ! time swap of div arrays
115         rotb (:,:,jk) = rotn (:,:,jk)    ! time swap of rot arrays
116         !
117         !                                             ! --------
118         ! Horizontal divergence                       !   div
119         !                                             ! --------
120         DO jj = 2, jpjm1
121            DO ji = fs_2, fs_jpim1   ! vector opt.
122               hdivn(ji,jj,jk) =   &
123                  (  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)       &
124                   + 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)  )    &
125                  / ( e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,jk) )
126            END DO
127         END DO
128
129#if defined key_obc
130         IF( Agrif_Root() ) THEN
131            ! open boundaries (div must be zero behind the open boundary)
132            !  mpp remark: The zeroing of hdivn can probably be extended to 1->jpi/jpj for the correct row/column
133            IF( lp_obc_east  )   hdivn(nie0p1:nie1p1,nje0  :nje1  ,jk) = 0.e0      ! east
134            IF( lp_obc_west  )   hdivn(niw0  :niw1  ,njw0  :njw1  ,jk) = 0.e0      ! west
135            IF( lp_obc_north )   hdivn(nin0  :nin1  ,njn0p1:njn1p1,jk) = 0.e0      ! north
136            IF( lp_obc_south )   hdivn(nis0  :nis1  ,njs0  :njs1  ,jk) = 0.e0      ! south
137         ENDIF
138#endif         
139         IF( .NOT. AGRIF_Root() ) THEN
140            IF ((nbondi ==  1).OR.(nbondi == 2)) hdivn(nlci-1 , :     ,jk) = 0.e0      ! east
141            IF ((nbondi == -1).OR.(nbondi == 2)) hdivn(2      , :     ,jk) = 0.e0      ! west
142            IF ((nbondj ==  1).OR.(nbondj == 2)) hdivn(:      ,nlcj-1 ,jk) = 0.e0      ! north
143            IF ((nbondj == -1).OR.(nbondj == 2)) hdivn(:      ,2      ,jk) = 0.e0      ! south
144         ENDIF
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)  ) * 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      END DO                                           !   End of slab
240      !                                                ! ===============
241
242      IF( ln_rnf      )   CALL sbc_rnf_div( hdivn )          ! runoffs (update hdivn field)
243      IF( nn_cla == 1 )   CALL cla_div    ( kt )             ! Cross Land Advection (Update Hor. divergence)
244     
245      ! 4. Lateral boundary conditions on hdivn and rotn
246      ! ---------------------------------=======---======
247      CALL lbc_lnk( hdivn, 'T', 1. )   ;   CALL lbc_lnk( rotn , 'F', 1. )    ! lateral boundary cond. (no sign change)
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] )
268      !!      correct hdiv with runoff inflow (div_rnf) and cross land flow (div_cla)
269      !!              - Relavtive Vorticity :
270      !!      - save the curl computed at the previous time-step (rotb = rotn)
271      !!      (note that the Asselin time filter has not been applied to rotb)
272      !!      - compute the now curl in tensorial formalism:
273      !!            rotn = 1/(e1f*e2f) ( di[e2v vn] - dj[e1u un] )
274      !!      Note: Coastal boundary condition: lateral friction set through
275      !!      the value of fmask along the coast (see dommsk.F90) and shlat
276      !!      (namelist parameter)
277      !!
278      !! ** Action  : - update hdivb, hdivn, the before & now hor. divergence
279      !!              - update rotb , rotn , the before & now rel. vorticity
280      !!----------------------------------------------------------------------
281      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
282      !
283      INTEGER  ::   ji, jj, jk    ! dummy loop indices
284      REAL(wp) ::   zraur, zdep   ! local scalars
285      !!----------------------------------------------------------------------
286
287      CALL timing_start('div_cur')
288
289      IF( kt == nit000 ) THEN
290         IF(lwp) WRITE(numout,*)
291         IF(lwp) WRITE(numout,*) 'div_cur : horizontal velocity divergence and'
292         IF(lwp) WRITE(numout,*) '~~~~~~~   relative vorticity'
293      ENDIF
294
295#if defined key_z_first
296      !                                             ! --------
297      ! Horizontal divergence                       !   div
298      !                                             ! --------
299      hdivb(:,:,1:jpkm1) = hdivn(:,:,1:jpkm1)    ! time swap of div arrays
300      DO jj = 2, jpjm1
301         DO ji = 2, jpim1
302            DO jk = 1, jpkm1
303               hdivn(ji,jj,jk) =   &
304                  (  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)       &
305                   + 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)  )    &
306                  / ( e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,jk) )
307            END DO 
308         END DO 
309      END DO
310
311
312#if defined key_obc
313      IF( Agrif_Root() ) THEN
314         ! open boundaries (div must be zero behind the open boundary)
315         !  mpp remark: The zeroing of hdivn can probably be extended to 1->jpi/jpj for the correct row/column
316         IF( lp_obc_east  )   hdivn(nie0p1:nie1p1,nje0  :nje1  ,1:jpkm1) = 0.e0      ! east
317         IF( lp_obc_west  )   hdivn(niw0  :niw1  ,njw0  :njw1  ,1:jpkm1) = 0.e0      ! west
318         IF( lp_obc_north )   hdivn(nin0  :nin1  ,njn0p1:njn1p1,1:jpkm1) = 0.e0      ! north
319         IF( lp_obc_south )   hdivn(nis0  :nis1  ,njs0  :njs1  ,1:jpkm1) = 0.e0      ! south
320      ENDIF
321#endif         
322      IF( .NOT. AGRIF_Root() ) THEN
323         IF ((nbondi ==  1).OR.(nbondi == 2)) hdivn(nlci-1 , :     ,1:jpkm1) = 0.e0      ! east
324         IF ((nbondi == -1).OR.(nbondi == 2)) hdivn(2      , :     ,1:jpkm1) = 0.e0      ! west
325         IF ((nbondj ==  1).OR.(nbondj == 2)) hdivn(:      ,nlcj-1 ,1:jpkm1) = 0.e0      ! north
326         IF ((nbondj == -1).OR.(nbondj == 2)) hdivn(:      ,2      ,1:jpkm1) = 0.e0      ! south
327      ENDIF
328
329         !                                             ! --------
330         ! relative vorticity                          !   rot
331         !                                             ! --------
332      rotb (:,:,1:jpkm1) = rotn (:,:,1:jpkm1)    ! time swap of rot arrays
333      DO jj = 1, jpjm1
334         DO ji = 1, jpim1
335            DO jk = 1, jpkm1
336               rotn(ji,jj,jk) = (  e2v(ji+1,jj  ) * vn(ji+1,jj  ,jk) - e2v(ji,jj) * vn(ji,jj,jk)    &
337                  &              - e1u(ji  ,jj+1) * un(ji  ,jj+1,jk) + e1u(ji,jj) * un(ji,jj,jk)  ) &
338                  &           * fmask(ji,jj,jk) / ( e1f(ji,jj) * e2f(ji,jj) )
339            END DO
340         END DO
341      END DO
342#else
343
344      !                                                ! ===============
345      DO jk = 1, jpkm1                                 ! Horizontal slab
346         !                                             ! ===============
347         !
348         hdivb(:,:,jk) = hdivn(:,:,jk)    ! time swap of div arrays
349         rotb (:,:,jk) = rotn (:,:,jk)    ! time swap of rot arrays
350         !
351         !                                             ! --------
352         ! Horizontal divergence                       !   div
353         !                                             ! --------
354         DO jj = 2, jpjm1
355            DO ji = fs_2, fs_jpim1   ! vector opt.
356               hdivn(ji,jj,jk) =   &
357                  (  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)       &
358                   + 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)  )    &
359                  / ( e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,jk) )
360            END DO 
361         END DO 
362
363#if defined key_obc
364         IF( Agrif_Root() ) THEN
365            ! open boundaries (div must be zero behind the open boundary)
366            !  mpp remark: The zeroing of hdivn can probably be extended to 1->jpi/jpj for the correct row/column
367            IF( lp_obc_east  )   hdivn(nie0p1:nie1p1,nje0  :nje1  ,jk) = 0.e0      ! east
368            IF( lp_obc_west  )   hdivn(niw0  :niw1  ,njw0  :njw1  ,jk) = 0.e0      ! west
369            IF( lp_obc_north )   hdivn(nin0  :nin1  ,njn0p1:njn1p1,jk) = 0.e0      ! north
370            IF( lp_obc_south )   hdivn(nis0  :nis1  ,njs0  :njs1  ,jk) = 0.e0      ! south
371         ENDIF
372#endif         
373         IF( .NOT. AGRIF_Root() ) THEN
374            IF ((nbondi ==  1).OR.(nbondi == 2)) hdivn(nlci-1 , :     ,jk) = 0.e0      ! east
375            IF ((nbondi == -1).OR.(nbondi == 2)) hdivn(2      , :     ,jk) = 0.e0      ! west
376            IF ((nbondj ==  1).OR.(nbondj == 2)) hdivn(:      ,nlcj-1 ,jk) = 0.e0      ! north
377            IF ((nbondj == -1).OR.(nbondj == 2)) hdivn(:      ,2      ,jk) = 0.e0      ! south
378         ENDIF
379
380         !                                             ! --------
381         ! relative vorticity                          !   rot
382         !                                             ! --------
383         DO jj = 1, jpjm1
384            DO ji = 1, fs_jpim1   ! vector opt.
385               rotn(ji,jj,jk) = (  e2v(ji+1,jj  ) * vn(ji+1,jj  ,jk) - e2v(ji,jj) * vn(ji,jj,jk)    &
386                  &              - e1u(ji  ,jj+1) * un(ji  ,jj+1,jk) + e1u(ji,jj) * un(ji,jj,jk)  ) &
387                  &           * fmask(ji,jj,jk) / ( e1f(ji,jj) * e2f(ji,jj) )
388            END DO
389         END DO
390         !                                             ! ===============
391      END DO                                           !   End of slab
392      !                                                ! ===============
393#if defined ARPDBGSUM
394      WRITE(*,*) 'ARPDBG, div_cur: sum hdivn=',SUM(hdivn),'at step=',kt
395      WRITE(*,*) 'ARPDBG, div_cur: sum un=',SUM(un),'at step=',kt
396      WRITE(*,*) 'ARPDBG, div_cur: sum vn=',SUM(vn),'at step=',kt
397#endif
398
399#endif
400
401      IF( ln_rnf      )   CALL sbc_rnf_div( hdivn )          ! runoffs (update hdivn field)
402      IF( nn_cla == 1 )   CALL cla_div    ( kt )             ! Cross Land Advection (update hdivn field)
403      !
404      CALL lbc_lnk( hdivn, 'T', 1. )   ;   CALL lbc_lnk( rotn , 'F', 1. )     ! lateral boundary cond. (no sign change)
405      !
406      CALL timing_stop('div_cur','section')
407
408   END SUBROUTINE div_cur
409   
410#endif
411   !!======================================================================
412END MODULE divcur
Note: See TracBrowser for help on using the repository browser.