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.
p2zsed.F90 in branches/2012/dev_r3438_LOCEAN15_PISLOB/NEMOGCM/NEMO/TOP_SRC/PISCES/P2Z – NEMO

source: branches/2012/dev_r3438_LOCEAN15_PISLOB/NEMOGCM/NEMO/TOP_SRC/PISCES/P2Z/p2zsed.F90 @ 3443

Last change on this file since 3443 was 3443, checked in by cetlod, 12 years ago

branch:2012/dev_r3438_LOCEAN15_PISLOB : 1st step of the merge, see ticket #972

File size: 7.4 KB
Line 
1MODULE p2zsed
2   !!======================================================================
3   !!                         ***  MODULE p2zsed  ***
4   !! TOP :   PISCES Compute loss of organic matter in the sediments
5   !!======================================================================
6   !! History :    -   !  1995-06 (M. Levy)  original code
7   !!              -   !  2000-12 (E. Kestenare)  clean up
8   !!             2.0  !  2007-12  (C. Deltel, G. Madec)  F90 + simplifications
9   !!----------------------------------------------------------------------
10#if defined key_pisces_reduced
11   !!----------------------------------------------------------------------
12   !!   'key_pisces_reduced'                                     LOBSTER bio-model
13   !!----------------------------------------------------------------------
14   !!   p2z_sed        :  Compute loss of organic matter in the sediments
15   !!----------------------------------------------------------------------
16   USE oce_trc         !
17   USE trc
18   USE sms_pisces
19   USE lbclnk
20   USE trdmod_oce
21   USE trdmod_trc
22   USE iom
23   USE prtctl_trc      ! Print control for debbuging
24
25   IMPLICIT NONE
26   PRIVATE
27
28   PUBLIC   p2z_sed         ! called in ???
29   PUBLIC   p2z_sed_init    ! called in ???
30
31   REAL(wp), PUBLIC ::   sedlam     = 3.86e-7   !: time coefficient of POC remineralization in sediments
32   REAL(wp), PUBLIC ::   sedlostpoc = 0.        ! mass of POC lost in sediments
33   REAL(wp), PUBLIC ::   vsed       = 3.47e-5   ! detritus sedimentation speed [m/s]
34   REAL(wp), PUBLIC ::   xhr        = -0.858    ! coeff for martin''s remineralisation profile
35
36   !!* Substitution
37#  include "top_substitute.h90"
38   !!----------------------------------------------------------------------
39   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
40   !! $Id: p2z_sed.F90 3294 2012-01-28 16:44:18Z rblod $
41   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
42   !!----------------------------------------------------------------------
43
44CONTAINS
45
46   SUBROUTINE p2z_sed( kt )
47      !!---------------------------------------------------------------------
48      !!                     ***  ROUTINE p2z_sed  ***
49      !!
50      !! ** Purpose :   compute the now trend due to the vertical sedimentation of
51      !!              detritus and add it to the general trend of detritus equations
52      !!
53      !! ** Method  :   this ROUTINE compute not exactly the advection but the
54      !!              transport term, i.e.  dz(wt) and dz(ws)., dz(wtr)
55      !!              using an upstream scheme
56      !!              the now vertical advection of tracers is given by:
57      !!                      dz(trn wn) = 1/bt dk+1( e1t e2t vsed (trn) )
58      !!              add this trend now to the general trend of tracer (ta,sa,tra):
59      !!                             tra = tra + dz(trn wn)
60      !!       
61      !!              IF 'key_diabio' is defined, the now vertical advection
62      !!              trend of passive tracers is saved for futher diagnostics.
63      !!---------------------------------------------------------------------
64      !!
65      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index     
66      !!
67      INTEGER  ::   ji, jj, jk, jl, ierr
68      CHARACTER (len=25) :: charout
69      REAL(wp), POINTER, DIMENSION(:,:  ) :: zw2d
70      REAL(wp), POINTER, DIMENSION(:,:,:) :: zwork, ztra, ztrbio
71      !!---------------------------------------------------------------------
72      !
73      IF( nn_timing == 1 )  CALL timing_start('p2z_sed')
74      !
75      IF( kt == nittrc000 ) THEN
76         IF(lwp) WRITE(numout,*)
77         IF(lwp) WRITE(numout,*) ' p2z_sed: LOBSTER sedimentation'
78         IF(lwp) WRITE(numout,*) ' ~~~~~~~'
79      ENDIF
80
81      ! Allocate temporary workspace
82                       CALL wrk_alloc( jpi, jpj, jpk, zwork, ztra )
83      IF( ln_diatrc )  CALL wrk_alloc( jpi, jpj, zw2d )
84      IF( l_trdtrc ) THEN
85         CALL wrk_alloc( jpi, jpj, jpk, ztrbio )
86         ztrbio(:,:,:) = tra(:,:,:,jpdet)
87      ENDIF
88
89      ! sedimentation of detritus  : upstream scheme
90      ! --------------------------------------------
91
92      ! for detritus sedimentation only - jpdet
93      zwork(:,:,1  ) = 0.e0      ! surface value set to zero
94      zwork(:,:,jpk) = 0.e0      ! bottom value  set to zero
95
96      ! tracer flux at w-point: we use -vsed (downward flux)  with simplification : no e1*e2
97      DO jk = 2, jpkm1
98         zwork(:,:,jk) = -vsed * trn(:,:,jk-1,jpdet)
99      END DO
100
101      ! tracer flux divergence at t-point added to the general trend
102      DO jk = 1, jpkm1
103         DO jj = 1, jpj
104            DO ji = 1, jpi
105               ztra(ji,jj,jk)  = - ( zwork(ji,jj,jk) - zwork(ji,jj,jk+1) ) / fse3t(ji,jj,jk)
106               tra(ji,jj,jk,jpdet) = tra(ji,jj,jk,jpdet) + ztra(ji,jj,jk) 
107            END DO
108         END DO
109      END DO
110
111      IF( ln_diatrc ) THEN
112         DO jk = 1, jpkm1
113            zw2d(:,:) = zw2d(:,:) + ztra(:,:,jk) * fse3t(:,:,jk) * 86400.
114         END DO
115         IF( lk_iomput )  THEN
116           CALL iom_put( "TDETSED", zw2d )
117         ELSE
118           trc2d(:,:,jp_pcs0_2d + 7) = zw2d(:,:)
119         ENDIF
120         CALL wrk_dealloc( jpi, jpj, zw2d )
121      ENDIF
122      !
123      IF( ln_diabio )  trbio(:,:,:,jp_pcs0_trd + 7) = ztra(:,:,:)
124      CALL wrk_dealloc( jpi, jpj, jpk, zwork, ztra )
125      !
126      IF( l_trdtrc ) THEN
127         ztrbio(:,:,:) = tra(:,:,:,jpdet) - ztrbio(:,:,:)
128         jl = jp_pcs0_trd + 7
129         CALL trd_mod_trc( ztrbio, jl, kt )   ! handle the trend
130         CALL wrk_dealloc( jpi, jpj, jpk, ztrbio )
131      ENDIF
132
133      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
134         WRITE(charout, FMT="('sed')")
135         CALL prt_ctl_trc_info(charout)
136         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
137      ENDIF
138      !
139      IF( nn_timing == 1 )  CALL timing_stop('p2z_sed')
140      !
141   END SUBROUTINE p2z_sed
142
143   SUBROUTINE p2z_sed_init
144      !!----------------------------------------------------------------------
145      !!                  ***  ROUTINE p2z_sed_init  ***
146      !!
147      !! ** Purpose :   Parameters from aphotic layers to sediment
148      !!
149      !! ** Method  :   Read the namlobsed namelist and check the parameters
150      !!
151      !!----------------------------------------------------------------------
152      NAMELIST/namlobsed/ sedlam, sedlostpoc, vsed, xhr
153
154      REWIND( numnatp )
155      READ  ( numnatp, namlobsed )
156
157      IF(lwp) THEN
158          WRITE(numout,*) ' Namelist namlobsed'
159          WRITE(numout,*) '    time coeff of POC in sediments                       sedlam    =', sedlam
160          WRITE(numout,*) '    Sediment geol loss for POC                           sedlostpoc=', sedlostpoc
161          WRITE(numout,*) '    detritus sedimentation speed                         vsed      =', 86400 * vsed  , ' d'
162          WRITE(numout,*) '    coeff for martin''s remineralistion                  xhr       =', xhr
163          WRITE(numout,*) ' '
164      ENDIF
165      !
166   END SUBROUTINE p2z_sed_init
167
168#else
169   !!======================================================================
170   !!  Dummy module :                                   No PISCES bio-model
171   !!======================================================================
172CONTAINS
173   SUBROUTINE p2z_sed( kt )                   ! Empty routine
174      INTEGER, INTENT( in ) ::   kt
175      WRITE(*,*) 'p2z_sed: You should not have seen this print! error?', kt
176   END SUBROUTINE p2z_sed
177#endif 
178
179   !!======================================================================
180END MODULE  p2zsed
Note: See TracBrowser for help on using the repository browser.