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

source: branches/2017/dev_r7881_no_wrk_alloc/NEMOGCM/NEMO/TOP_SRC/PISCES/P2Z/p2zsed.F90 @ 7910

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

All wrk_alloc removed

  • 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   !!----------------------------------------------------------------------
37
38CONTAINS
39
40   SUBROUTINE p2z_sed( kt )
41      !!---------------------------------------------------------------------
42      !!                     ***  ROUTINE p2z_sed  ***
43      !!
44      !! ** Purpose :   compute the now trend due to the vertical sedimentation of
45      !!              detritus and add it to the general trend of detritus equations
46      !!
47      !! ** Method  :   this ROUTINE compute not exactly the advection but the
48      !!              transport term, i.e.  dz(wt) and dz(ws)., dz(wtr)
49      !!              using an upstream scheme
50      !!              the now vertical advection of tracers is given by:
51      !!                      dz(trn wn) = 1/bt dk+1( e1t e2t vsed (trn) )
52      !!              add this trend now to the general trend of tracer (ta,sa,tra):
53      !!                             tra = tra + dz(trn wn)
54      !!       
55      !!              IF 'key_diabio' is defined, the now vertical advection
56      !!              trend of passive tracers is saved for futher diagnostics.
57      !!---------------------------------------------------------------------
58      !!
59      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index     
60      !!
61      INTEGER  ::   ji, jj, jk, jl, ierr
62      CHARACTER (len=25) :: charout
63      REAL(wp), DIMENSION(jpi,jpj) :: zw2d
64      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zwork, ztra
65      !!---------------------------------------------------------------------
66      !
67      IF( nn_timing == 1 )  CALL timing_start('p2z_sed')
68      !
69      IF( kt == nittrc000 ) THEN
70         IF(lwp) WRITE(numout,*)
71         IF(lwp) WRITE(numout,*) ' p2z_sed: LOBSTER sedimentation'
72         IF(lwp) WRITE(numout,*) ' ~~~~~~~'
73      ENDIF
74
75      ! Allocate temporary workspace
76
77      ! sedimentation of detritus  : upstream scheme
78      ! --------------------------------------------
79
80      ! for detritus sedimentation only - jpdet
81      zwork(:,:,1  ) = 0.e0      ! surface value set to zero
82      zwork(:,:,jpk) = 0.e0      ! bottom value  set to zero
83
84      ! tracer flux at w-point: we use -vsed (downward flux)  with simplification : no e1*e2
85      DO jk = 2, jpkm1
86         zwork(:,:,jk) = -vsed * trn(:,:,jk-1,jpdet)
87      END DO
88
89      ! tracer flux divergence at t-point added to the general trend
90      DO jk = 1, jpkm1
91         DO jj = 1, jpj
92            DO ji = 1, jpi
93               ztra(ji,jj,jk)  = - ( zwork(ji,jj,jk) - zwork(ji,jj,jk+1) ) / e3t_n(ji,jj,jk)
94               tra(ji,jj,jk,jpdet) = tra(ji,jj,jk,jpdet) + ztra(ji,jj,jk) 
95            END DO
96         END DO
97      END DO
98
99      IF( lk_iomput )  THEN
100         IF( iom_use( "TDETSED" ) ) THEN
101            zw2d(:,:) =  ztra(:,:,1) * e3t_n(:,:,1) * 86400._wp
102            DO jk = 2, jpkm1
103               zw2d(:,:) = zw2d(:,:) + ztra(:,:,jk) * e3t_n(:,:,jk) * 86400._wp
104            END DO
105            CALL iom_put( "TDETSED", zw2d )
106         ENDIF
107      ENDIF
108      !
109      !
110
111      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
112         WRITE(charout, FMT="('sed')")
113         CALL prt_ctl_trc_info(charout)
114         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
115      ENDIF
116      !
117      IF( nn_timing == 1 )  CALL timing_stop('p2z_sed')
118      !
119   END SUBROUTINE p2z_sed
120
121   SUBROUTINE p2z_sed_init
122      !!----------------------------------------------------------------------
123      !!                  ***  ROUTINE p2z_sed_init  ***
124      !!
125      !! ** Purpose :   Parameters from aphotic layers to sediment
126      !!
127      !! ** Method  :   Read the namlobsed namelist and check the parameters
128      !!
129      !!----------------------------------------------------------------------
130      NAMELIST/namlobsed/ sedlam, sedlostpoc, vsed, xhr
131      INTEGER :: ios                 ! Local integer output status for namelist read
132
133      REWIND( numnatp_ref )              ! Namelist namlobsed in reference namelist : Lobster sediments
134      READ  ( numnatp_ref, namlobsed, IOSTAT = ios, ERR = 901)
135901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namlosed in reference namelist', lwp )
136
137      REWIND( numnatp_cfg )              ! Namelist namlobsed in configuration namelist : Lobster sediments
138      READ  ( numnatp_cfg, namlobsed, IOSTAT = ios, ERR = 902 )
139902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namlobsed in configuration namelist', lwp )
140      IF(lwm) WRITE ( numonp, namlobsed )
141
142      IF(lwp) THEN
143          WRITE(numout,*) ' Namelist namlobsed'
144          WRITE(numout,*) '    time coeff of POC in sediments                       sedlam    =', sedlam
145          WRITE(numout,*) '    Sediment geol loss for POC                           sedlostpoc=', sedlostpoc
146          WRITE(numout,*) '    detritus sedimentation speed                         vsed      =', 86400 * vsed  , ' d'
147          WRITE(numout,*) '    coeff for martin''s remineralistion                  xhr       =', xhr
148          WRITE(numout,*) ' '
149      ENDIF
150      !
151   END SUBROUTINE p2z_sed_init
152
153   !!======================================================================
154END MODULE  p2zsed
Note: See TracBrowser for help on using the repository browser.