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.
p4zrem.F90 in branches/2016/dev_r6519_HPC_4/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z – NEMO

source: branches/2016/dev_r6519_HPC_4/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zrem.F90 @ 7037

Last change on this file since 7037 was 7037, checked in by mocavero, 8 years ago

ORCA2_LIM_PISCES hybrid version update

File size: 19.3 KB
Line 
1MODULE p4zrem
2   !!======================================================================
3   !!                         ***  MODULE p4zrem  ***
4   !! TOP :   PISCES Compute remineralization/dissolution of organic compounds
5   !!=========================================================================
6   !! History :   1.0  !  2004     (O. Aumont) Original code
7   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90
8   !!             3.4  !  2011-06  (O. Aumont, C. Ethe) Quota model for iron
9   !!----------------------------------------------------------------------
10#if defined key_pisces
11   !!----------------------------------------------------------------------
12   !!   'key_top'       and                                      TOP models
13   !!   'key_pisces'                                       PISCES bio-model
14   !!----------------------------------------------------------------------
15   !!   p4z_rem       :  Compute remineralization/dissolution of organic compounds
16   !!   p4z_rem_init  :  Initialisation of parameters for remineralisation
17   !!   p4z_rem_alloc :  Allocate remineralisation variables
18   !!----------------------------------------------------------------------
19   USE oce_trc         !  shared variables between ocean and passive tracers
20   USE trc             !  passive tracers common variables
21   USE sms_pisces      !  PISCES Source Minus Sink variables
22   USE p4zopt          !  optical model
23   USE p4zche          !  chemical model
24   USE p4zprod         !  Growth rate of the 2 phyto groups
25   USE p4zmeso         !  Sources and sinks of mesozooplankton
26   USE p4zint          !  interpolation and computation of various fields
27   USE p4zlim
28   USE prtctl_trc      !  print control for debugging
29   USE iom             !  I/O manager
30
31
32   IMPLICIT NONE
33   PRIVATE
34
35   PUBLIC   p4z_rem         ! called in p4zbio.F90
36   PUBLIC   p4z_rem_init    ! called in trcsms_pisces.F90
37   PUBLIC   p4z_rem_alloc
38
39   !! * Shared module variables
40   REAL(wp), PUBLIC ::  xremik     !: remineralisation rate of POC
41   REAL(wp), PUBLIC ::  xremip     !: remineralisation rate of DOC
42   REAL(wp), PUBLIC ::  nitrif     !: NH4 nitrification rate
43   REAL(wp), PUBLIC ::  xsirem     !: remineralisation rate of POC
44   REAL(wp), PUBLIC ::  xsiremlab  !: fast remineralisation rate of POC
45   REAL(wp), PUBLIC ::  xsilab     !: fraction of labile biogenic silica
46   REAL(wp), PUBLIC ::  oxymin     !: halk saturation constant for anoxia
47
48
49   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   denitr     !: denitrification array
50   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   denitnh4   !: -    -    -    -   -
51
52   !!----------------------------------------------------------------------
53   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
54   !! $Id: p4zrem.F90 3160 2011-11-20 14:27:18Z cetlod $
55   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
56   !!----------------------------------------------------------------------
57CONTAINS
58
59   SUBROUTINE p4z_rem( kt, knt )
60      !!---------------------------------------------------------------------
61      !!                     ***  ROUTINE p4z_rem  ***
62      !!
63      !! ** Purpose :   Compute remineralization/scavenging of organic compounds
64      !!
65      !! ** Method  : - ???
66      !!---------------------------------------------------------------------
67      !
68      INTEGER, INTENT(in) ::   kt, knt ! ocean time step
69      !
70      INTEGER  ::   ji, jj, jk
71      REAL(wp) ::   zremip, zremik, zsiremin 
72      REAL(wp) ::   zsatur, zsatur2, znusil, znusil2, zdep, zdepmin, zfactdep
73      REAL(wp) ::   zbactfer, zorem, zorem2, zofer, zolimit
74      REAL(wp) ::   zosil, ztem
75#if ! defined key_kriest
76      REAL(wp) ::   zofer2
77#endif
78      REAL(wp) ::   zonitr, zstep, zfact
79      CHARACTER (len=25) :: charout
80      REAL(wp), POINTER, DIMENSION(:,:  ) :: ztempbac
81      REAL(wp), POINTER, DIMENSION(:,:,:) :: zdepbac, zolimi, zdepprod, zw3d
82      !!---------------------------------------------------------------------
83      !
84      IF( nn_timing == 1 )  CALL timing_start('p4z_rem')
85      !
86      ! Allocate temporary workspace
87      CALL wrk_alloc( jpi, jpj,      ztempbac                  )
88      CALL wrk_alloc( jpi, jpj, jpk, zdepbac, zdepprod, zolimi )
89
90      ! Initialisation of temprary arrys
91!$OMP PARALLEL
92!$OMP WORKSHARE
93      zdepprod(:,:,:) = 1._wp
94      ztempbac(:,:)   = 0._wp
95!$OMP END WORKSHARE
96
97      ! Computation of the mean phytoplankton concentration as
98      ! a crude estimate of the bacterial biomass
99      ! this parameterization has been deduced from a model version
100      ! that was modeling explicitely bacteria
101      ! -------------------------------------------------------
102      DO jk = 1, jpkm1
103!$OMP DO schedule(static) private(jj,ji,zdep,zdepmin)
104         DO jj = 1, jpj
105            DO ji = 1, jpi
106               zdep = MAX( hmld(ji,jj), heup(ji,jj) )
107               IF( gdept_n(ji,jj,jk) < zdep ) THEN
108                  zdepbac(ji,jj,jk) = MIN( 0.7 * ( trb(ji,jj,jk,jpzoo) + 2.* trb(ji,jj,jk,jpmes) ), 4.e-6 )
109                  ztempbac(ji,jj)   = zdepbac(ji,jj,jk)
110               ELSE
111                  zdepmin = MIN( 1., zdep / gdept_n(ji,jj,jk) )
112                  zdepbac (ji,jj,jk) = zdepmin**0.683 * ztempbac(ji,jj)
113                  zdepprod(ji,jj,jk) = zdepmin**0.273
114               ENDIF
115            END DO
116         END DO
117!$OMP END DO NOWAIT
118      END DO
119
120!$OMP DO schedule(static) private(jk,jj,ji)
121      DO jk = 1, jpkm1
122         DO jj = 1, jpj
123            DO ji = 1, jpi
124               ! denitrification factor computed from O2 levels
125               nitrfac(ji,jj,jk) = MAX(  0.e0, 0.4 * ( 6.e-6  - trb(ji,jj,jk,jpoxy) )    &
126                  &                                / ( oxymin + trb(ji,jj,jk,jpoxy) )  )
127               nitrfac(ji,jj,jk) = MIN( 1., nitrfac(ji,jj,jk) )
128            END DO
129         END DO
130      END DO
131
132!$OMP DO schedule(static) private(jk,jj,ji,zstep,zremik,zolimit)
133      DO jk = 1, jpkm1
134         DO jj = 1, jpj
135            DO ji = 1, jpi
136               zstep   = xstep
137# if defined key_degrad
138               zstep = zstep * facvol(ji,jj,jk)
139# endif
140               ! DOC ammonification. Depends on depth, phytoplankton biomass
141               ! and a limitation term which is supposed to be a parameterization
142               !     of the bacterial activity.
143               zremik = xremik * zstep / 1.e-6 * xlimbac(ji,jj,jk) * zdepbac(ji,jj,jk) 
144               zremik = MAX( zremik, 2.74e-4 * xstep )
145               ! Ammonification in oxic waters with oxygen consumption
146               ! -----------------------------------------------------
147               zolimit = zremik * ( 1.- nitrfac(ji,jj,jk) ) * trb(ji,jj,jk,jpdoc) 
148               zolimi(ji,jj,jk) = MIN( ( trb(ji,jj,jk,jpoxy) - rtrn ) / o2ut, zolimit ) 
149               ! Ammonification in suboxic waters with denitrification
150               ! -------------------------------------------------------
151               denitr(ji,jj,jk)  = MIN(  ( trb(ji,jj,jk,jpno3) - rtrn ) / rdenit,   &
152                  &                     zremik * nitrfac(ji,jj,jk) * trb(ji,jj,jk,jpdoc)  )
153               !
154               zolimi (ji,jj,jk) = MAX( 0.e0, zolimi (ji,jj,jk) )
155               denitr (ji,jj,jk) = MAX( 0.e0, denitr (ji,jj,jk) )
156               !
157            END DO
158         END DO
159      END DO
160
161
162!$OMP DO schedule(static) private(jk,jj,ji,zstep,zonitr)
163      DO jk = 1, jpkm1
164         DO jj = 1, jpj
165            DO ji = 1, jpi
166               zstep   = xstep
167# if defined key_degrad
168               zstep = zstep * facvol(ji,jj,jk)
169# endif
170               ! NH4 nitrification to NO3. Ceased for oxygen concentrations
171               ! below 2 umol/L. Inhibited at strong light
172               ! ----------------------------------------------------------
173               zonitr  =nitrif * zstep * trb(ji,jj,jk,jpnh4) / ( 1.+ emoy(ji,jj,jk) ) * ( 1.- nitrfac(ji,jj,jk) ) 
174               denitnh4(ji,jj,jk) = nitrif * zstep * trb(ji,jj,jk,jpnh4) * nitrfac(ji,jj,jk) 
175               ! Update of the tracers trends
176               ! ----------------------------
177               tra(ji,jj,jk,jpnh4) = tra(ji,jj,jk,jpnh4) - zonitr - denitnh4(ji,jj,jk)
178               tra(ji,jj,jk,jpno3) = tra(ji,jj,jk,jpno3) + zonitr - rdenita * denitnh4(ji,jj,jk)
179               tra(ji,jj,jk,jpoxy) = tra(ji,jj,jk,jpoxy) - o2nit * zonitr
180               tra(ji,jj,jk,jptal) = tra(ji,jj,jk,jptal) - 2 * rno3 * zonitr + rno3 * ( rdenita - 1. ) * denitnh4(ji,jj,jk)
181            END DO
182         END DO
183      END DO
184!$OMP END DO NOWAIT
185!$OMP END PARALLEL
186
187       IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
188         WRITE(charout, FMT="('rem1')")
189         CALL prt_ctl_trc_info(charout)
190         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
191       ENDIF
192
193!$OMP PARALLEL DO schedule(static) private(jk,jj,ji,zbactfer)
194      DO jk = 1, jpkm1
195         DO jj = 1, jpj
196            DO ji = 1, jpi
197
198               ! Bacterial uptake of iron. No iron is available in DOC. So
199               ! Bacteries are obliged to take up iron from the water. Some
200               ! studies (especially at Papa) have shown this uptake to be significant
201               ! ----------------------------------------------------------
202               zbactfer = 10.e-6 *  rfact2 * prmax(ji,jj,jk) * xlimbacl(ji,jj,jk)             &
203                  &              * trb(ji,jj,jk,jpfer) / ( 2.5E-10 + trb(ji,jj,jk,jpfer) )    &
204                  &              * zdepprod(ji,jj,jk) * zdepbac(ji,jj,jk)
205#if defined key_kriest
206               tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) - zbactfer*0.05
207               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + zbactfer*0.05
208#else
209               tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) - zbactfer*0.16
210               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + zbactfer*0.12
211               tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) + zbactfer*0.04
212#endif
213            END DO
214         END DO
215      END DO
216
217       IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
218         WRITE(charout, FMT="('rem2')")
219         CALL prt_ctl_trc_info(charout)
220         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
221       ENDIF
222
223!$OMP PARALLEL DO schedule(static) private(jk,jj,ji,zstep,zremip,zorem,zofer,zorem2,zofer2)
224      DO jk = 1, jpkm1
225         DO jj = 1, jpj
226            DO ji = 1, jpi
227               zstep   = xstep
228# if defined key_degrad
229               zstep = zstep * facvol(ji,jj,jk)
230# endif
231               ! POC disaggregation by turbulence and bacterial activity.
232               ! --------------------------------------------------------
233               zremip = xremip * zstep * tgfunc(ji,jj,jk) * ( 1.- 0.55 * nitrfac(ji,jj,jk) ) 
234
235               ! POC disaggregation rate is reduced in anoxic zone as shown by
236               ! sediment traps data. In oxic area, the exponent of the martin s
237               ! law is around -0.87. In anoxic zone, it is around -0.35. This
238               ! means a disaggregation constant about 0.5 the value in oxic zones
239               ! -----------------------------------------------------------------
240               zorem  = zremip * trb(ji,jj,jk,jppoc)
241               zofer  = zremip * trb(ji,jj,jk,jpsfe)
242#if ! defined key_kriest
243               zorem2 = zremip * trb(ji,jj,jk,jpgoc)
244               zofer2 = zremip * trb(ji,jj,jk,jpbfe)
245#else
246               zorem2 = zremip * trb(ji,jj,jk,jpnum)
247#endif
248
249               ! Update the appropriate tracers trends
250               ! -------------------------------------
251
252               tra(ji,jj,jk,jpdoc) = tra(ji,jj,jk,jpdoc) + zorem
253               tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) + zofer
254#if defined key_kriest
255               tra(ji,jj,jk,jppoc) = tra(ji,jj,jk,jppoc) - zorem
256               tra(ji,jj,jk,jpnum) = tra(ji,jj,jk,jpnum) - zorem2
257               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) - zofer
258#else
259               tra(ji,jj,jk,jppoc) = tra(ji,jj,jk,jppoc) + zorem2 - zorem
260               tra(ji,jj,jk,jpgoc) = tra(ji,jj,jk,jpgoc) - zorem2
261               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + zofer2 - zofer
262               tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) - zofer2
263#endif
264
265            END DO
266         END DO
267      END DO
268
269       IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
270         WRITE(charout, FMT="('rem3')")
271         CALL prt_ctl_trc_info(charout)
272         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
273       ENDIF
274
275!$OMP PARALLEL DO schedule(static) private(jk,jj,ji,zstep,zsatur,zsatur2,znusil,znusil2,zdep,ztem,zfactdep,zsiremin,zosil)
276      DO jk = 1, jpkm1
277         DO jj = 1, jpj
278            DO ji = 1, jpi
279               zstep   = xstep
280# if defined key_degrad
281               zstep = zstep * facvol(ji,jj,jk)
282# endif
283               ! Remineralization rate of BSi depedant on T and saturation
284               ! ---------------------------------------------------------
285               zsatur   = ( sio3eq(ji,jj,jk) - trb(ji,jj,jk,jpsil) ) / ( sio3eq(ji,jj,jk) + rtrn )
286               zsatur   = MAX( rtrn, zsatur )
287               zsatur2  = ( 1. + tsn(ji,jj,jk,jp_tem) / 400.)**37
288               znusil   = 0.225  * ( 1. + tsn(ji,jj,jk,jp_tem) / 15.) * zsatur + 0.775 * zsatur2 * zsatur**9.25
289               znusil2  = 0.225  * ( 1. + tsn(ji,jj,1,jp_tem) / 15.) + 0.775 * zsatur2
290
291               ! Two classes of BSi are considered : a labile fraction and
292               ! a more refractory one. The ratio between both fractions is
293               ! constant and specified in the namelist.
294               ! ----------------------------------------------------------
295               zdep     = MAX( hmld(ji,jj), heup(ji,jj) ) 
296               zdep     = MAX( 0., gdept_n(ji,jj,jk) - zdep )
297               ztem     = MAX( tsn(ji,jj,1,jp_tem), 0. )
298               zfactdep = xsilab * EXP(-( xsiremlab - xsirem ) * znusil2 * zdep / wsbio2 ) * ztem / ( ztem + 10. )
299               zsiremin = ( xsiremlab * zfactdep + xsirem * ( 1. - zfactdep ) ) * zstep * znusil
300               zosil    = zsiremin * trb(ji,jj,jk,jpgsi)
301               !
302               tra(ji,jj,jk,jpgsi) = tra(ji,jj,jk,jpgsi) - zosil
303               tra(ji,jj,jk,jpsil) = tra(ji,jj,jk,jpsil) + zosil
304               !
305            END DO
306         END DO
307      END DO
308
309      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
310         WRITE(charout, FMT="('rem4')")
311         CALL prt_ctl_trc_info(charout)
312         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
313       ENDIF
314
315      ! Update the arrays TRA which contain the biological sources and sinks
316      ! --------------------------------------------------------------------
317
318!$OMP PARALLEL DO schedule(static) private(jk)
319      DO jk = 1, jpkm1
320         tra(:,:,jk,jppo4) = tra(:,:,jk,jppo4) + zolimi (:,:,jk) + denitr(:,:,jk)
321         tra(:,:,jk,jpnh4) = tra(:,:,jk,jpnh4) + zolimi (:,:,jk) + denitr(:,:,jk)
322         tra(:,:,jk,jpno3) = tra(:,:,jk,jpno3) - denitr (:,:,jk) * rdenit
323         tra(:,:,jk,jpdoc) = tra(:,:,jk,jpdoc) - zolimi (:,:,jk) - denitr(:,:,jk)
324         tra(:,:,jk,jpoxy) = tra(:,:,jk,jpoxy) - zolimi (:,:,jk) * o2ut
325         tra(:,:,jk,jpdic) = tra(:,:,jk,jpdic) + zolimi (:,:,jk) + denitr(:,:,jk)
326         tra(:,:,jk,jptal) = tra(:,:,jk,jptal) + rno3 * ( zolimi(:,:,jk) + ( rdenit + 1.) * denitr(:,:,jk) )
327      END DO
328
329      IF( knt == nrdttrc ) THEN
330          CALL wrk_alloc( jpi, jpj, jpk, zw3d )
331          zfact = 1.e+3 * rfact2r  !  conversion from mol/l/kt to  mol/m3/s
332          !
333          IF( iom_use( "REMIN" ) )  THEN
334!$OMP PARALLEL WORKSHARE
335              zw3d(:,:,:) = zolimi(:,:,:) * tmask(:,:,:) * zfact !  Remineralisation rate
336!$OMP END PARALLEL WORKSHARE
337              CALL iom_put( "REMIN"  , zw3d )
338          ENDIF
339          IF( iom_use( "DENIT" ) )  THEN
340!$OMP PARALLEL WORKSHARE
341              zw3d(:,:,:) = denitr(:,:,:) * rdenit * rno3 * tmask(:,:,:) * zfact ! Denitrification
342!$OMP END PARALLEL WORKSHARE
343              CALL iom_put( "DENIT"  , zw3d )
344          ENDIF
345          !
346          CALL wrk_dealloc( jpi, jpj, jpk, zw3d )
347       ENDIF
348
349      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
350         WRITE(charout, FMT="('rem6')")
351         CALL prt_ctl_trc_info(charout)
352         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
353      ENDIF
354      !
355      CALL wrk_dealloc( jpi, jpj,      ztempbac                  )
356      CALL wrk_dealloc( jpi, jpj, jpk, zdepbac, zdepprod, zolimi )
357      !
358      IF( nn_timing == 1 )  CALL timing_stop('p4z_rem')
359      !
360   END SUBROUTINE p4z_rem
361
362
363   SUBROUTINE p4z_rem_init
364      !!----------------------------------------------------------------------
365      !!                  ***  ROUTINE p4z_rem_init  ***
366      !!
367      !! ** Purpose :   Initialization of remineralization parameters
368      !!
369      !! ** Method  :   Read the nampisrem namelist and check the parameters
370      !!      called at the first timestep
371      !!
372      !! ** input   :   Namelist nampisrem
373      !!
374      !!----------------------------------------------------------------------
375      NAMELIST/nampisrem/ xremik, xremip, nitrif, xsirem, xsiremlab, xsilab,   &
376      &                   oxymin
377      INTEGER :: ios                 ! Local integer output status for namelist read
378
379      REWIND( numnatp_ref )              ! Namelist nampisrem in reference namelist : Pisces remineralization
380      READ  ( numnatp_ref, nampisrem, IOSTAT = ios, ERR = 901)
381901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisrem in reference namelist', lwp )
382
383      REWIND( numnatp_cfg )              ! Namelist nampisrem in configuration namelist : Pisces remineralization
384      READ  ( numnatp_cfg, nampisrem, IOSTAT = ios, ERR = 902 )
385902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisrem in configuration namelist', lwp )
386      IF(lwm) WRITE ( numonp, nampisrem )
387
388      IF(lwp) THEN                         ! control print
389         WRITE(numout,*) ' '
390         WRITE(numout,*) ' Namelist parameters for remineralization, nampisrem'
391         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
392         WRITE(numout,*) '    remineralisation rate of POC              xremip    =', xremip
393         WRITE(numout,*) '    remineralization rate of DOC              xremik    =', xremik
394         WRITE(numout,*) '    remineralization rate of Si               xsirem    =', xsirem
395         WRITE(numout,*) '    fast remineralization rate of Si          xsiremlab =', xsiremlab
396         WRITE(numout,*) '    fraction of labile biogenic silica        xsilab    =', xsilab
397         WRITE(numout,*) '    NH4 nitrification rate                    nitrif    =', nitrif
398         WRITE(numout,*) '    halk saturation constant for anoxia       oxymin    =', oxymin
399      ENDIF
400      !
401!$OMP PARALLEL WORKSHARE
402      nitrfac (:,:,:) = 0._wp
403      denitr  (:,:,:) = 0._wp
404      denitnh4(:,:,:) = 0._wp
405!$OMP END PARALLEL WORKSHARE
406      !
407   END SUBROUTINE p4z_rem_init
408
409
410   INTEGER FUNCTION p4z_rem_alloc()
411      !!----------------------------------------------------------------------
412      !!                     ***  ROUTINE p4z_rem_alloc  ***
413      !!----------------------------------------------------------------------
414      ALLOCATE( denitr(jpi,jpj,jpk), denitnh4(jpi,jpj,jpk), STAT=p4z_rem_alloc )
415      !
416      IF( p4z_rem_alloc /= 0 )   CALL ctl_warn('p4z_rem_alloc: failed to allocate arrays')
417      !
418   END FUNCTION p4z_rem_alloc
419
420#else
421   !!======================================================================
422   !!  Dummy module :                                   No PISCES bio-model
423   !!======================================================================
424CONTAINS
425   SUBROUTINE p4z_rem                    ! Empty routine
426   END SUBROUTINE p4z_rem
427#endif 
428
429   !!======================================================================
430END MODULE p4zrem
Note: See TracBrowser for help on using the repository browser.