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.
agrif_user.F90 in branches/2012/dev_r3387_LOCEAN6_AGRIF_LIM/NEMOGCM/NEMO/NST_SRC – NEMO

source: branches/2012/dev_r3387_LOCEAN6_AGRIF_LIM/NEMOGCM/NEMO/NST_SRC/agrif_user.F90 @ 3390

Last change on this file since 3390 was 3390, checked in by rblod, 12 years ago

NEMO branch dev_r3387_LOCEAN6_AGRIF_LIM : preliminary commit to allow faster compilation with AGRIF

  • Property svn:keywords set to Id
File size: 19.3 KB
Line 
1#if defined key_agrif
2   !!----------------------------------------------------------------------
3   !! NEMO/NST 3.3 , NEMO Consortium (2010)
4   !! $Id$
5   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
6   !!----------------------------------------------------------------------
7   SUBROUTINE agrif_user
8   END SUBROUTINE
9
10   SUBROUTINE agrif_before_regridding
11   END SUBROUTINE
12
13   SUBROUTINE Agrif_InitWorkspace
14      !!----------------------------------------------------------------------
15      !!                 *** ROUTINE Agrif_InitWorkspace ***
16      !!----------------------------------------------------------------------
17      USE par_oce
18      USE dom_oce
19      USE Agrif_Util
20      USE nemogcm
21      !
22      IMPLICIT NONE
23      !!----------------------------------------------------------------------
24      !
25      IF( .NOT. Agrif_Root() ) THEN
26         jpni = Agrif_Parent(jpni)
27         jpnj = Agrif_Parent(jpnj)
28         jpnij = Agrif_Parent(jpnij)
29         jpiglo  = nbcellsx + 2 + 2*nbghostcells
30         jpjglo  = nbcellsy + 2 + 2*nbghostcells
31         jpi     = ( jpiglo-2*jpreci + (jpni-1+0) ) / jpni + 2*jpreci
32         jpj     = ( jpjglo-2*jprecj + (jpnj-1+0) ) / jpnj + 2*jprecj
33         jpk     = jpkdta
34         jpim1   = jpi-1
35         jpjm1   = jpj-1
36         jpkm1   = jpk-1                                       
37         jpij    = jpi*jpj
38         jpidta  = jpiglo
39         jpjdta  = jpjglo
40         jpizoom = 1
41         jpjzoom = 1
42         nperio  = 0
43         jperio  = 0
44      ENDIF
45      !
46   END SUBROUTINE Agrif_InitWorkspace
47
48
49   SUBROUTINE Agrif_InitValues
50      !!----------------------------------------------------------------------
51      !!                 *** ROUTINE Agrif_InitValues ***
52      !!
53      !! ** Purpose :: Declaration of variables to be interpolated
54      !!----------------------------------------------------------------------
55      USE Agrif_Util
56      USE oce 
57      USE dom_oce
58      USE nemogcm
59      USE tradmp
60      USE obc_par
61      USE bdy_par
62
63      IMPLICIT NONE
64      !!----------------------------------------------------------------------
65
66      ! 0. Initializations
67      !-------------------
68#if defined key_orca_r025 || defined key_orca_r05 || defined key_orca_r2 || defined key_orca_r4
69      jp_cfg = -1    ! set special value for jp_cfg on fine grids
70      cp_cfg = "default"
71#endif
72
73      ! Specific fine grid Initializations
74      ! no tracer damping on fine grids
75      ln_tradmp = .FALSE.
76      ! no open boundary on fine grids
77      lk_obc = .FALSE.
78      lk_bdy = .FALSE.
79
80      CALL nemo_init  ! Initializations of each fine grid
81      CALL agrif_nemo_init
82# if ! defined key_offline
83      CALL Agrif_InitValues_cont
84# endif       
85# if defined key_top
86      CALL Agrif_InitValues_cont_top
87# endif     
88   END SUBROUTINE Agrif_initvalues
89
90# if ! defined key_offline
91
92   SUBROUTINE Agrif_InitValues_cont
93      !!----------------------------------------------------------------------
94      !!                 *** ROUTINE Agrif_InitValues_cont ***
95      !!
96      !! ** Purpose ::   Declaration of variables to be interpolated
97      !!----------------------------------------------------------------------
98      USE Agrif_Util
99      USE oce 
100      USE dom_oce
101      USE nemogcm
102      USE sol_oce
103      USE in_out_manager
104      USE agrif_opa_update
105      USE agrif_opa_interp
106      USE agrif_opa_sponge
107      !
108      IMPLICIT NONE
109      !
110      REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE :: tabtstemp
111      REAL(wp), DIMENSION(:,:,:  ), ALLOCATABLE :: tabuvtemp
112      LOGICAL :: check_namelist
113      !!----------------------------------------------------------------------
114
115      ALLOCATE( tabtstemp(jpi, jpj, jpk, jpts) )
116      ALLOCATE( tabuvtemp(jpi, jpj, jpk)       )
117
118
119      ! 1. Declaration of the type of variable which have to be interpolated
120      !---------------------------------------------------------------------
121      CALL agrif_declare_var
122
123      ! 2. First interpolations of potentially non zero fields
124      !-------------------------------------------------------
125      Agrif_SpecialValue=0.
126      Agrif_UseSpecialValue = .TRUE.
127      Call Agrif_Bc_variable(tabtstemp,tsn_id,calledweight=1.,procname=interptsn)
128      Call Agrif_Bc_variable(tabtstemp,tsa_id,calledweight=1.,procname=interptsn)
129
130      Call Agrif_Bc_variable(tabuvtemp,un_id,calledweight=1.,procname=interpu)
131      Call Agrif_Bc_variable(tabuvtemp,vn_id,calledweight=1.,procname=interpv)
132      Call Agrif_Bc_variable(tabuvtemp,ua_id,calledweight=1.,procname=interpun)
133      Call Agrif_Bc_variable(tabuvtemp,va_id,calledweight=1.,procname=interpvn)
134      Agrif_UseSpecialValue = .FALSE.
135
136      ! 3. Some controls
137      !-----------------
138      check_namelist = .true.
139           
140      IF( check_namelist ) THEN
141     
142         ! Check time steps           
143         IF( NINT(Agrif_Rhot()) * nint(rdt) /= Agrif_Parent(rdt) ) THEN
144            WRITE(*,*) 'incompatible time step between grids'
145            WRITE(*,*) 'parent grid value : ',Agrif_Parent(rdt)
146            WRITE(*,*) 'child  grid value : ',nint(rdt)
147            WRITE(*,*) 'value on parent grid should be : ',rdt*Agrif_Rhot()
148            STOP
149         ENDIF
150         
151         ! Check run length
152         IF( Agrif_IRhot() * (Agrif_Parent(nitend)- &
153            Agrif_Parent(nit000)+1) .ne. (nitend-nit000+1) ) THEN
154            WRITE(*,*) 'incompatible run length between grids'
155            WRITE(*,*) 'parent grid value : ',(Agrif_Parent(nitend)- &
156               Agrif_Parent(nit000)+1),' time step'
157            WRITE(*,*) 'child  grid value : ', &
158               (nitend-nit000+1),' time step'
159            WRITE(*,*) 'value on child grid should be : ', &
160               Agrif_IRhot() * (Agrif_Parent(nitend)- &
161               Agrif_Parent(nit000)+1)
162            STOP
163         ENDIF
164         
165         ! Check coordinates
166         IF( ln_zps ) THEN
167            ! check parameters for partial steps
168            IF( Agrif_Parent(e3zps_min) .ne. e3zps_min ) THEN
169               WRITE(*,*) 'incompatible e3zps_min between grids'
170               WRITE(*,*) 'parent grid :',Agrif_Parent(e3zps_min)
171               WRITE(*,*) 'child grid  :',e3zps_min
172               WRITE(*,*) 'those values should be identical'
173               STOP
174            ENDIF         
175            IF( Agrif_Parent(e3zps_rat) /= e3zps_rat ) THEN
176               WRITE(*,*) 'incompatible e3zps_rat between grids'
177               WRITE(*,*) 'parent grid :',Agrif_Parent(e3zps_rat)
178               WRITE(*,*) 'child grid  :',e3zps_rat
179               WRITE(*,*) 'those values should be identical'                 
180               STOP
181            ENDIF
182         ENDIF
183      ENDIF
184       
185      CALL Agrif_Update_tra(0)
186      CALL Agrif_Update_dyn(0)
187
188      nbcline = 0
189      !
190      DEALLOCATE(tabtstemp)
191      DEALLOCATE(tabuvtemp)
192      !
193   END SUBROUTINE Agrif_InitValues_cont
194
195
196   SUBROUTINE agrif_declare_var
197      !!----------------------------------------------------------------------
198      !!                 *** ROUTINE agrif_declarE_var ***
199      !!
200      !! ** Purpose :: Declaration of variables to be interpolated
201      !!----------------------------------------------------------------------
202      USE agrif_util
203      USE par_oce       !   ONLY : jpts
204      USE oce
205      IMPLICIT NONE
206      !!----------------------------------------------------------------------
207   
208      ! 1. Declaration of the type of variable which have to be interpolated
209      !---------------------------------------------------------------------
210      CALL agrif_declare_variable((/2,2,0,0/),(/3,3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/jpi,jpj,jpk,jpts/),tsn_id)
211      CALL agrif_declare_variable((/2,2,0,0/),(/3,3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/jpi,jpj,jpk,jpts/),tsa_id)
212      CALL agrif_declare_variable((/2,2,0,0/),(/3,3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/jpi,jpj,jpk,jpts/),tsb_id)
213
214      CALL agrif_declare_variable((/1,2,0/),(/2,3,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj,jpk/),un_id)
215      CALL agrif_declare_variable((/2,1,0/),(/3,2,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj,jpk/),vn_id)
216      CALL agrif_declare_variable((/1,2,0/),(/2,3,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj,jpk/),ua_id)
217      CALL agrif_declare_variable((/2,1,0/),(/3,2,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj,jpk/),va_id)
218   
219      CALL agrif_declare_variable((/1,2/),(/2,3/),(/'x','y'/),(/1,1/),(/jpi,jpj/),e1u_id)
220      CALL agrif_declare_variable((/2,1/),(/3,2/),(/'x','y'/),(/1,1/),(/jpi,jpj/),e2v_id)
221
222      CALL agrif_declare_variable((/2,2/),(/3,3/),(/'x','y'/),(/1,1/),(/jpi,jpj/),sshn_id)
223      CALL agrif_declare_variable((/2,2/),(/3,3/),(/'x','y'/),(/1,1/),(/jpi,jpj/),gcb_id)
224       
225      ! 2. Type of interpolation
226      !-------------------------
227      CALL Agrif_Set_bcinterp(tsn_id,interp=AGRIF_linear)
228      CALL Agrif_Set_bcinterp(tsa_id,interp=AGRIF_linear)
229   
230      Call Agrif_Set_bcinterp(un_id,interp1=Agrif_linear,interp2=AGRIF_ppm)
231      Call Agrif_Set_bcinterp(vn_id,interp1=AGRIF_ppm,interp2=Agrif_linear)
232
233      Call Agrif_Set_bcinterp(ua_id,interp1=Agrif_linear,interp2=AGRIF_ppm)
234      Call Agrif_Set_bcinterp(va_id,interp1=AGRIF_ppm,interp2=Agrif_linear)
235
236      Call Agrif_Set_bcinterp(e1u_id,interp1=Agrif_linear,interp2=AGRIF_ppm)
237      Call Agrif_Set_bcinterp(e2v_id,interp1=AGRIF_ppm,interp2=Agrif_linear)
238
239      ! 3. Location of interpolation
240      !-----------------------------
241      Call Agrif_Set_bc(un_id,(/0,1/))
242      Call Agrif_Set_bc(vn_id,(/0,1/))
243
244      Call Agrif_Set_bc(e1u_id,(/0,0/))
245      Call Agrif_Set_bc(e2v_id,(/0,0/))
246
247      Call Agrif_Set_bc(tsn_id,(/0,1/))
248      Call Agrif_Set_bc(tsa_id,(/-3*Agrif_irhox(),0/))
249
250      Call Agrif_Set_bc(ua_id,(/-2*Agrif_irhox(),0/))
251      Call Agrif_Set_bc(va_id,(/-2*Agrif_irhox(),0/))
252
253      ! 5. Update type
254      !---------------
255      Call Agrif_Set_Updatetype(tsn_id, update = AGRIF_Update_Average)
256      Call Agrif_Set_Updatetype(tsb_id, update = AGRIF_Update_Average)
257
258      Call Agrif_Set_Updatetype(sshn_id, update = AGRIF_Update_Average)
259      Call Agrif_Set_Updatetype(gcb_id,update = AGRIF_Update_Average)
260
261      Call Agrif_Set_Updatetype(un_id,update1 = Agrif_Update_Copy, update2 = Agrif_Update_Average)
262      Call Agrif_Set_Updatetype(vn_id,update1 = Agrif_Update_Average, update2 = Agrif_Update_Copy)
263
264      Call Agrif_Set_Updatetype(e1u_id,update1 = Agrif_Update_Copy, update2=Agrif_Update_Average)
265      Call Agrif_Set_Updatetype(e2v_id,update1 = Agrif_Update_Average, update2=Agrif_Update_Copy)
266
267   END SUBROUTINE agrif_declare_var
268# endif
269   
270# if defined key_top
271   SUBROUTINE Agrif_InitValues_cont_top
272      !!----------------------------------------------------------------------
273      !!                 *** ROUTINE Agrif_InitValues_cont_top ***
274      !!
275      !! ** Purpose :: Declaration of variables to be interpolated
276      !!----------------------------------------------------------------------
277      USE Agrif_Util
278      USE oce 
279      USE dom_oce
280      USE nemogcm
281      USE trc
282      USE in_out_manager
283      USE agrif_top_update
284      USE agrif_top_interp
285      USE agrif_top_sponge
286      !
287      IMPLICIT NONE
288      !
289      REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE :: tabtrtemp
290      LOGICAL :: check_namelist
291      !!----------------------------------------------------------------------
292
293      ALLOCATE( tabtrtemp(jpi,jpj,jpk,jptra) )
294     
295     
296      ! 1. Declaration of the type of variable which have to be interpolated
297      !---------------------------------------------------------------------
298      CALL agrif_declare_var_top
299
300      ! 2. First interpolations of potentially non zero fields
301      !-------------------------------------------------------
302      Agrif_SpecialValue=0.
303      Agrif_UseSpecialValue = .TRUE.
304      Call Agrif_Bc_variable(tabtrtemp,trn_id,calledweight=1.)
305      Call Agrif_Bc_variable(tabtrtemp,tra_id,calledweight=1.,procname=interptrn)
306      Agrif_UseSpecialValue = .FALSE.
307
308      ! 3. Some controls
309      !-----------------
310      check_namelist = .true.
311           
312      IF( check_namelist ) THEN
313#  if defined offline     
314         ! Check time steps
315         IF( nint(Agrif_Rhot()) * nint(rdt) .ne. Agrif_Parent(rdt) ) THEN
316            WRITE(*,*) 'incompatible time step between grids'
317            WRITE(*,*) 'parent grid value : ',Agrif_Parent(rdt)
318            WRITE(*,*) 'child  grid value : ',nint(rdt)
319            WRITE(*,*) 'value on parent grid should be : ',rdt*Agrif_Rhot()
320            STOP
321         ENDIF
322
323         ! Check run length
324         IF( Agrif_IRhot() * (Agrif_Parent(nitend)- &
325            Agrif_Parent(nit000)+1) .ne. (nitend-nit000+1) ) THEN
326            WRITE(*,*) 'incompatible run length between grids'
327            WRITE(*,*) 'parent grid value : ',(Agrif_Parent(nitend)- &
328               Agrif_Parent(nit000)+1),' time step'
329            WRITE(*,*) 'child  grid value : ', &
330               (nitend-nit000+1),' time step'
331            WRITE(*,*) 'value on child grid should be : ', &
332               Agrif_IRhot() * (Agrif_Parent(nitend)- &
333               Agrif_Parent(nit000)+1)
334            STOP
335         ENDIF
336         
337         ! Check coordinates
338         IF( ln_zps ) THEN
339            ! check parameters for partial steps
340            IF( Agrif_Parent(e3zps_min) .ne. e3zps_min ) THEN
341               WRITE(*,*) 'incompatible e3zps_min between grids'
342               WRITE(*,*) 'parent grid :',Agrif_Parent(e3zps_min)
343               WRITE(*,*) 'child grid  :',e3zps_min
344               WRITE(*,*) 'those values should be identical'
345               STOP
346            ENDIF         
347            IF( Agrif_Parent(e3zps_rat) .ne. e3zps_rat ) THEN
348               WRITE(*,*) 'incompatible e3zps_rat between grids'
349               WRITE(*,*) 'parent grid :',Agrif_Parent(e3zps_rat)
350               WRITE(*,*) 'child grid  :',e3zps_rat
351               WRITE(*,*) 'those values should be identical'                 
352               STOP
353            ENDIF
354         ENDIF
355#  endif         
356        ! Check passive tracer cell
357        IF( nn_dttrc .ne. 1 ) THEN
358           WRITE(*,*) 'nn_dttrc should be equal to 1'
359        ENDIF
360      ENDIF
361       
362      CALL Agrif_Update_trc(0)
363      nbcline_trc = 0
364      !
365      DEALLOCATE(tabtrtemp)
366      !
367   END SUBROUTINE Agrif_InitValues_cont_top
368
369
370   SUBROUTINE agrif_declare_var_top
371      !!----------------------------------------------------------------------
372      !!                 *** ROUTINE agrif_declare_var_top ***
373      !!
374      !! ** Purpose :: Declaration of TOP variables to be interpolated
375      !!----------------------------------------------------------------------
376      USE agrif_util
377      USE dom_oce
378      USE trc
379     
380      IMPLICIT NONE
381   
382      ! 1. Declaration of the type of variable which have to be interpolated
383      !---------------------------------------------------------------------
384      CALL agrif_declare_variable((/2,2,0,0/),(/3,3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/jpi,jpj,jpk,jptra/),trn_id)
385      CALL agrif_declare_variable((/2,2,0,0/),(/3,3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/jpi,jpj,jpk,jptra/),trb_id)
386      CALL agrif_declare_variable((/2,2,0,0/),(/3,3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/jpi,jpj,jpk,jptra/),tra_id)
387#  if defined key_offline
388      CALL agrif_declare_variable((/1,2/),(/2,3/),(/'x','y'/),(/1,1/),(/jpi,jpj/),e1u_id)
389      CALL agrif_declare_variable((/2,1/),(/3,2/),(/'x','y'/),(/1,1/),(/jpi,jpj/),e2v_id)
390#  endif
391       
392      ! 2. Type of interpolation
393      !-------------------------
394      CALL Agrif_Set_bcinterp(trn_id,interp=AGRIF_linear)
395      CALL Agrif_Set_bcinterp(tra_id,interp=AGRIF_linear)
396   
397#  if defined key_offline
398      Call Agrif_Set_bcinterp(e1u_id,interp1=Agrif_linear,interp2=AGRIF_ppm)
399      Call Agrif_Set_bcinterp(e2v_id,interp1=AGRIF_ppm,interp2=Agrif_linear)
400#  endif
401
402      ! 3. Location of interpolation
403      !-----------------------------
404#  if defined key_offline
405      Call Agrif_Set_bc(e1u_id,(/0,0/))
406      Call Agrif_Set_bc(e2v_id,(/0,0/))
407#  endif
408      Call Agrif_Set_bc(trn_id,(/0,1/))
409      Call Agrif_Set_bc(tra_id,(/-3*Agrif_irhox(),0/))
410
411      ! 5. Update type
412      !---------------
413      Call Agrif_Set_Updatetype(trn_id, update = AGRIF_Update_Average)
414      Call Agrif_Set_Updatetype(trb_id, update = AGRIF_Update_Average)
415
416#  if defined key_offline
417      Call Agrif_Set_Updatetype(e1u_id,update1 = Agrif_Update_Copy, update2=Agrif_Update_Average)
418      Call Agrif_Set_Updatetype(e2v_id,update1 = Agrif_Update_Average, update2=Agrif_Update_Copy)
419#  endif
420
421   END SUBROUTINE agrif_declare_var_top
422# endif
423   
424   SUBROUTINE Agrif_detect( kg, ksizex )
425      !!----------------------------------------------------------------------
426      !!   *** ROUTINE Agrif_detect ***
427      !!----------------------------------------------------------------------
428      USE Agrif_Types
429      !
430      INTEGER, DIMENSION(2) :: ksizex
431      INTEGER, DIMENSION(ksizex(1),ksizex(2)) :: kg 
432      !!----------------------------------------------------------------------
433      !
434      RETURN
435      !
436   END SUBROUTINE Agrif_detect
437
438
439   SUBROUTINE agrif_nemo_init
440      !!----------------------------------------------------------------------
441      !!                     *** ROUTINE agrif_init ***
442      !!----------------------------------------------------------------------
443      USE agrif_oce 
444      USE in_out_manager
445      USE lib_mpp
446      IMPLICIT NONE
447      !
448      NAMELIST/namagrif/ nn_cln_update, rn_sponge_tra, rn_sponge_dyn, ln_spc_dyn
449      !!----------------------------------------------------------------------
450      !
451      REWIND( numnam )                ! Read namagrif namelist
452      READ  ( numnam, namagrif )
453      !
454      IF(lwp) THEN                    ! control print
455         WRITE(numout,*)
456         WRITE(numout,*) 'agrif_nemo_init : AGRIF parameters'
457         WRITE(numout,*) '~~~~~~~~~~~~~~~'
458         WRITE(numout,*) '   Namelist namagrif : set AGRIF parameters'
459         WRITE(numout,*) '      baroclinic update frequency       nn_cln_update = ', nn_cln_update
460         WRITE(numout,*) '      sponge coefficient for tracers    rn_sponge_tra = ', rn_sponge_tra, ' s'
461         WRITE(numout,*) '      sponge coefficient for dynamics   rn_sponge_tra = ', rn_sponge_dyn, ' s'
462         WRITE(numout,*) '      use special values for dynamics   ln_spc_dyn    = ', ln_spc_dyn
463         WRITE(numout,*) 
464      ENDIF
465      !
466      ! convert DOCTOR namelist name into OLD names
467      nbclineupdate = nn_cln_update
468      visc_tra      = rn_sponge_tra
469      visc_dyn      = rn_sponge_dyn
470      !
471      IF( agrif_oce_alloc()  > 0 )   CALL ctl_warn('agrif sol_oce_alloc: allocation of arrays failed')
472      !
473    END SUBROUTINE agrif_nemo_init
474
475# if defined key_mpp_mpi
476
477   SUBROUTINE Agrif_InvLoc( indloc, nprocloc, i, indglob )
478      !!----------------------------------------------------------------------
479      !!                     *** ROUTINE Agrif_detect ***
480      !!----------------------------------------------------------------------
481      USE dom_oce
482      IMPLICIT NONE
483      !
484      INTEGER :: indglob, indloc, nprocloc, i
485      !!----------------------------------------------------------------------
486      !
487      SELECT CASE( i )
488      CASE(1)   ;   indglob = indloc + nimppt(nprocloc+1) - 1
489      CASE(2)   ;   indglob = indloc + njmppt(nprocloc+1) - 1 
490      CASE(3)   ;   indglob = indloc
491      CASE(4)   ;   indglob = indloc
492      END SELECT
493      !
494   END SUBROUTINE Agrif_InvLoc
495
496# endif
497
498#else
499   SUBROUTINE Subcalledbyagrif
500      !!----------------------------------------------------------------------
501      !!                   *** ROUTINE Subcalledbyagrif ***
502      !!----------------------------------------------------------------------
503      WRITE(*,*) 'Impossible to be here'
504   END SUBROUTINE Subcalledbyagrif
505#endif
Note: See TracBrowser for help on using the repository browser.