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 @ 9124

Last change on this file since 9124 was 9124, checked in by gm, 6 years ago

dev_merge_2017: ln_timing instead of nn_timing + restricted timing to nemo_init and routine called by step in OPA_SRC

  • Property svn:keywords set to Id
File size: 6.6 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), POINTER, DIMENSION(:,:  ) :: zw2d
62      REAL(wp), POINTER, DIMENSION(:,:,:) :: 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      ! Allocate temporary workspace
74      CALL wrk_alloc( jpi, jpj, jpk, zwork, ztra )
75
76      ! sedimentation of detritus  : upstream scheme
77      ! --------------------------------------------
78
79      ! for detritus sedimentation only - jpdet
80      zwork(:,:,1  ) = 0.e0      ! surface value set to zero
81      zwork(:,:,jpk) = 0.e0      ! bottom value  set to zero
82
83      ! tracer flux at w-point: we use -vsed (downward flux)  with simplification : no e1*e2
84      DO jk = 2, jpkm1
85         zwork(:,:,jk) = -vsed * trn(:,:,jk-1,jpdet)
86      END DO
87
88      ! tracer flux divergence at t-point added to the general trend
89      DO jk = 1, jpkm1
90         DO jj = 1, jpj
91            DO ji = 1, jpi
92               ztra(ji,jj,jk)  = - ( zwork(ji,jj,jk) - zwork(ji,jj,jk+1) ) / e3t_n(ji,jj,jk)
93               tra(ji,jj,jk,jpdet) = tra(ji,jj,jk,jpdet) + ztra(ji,jj,jk) 
94            END DO
95         END DO
96      END DO
97
98      IF( lk_iomput )  THEN
99         IF( iom_use( "TDETSED" ) ) THEN
100            CALL wrk_alloc( jpi, jpj, zw2d )
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            CALL wrk_dealloc( jpi, jpj, zw2d )
107         ENDIF
108      ENDIF
109      !
110      CALL wrk_dealloc( jpi, jpj, jpk, zwork, ztra )
111      !
112
113      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
114         WRITE(charout, FMT="('sed')")
115         CALL prt_ctl_trc_info(charout)
116         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
117      ENDIF
118      !
119      IF( ln_timing )   CALL timing_stop('p2z_sed')
120      !
121   END SUBROUTINE p2z_sed
122
123
124   SUBROUTINE p2z_sed_init
125      !!----------------------------------------------------------------------
126      !!                  ***  ROUTINE p2z_sed_init  ***
127      !!
128      !! ** Purpose :   Parameters from aphotic layers to sediment
129      !!
130      !! ** Method  :   Read the namlobsed namelist and check the parameters
131      !!
132      !!----------------------------------------------------------------------
133      NAMELIST/namlobsed/ sedlam, sedlostpoc, vsed, xhr
134      INTEGER :: ios                 ! Local integer output status for namelist read
135
136      REWIND( numnatp_ref )              ! Namelist namlobsed in reference namelist : Lobster sediments
137      READ  ( numnatp_ref, namlobsed, IOSTAT = ios, ERR = 901)
138901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namlosed in reference namelist', lwp )
139
140      REWIND( numnatp_cfg )              ! Namelist namlobsed in configuration namelist : Lobster sediments
141      READ  ( numnatp_cfg, namlobsed, IOSTAT = ios, ERR = 902 )
142902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namlobsed in configuration namelist', lwp )
143      IF(lwm) WRITE ( numonp, namlobsed )
144
145      IF(lwp) THEN
146          WRITE(numout,*) ' Namelist namlobsed'
147          WRITE(numout,*) '    time coeff of POC in sediments                       sedlam    =', sedlam
148          WRITE(numout,*) '    Sediment geol loss for POC                           sedlostpoc=', sedlostpoc
149          WRITE(numout,*) '    detritus sedimentation speed                         vsed      =', 86400 * vsed  , ' d'
150          WRITE(numout,*) '    coeff for martin''s remineralistion                  xhr       =', xhr
151          WRITE(numout,*) ' '
152      ENDIF
153      !
154   END SUBROUTINE p2z_sed_init
155
156   !!======================================================================
157END MODULE  p2zsed
Note: See TracBrowser for help on using the repository browser.