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/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P2Z – NEMO

source: branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P2Z/p2zsed.F90 @ 9125

Last change on this file since 9125 was 9125, checked in by timgraham, 7 years ago

Removed wrk_arrays from whole code. No change in SETTE results from this.

  • Property svn:keywords set to Id
File size: 6.5 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   !!   p2z_sed        :  Compute loss of organic matter in the sediments
11   !!----------------------------------------------------------------------
12   USE oce_trc         !
13   USE trc
14   USE sms_pisces
15   USE lbclnk
16   USE trd_oce
17   USE trdtrc
18   USE iom
19   USE prtctl_trc      ! Print control for debbuging
20
21   IMPLICIT NONE
22   PRIVATE
23
24   PUBLIC   p2z_sed         ! called in ???
25   PUBLIC   p2z_sed_init    ! called in ???
26
27   REAL(wp), PUBLIC ::   sedlam      !: time coefficient of POC remineralization in sediments
28   REAL(wp), PUBLIC ::   sedlostpoc  ! mass of POC lost in sediments
29   REAL(wp), PUBLIC ::   vsed        ! detritus sedimentation speed [m/s]
30   REAL(wp), PUBLIC ::   xhr         ! coeff for martin''s remineralisation profile
31
32   !!----------------------------------------------------------------------
33   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
34   !! $Id$
35   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
36   !!----------------------------------------------------------------------
37CONTAINS
38
39   SUBROUTINE p2z_sed( kt )
40      !!---------------------------------------------------------------------
41      !!                     ***  ROUTINE p2z_sed  ***
42      !!
43      !! ** Purpose :   compute the now trend due to the vertical sedimentation of
44      !!              detritus and add it to the general trend of detritus equations
45      !!
46      !! ** Method  :   this ROUTINE compute not exactly the advection but the
47      !!              transport term, i.e.  dz(wt) and dz(ws)., dz(wtr)
48      !!              using an upstream scheme
49      !!              the now vertical advection of tracers is given by:
50      !!                      dz(trn wn) = 1/bt dk+1( e1t e2t vsed (trn) )
51      !!              add this trend now to the general trend of tracer (ta,sa,tra):
52      !!                             tra = tra + dz(trn wn)
53      !!       
54      !!              IF 'key_diabio' is defined, the now vertical advection
55      !!              trend of passive tracers is saved for futher diagnostics.
56      !!---------------------------------------------------------------------
57      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index     
58      !
59      INTEGER  ::   ji, jj, jk, jl, ierr
60      CHARACTER (len=25) :: charout
61      REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zw2d
62      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zwork, ztra
63      !!---------------------------------------------------------------------
64      !
65      IF( ln_timing )   CALL timing_start('p2z_sed')
66      !
67      IF( kt == nittrc000 ) THEN
68         IF(lwp) WRITE(numout,*)
69         IF(lwp) WRITE(numout,*) ' p2z_sed: LOBSTER sedimentation'
70         IF(lwp) WRITE(numout,*) ' ~~~~~~~'
71      ENDIF
72
73      ! sedimentation of detritus  : upstream scheme
74      ! --------------------------------------------
75
76      ! for detritus sedimentation only - jpdet
77      zwork(:,:,1  ) = 0.e0      ! surface value set to zero
78      zwork(:,:,jpk) = 0.e0      ! bottom value  set to zero
79
80      ! tracer flux at w-point: we use -vsed (downward flux)  with simplification : no e1*e2
81      DO jk = 2, jpkm1
82         zwork(:,:,jk) = -vsed * trn(:,:,jk-1,jpdet)
83      END DO
84
85      ! tracer flux divergence at t-point added to the general trend
86      DO jk = 1, jpkm1
87         DO jj = 1, jpj
88            DO ji = 1, jpi
89               ztra(ji,jj,jk)  = - ( zwork(ji,jj,jk) - zwork(ji,jj,jk+1) ) / e3t_n(ji,jj,jk)
90               tra(ji,jj,jk,jpdet) = tra(ji,jj,jk,jpdet) + ztra(ji,jj,jk) 
91            END DO
92         END DO
93      END DO
94
95      IF( lk_iomput )  THEN
96         IF( iom_use( "TDETSED" ) ) THEN
97            ALLOCATE( zw2d(jpi,jpj) )
98            zw2d(:,:) =  ztra(:,:,1) * e3t_n(:,:,1) * 86400._wp
99            DO jk = 2, jpkm1
100               zw2d(:,:) = zw2d(:,:) + ztra(:,:,jk) * e3t_n(:,:,jk) * 86400._wp
101            END DO
102            CALL iom_put( "TDETSED", zw2d )
103            DEALLOCATE( zw2d )
104         ENDIF
105      ENDIF
106      !
107
108      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
109         WRITE(charout, FMT="('sed')")
110         CALL prt_ctl_trc_info(charout)
111         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
112      ENDIF
113      !
114      IF( ln_timing )   CALL timing_stop('p2z_sed')
115      !
116   END SUBROUTINE p2z_sed
117
118
119   SUBROUTINE p2z_sed_init
120      !!----------------------------------------------------------------------
121      !!                  ***  ROUTINE p2z_sed_init  ***
122      !!
123      !! ** Purpose :   Parameters from aphotic layers to sediment
124      !!
125      !! ** Method  :   Read the namlobsed namelist and check the parameters
126      !!
127      !!----------------------------------------------------------------------
128      NAMELIST/namlobsed/ sedlam, sedlostpoc, vsed, xhr
129      INTEGER :: ios                 ! Local integer output status for namelist read
130
131      REWIND( numnatp_ref )              ! Namelist namlobsed in reference namelist : Lobster sediments
132      READ  ( numnatp_ref, namlobsed, IOSTAT = ios, ERR = 901)
133901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namlosed in reference namelist', lwp )
134
135      REWIND( numnatp_cfg )              ! Namelist namlobsed in configuration namelist : Lobster sediments
136      READ  ( numnatp_cfg, namlobsed, IOSTAT = ios, ERR = 902 )
137902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namlobsed in configuration namelist', lwp )
138      IF(lwm) WRITE ( numonp, namlobsed )
139
140      IF(lwp) THEN
141          WRITE(numout,*) ' Namelist namlobsed'
142          WRITE(numout,*) '    time coeff of POC in sediments                       sedlam    =', sedlam
143          WRITE(numout,*) '    Sediment geol loss for POC                           sedlostpoc=', sedlostpoc
144          WRITE(numout,*) '    detritus sedimentation speed                         vsed      =', 86400 * vsed  , ' d'
145          WRITE(numout,*) '    coeff for martin''s remineralistion                  xhr       =', xhr
146          WRITE(numout,*) ' '
147      ENDIF
148      !
149   END SUBROUTINE p2z_sed_init
150
151   !!======================================================================
152END MODULE  p2zsed
Note: See TracBrowser for help on using the repository browser.