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/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/NEMO/TOP_SRC/PISCES/P2Z – NEMO

source: branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/NEMO/TOP_SRC/PISCES/P2Z/p2zsed.F90 @ 6225

Last change on this file since 6225 was 6225, checked in by jamesharle, 8 years ago

Update MPP_BDY_UPDATE branch to be consistent with head of trunk

  • Property svn:keywords set to Id
File size: 8.2 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 trd_oce
21   USE trdtrc
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      !: time coefficient of POC remineralization in sediments
32   REAL(wp), PUBLIC ::   sedlostpoc  ! mass of POC lost in sediments
33   REAL(wp), PUBLIC ::   vsed        ! detritus sedimentation speed [m/s]
34   REAL(wp), PUBLIC ::   xhr         ! coeff for martin''s remineralisation profile
35
36   !!----------------------------------------------------------------------
37   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
38   !! $Id$
39   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
40   !!----------------------------------------------------------------------
41
42CONTAINS
43
44   SUBROUTINE p2z_sed( kt )
45      !!---------------------------------------------------------------------
46      !!                     ***  ROUTINE p2z_sed  ***
47      !!
48      !! ** Purpose :   compute the now trend due to the vertical sedimentation of
49      !!              detritus and add it to the general trend of detritus equations
50      !!
51      !! ** Method  :   this ROUTINE compute not exactly the advection but the
52      !!              transport term, i.e.  dz(wt) and dz(ws)., dz(wtr)
53      !!              using an upstream scheme
54      !!              the now vertical advection of tracers is given by:
55      !!                      dz(trn wn) = 1/bt dk+1( e1t e2t vsed (trn) )
56      !!              add this trend now to the general trend of tracer (ta,sa,tra):
57      !!                             tra = tra + dz(trn wn)
58      !!       
59      !!              IF 'key_diabio' is defined, the now vertical advection
60      !!              trend of passive tracers is saved for futher diagnostics.
61      !!---------------------------------------------------------------------
62      !!
63      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index     
64      !!
65      INTEGER  ::   ji, jj, jk, jl, ierr
66      CHARACTER (len=25) :: charout
67      REAL(wp), POINTER, DIMENSION(:,:  ) :: zw2d
68      REAL(wp), POINTER, DIMENSION(:,:,:) :: zwork, ztra, ztrbio
69      !!---------------------------------------------------------------------
70      !
71      IF( nn_timing == 1 )  CALL timing_start('p2z_sed')
72      !
73      IF( kt == nittrc000 ) THEN
74         IF(lwp) WRITE(numout,*)
75         IF(lwp) WRITE(numout,*) ' p2z_sed: LOBSTER sedimentation'
76         IF(lwp) WRITE(numout,*) ' ~~~~~~~'
77      ENDIF
78
79      ! Allocate temporary workspace
80      CALL wrk_alloc( jpi, jpj, jpk, zwork, ztra )
81      IF( l_trdtrc ) THEN
82         CALL wrk_alloc( jpi, jpj, jpk, ztrbio )
83         ztrbio(:,:,:) = tra(:,:,:,jpdet)
84      ENDIF
85
86      ! sedimentation of detritus  : upstream scheme
87      ! --------------------------------------------
88
89      ! for detritus sedimentation only - jpdet
90      zwork(:,:,1  ) = 0.e0      ! surface value set to zero
91      zwork(:,:,jpk) = 0.e0      ! bottom value  set to zero
92
93      ! tracer flux at w-point: we use -vsed (downward flux)  with simplification : no e1*e2
94      DO jk = 2, jpkm1
95         zwork(:,:,jk) = -vsed * trn(:,:,jk-1,jpdet)
96      END DO
97
98      ! tracer flux divergence at t-point added to the general trend
99      DO jk = 1, jpkm1
100         DO jj = 1, jpj
101            DO ji = 1, jpi
102               ztra(ji,jj,jk)  = - ( zwork(ji,jj,jk) - zwork(ji,jj,jk+1) ) / e3t_n(ji,jj,jk)
103               tra(ji,jj,jk,jpdet) = tra(ji,jj,jk,jpdet) + ztra(ji,jj,jk) 
104            END DO
105         END DO
106      END DO
107
108      IF( lk_iomput )  THEN
109         IF( iom_use( "TDETSED" ) ) THEN
110            CALL wrk_alloc( jpi, jpj, zw2d )
111            zw2d(:,:) =  ztra(:,:,1) * e3t_n(:,:,1) * 86400._wp
112            DO jk = 2, jpkm1
113               zw2d(:,:) = zw2d(:,:) + ztra(:,:,jk) * e3t_n(:,:,jk) * 86400._wp
114            END DO
115            CALL iom_put( "TDETSED", zw2d )
116            CALL wrk_dealloc( jpi, jpj, zw2d )
117         ENDIF
118      ELSE
119         IF( ln_diatrc ) THEN
120            CALL wrk_alloc( jpi, jpj, zw2d )
121            zw2d(:,:) =  ztra(:,:,1) * e3t_n(:,:,1) * 86400._wp
122            DO jk = 2, jpkm1
123               zw2d(:,:) = zw2d(:,:) + ztra(:,:,jk) * e3t_n(:,:,jk) * 86400._wp
124            END DO
125            trc2d(:,:,jp_pcs0_2d + 7) = zw2d(:,:)
126            CALL wrk_dealloc( jpi, jpj, zw2d )
127         ENDIF
128      ENDIF
129      !
130      IF( ln_diabio .AND. .NOT. lk_iomput )  trbio(:,:,:,jp_pcs0_trd + 7) = ztra(:,:,:)
131      CALL wrk_dealloc( jpi, jpj, jpk, zwork, ztra )
132      !
133      IF( l_trdtrc ) THEN
134         ztrbio(:,:,:) = tra(:,:,:,jpdet) - ztrbio(:,:,:)
135         jl = jp_pcs0_trd + 7
136         CALL trd_trc( ztrbio, jl, kt )   ! handle the trend
137         CALL wrk_dealloc( jpi, jpj, jpk, ztrbio )
138      ENDIF
139
140      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
141         WRITE(charout, FMT="('sed')")
142         CALL prt_ctl_trc_info(charout)
143         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
144      ENDIF
145      !
146      IF( nn_timing == 1 )  CALL timing_stop('p2z_sed')
147      !
148   END SUBROUTINE p2z_sed
149
150   SUBROUTINE p2z_sed_init
151      !!----------------------------------------------------------------------
152      !!                  ***  ROUTINE p2z_sed_init  ***
153      !!
154      !! ** Purpose :   Parameters from aphotic layers to sediment
155      !!
156      !! ** Method  :   Read the namlobsed namelist and check the parameters
157      !!
158      !!----------------------------------------------------------------------
159      NAMELIST/namlobsed/ sedlam, sedlostpoc, vsed, xhr
160      INTEGER :: ios                 ! Local integer output status for namelist read
161
162      REWIND( numnatp_ref )              ! Namelist namlobsed in reference namelist : Lobster sediments
163      READ  ( numnatp_ref, namlobsed, IOSTAT = ios, ERR = 901)
164901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namlosed in reference namelist', lwp )
165
166      REWIND( numnatp_cfg )              ! Namelist namlobsed in configuration namelist : Lobster sediments
167      READ  ( numnatp_cfg, namlobsed, IOSTAT = ios, ERR = 902 )
168902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namlobsed in configuration namelist', lwp )
169      IF(lwm) WRITE ( numonp, namlobsed )
170
171      IF(lwp) THEN
172          WRITE(numout,*) ' Namelist namlobsed'
173          WRITE(numout,*) '    time coeff of POC in sediments                       sedlam    =', sedlam
174          WRITE(numout,*) '    Sediment geol loss for POC                           sedlostpoc=', sedlostpoc
175          WRITE(numout,*) '    detritus sedimentation speed                         vsed      =', 86400 * vsed  , ' d'
176          WRITE(numout,*) '    coeff for martin''s remineralistion                  xhr       =', xhr
177          WRITE(numout,*) ' '
178      ENDIF
179      !
180   END SUBROUTINE p2z_sed_init
181
182#else
183   !!======================================================================
184   !!  Dummy module :                                   No PISCES bio-model
185   !!======================================================================
186CONTAINS
187   SUBROUTINE p2z_sed( kt )                   ! Empty routine
188      INTEGER, INTENT( in ) ::   kt
189      WRITE(*,*) 'p2z_sed: You should not have seen this print! error?', kt
190   END SUBROUTINE p2z_sed
191#endif 
192
193   !!======================================================================
194END MODULE  p2zsed
Note: See TracBrowser for help on using the repository browser.