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.
trcsed.F90 in branches/dev_001_GM/NEMO/TOP_SRC/LOBSTER – NEMO

source: branches/dev_001_GM/NEMO/TOP_SRC/LOBSTER/trcsed.F90 @ 2793

Last change on this file since 2793 was 790, checked in by gm, 16 years ago

dev_001_GM - complete theprevious comit with omitted routines

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 4.7 KB
Line 
1MODULE trcsed
2   !!======================================================================
3   !!                         ***  MODULE p4sed  ***
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_lobster
11   !!----------------------------------------------------------------------
12   !!   'key_lobster'                                     LOBSTER bio-model
13   !!----------------------------------------------------------------------
14   !!   trc_sed        :  Compute loss of organic matter in the sediments
15   !!----------------------------------------------------------------------
16   USE oce_trc         !
17   USE trp_trc
18   USE sms
19   USE lbclnk
20
21   IMPLICIT NONE
22   PRIVATE
23
24   PUBLIC   trc_sed    ! called in ???
25
26   !!* Substitution
27#  include "domzgr_substitute.h90"
28   !!----------------------------------------------------------------------
29   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
30   !! $Id$
31   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
32   !!----------------------------------------------------------------------
33
34CONTAINS
35
36   SUBROUTINE trc_sed( kt )
37      !!---------------------------------------------------------------------
38      !!                     ***  ROUTINE trc_sed  ***
39      !!
40      !! ** Purpose :   compute the now trend due to the vertical sedimentation of
41      !!              detritus and add it to the general trend of detritus equations
42      !!
43      !! ** Method  :   this ROUTINE compute not exactly the advection but the
44      !!              transport term, i.e.  dz(wt) and dz(ws)., dz(wtr)
45      !!              using an upstream scheme
46      !!              the now vertical advection of tracers is given by:
47      !!                      dz(trn wn) = 1/bt dk+1( e1t e2t vsed (trn) )
48      !!              add this trend now to the general trend of tracer (ta,sa,tra):
49      !!                             tra = tra + dz(trn wn)
50      !!       
51      !!              IF 'key_trc_diabio' is defined, the now vertical advection
52      !!              trend of passive tracers is saved for futher diagnostics.
53      !!---------------------------------------------------------------------
54      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index     
55      !!
56      INTEGER  ::   ji, jj, jk
57      REAL(wp) ::   ztra
58      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zwork
59      !!---------------------------------------------------------------------
60
61      IF( kt == nit000 ) THEN
62         IF(lwp) WRITE(numout,*)
63         IF(lwp) WRITE(numout,*) ' trc_sed: LOBSTER sedimentation'
64         IF(lwp) WRITE(numout,*) ' ~~~~~~~'
65      ENDIF
66
67      ! sedimentation of detritus  : upstream scheme
68      ! --------------------------------------------
69
70      ! for detritus sedimentation only - jpdet
71
72      zwork(:,:,1  ) = 0.e0      ! surface value set to zero
73      zwork(:,:,jpk) = 0.e0      ! bottom value  set to zero
74
75      ! tracer flux at w-point: we use -vsed (downward flux)  with simplification : no e1*e2
76
77      DO jk = 2, jpkm1
78         zwork(:,:,jk) = -vsed * trn(:,:,jk-1,jpdet)
79      END DO
80
81      ! tracer flux divergence at t-point added to the general trend
82
83      DO jk = 1, jpkm1
84         DO jj = 1, jpj
85            DO ji = 1,jpi
86               ztra  = - ( zwork(ji,jj,jk) - zwork(ji,jj,jk+1) ) / fse3t(ji,jj,jk)
87               tra(ji,jj,jk,jpdet) = tra(ji,jj,jk,jpdet) + ztra
88# if defined key_trc_diabio
89               trbio(ji,jj,jk,8) = ztra
90# endif
91# if defined key_trc_diaadd
92!!gm  bug introduced: no more mask below jpkb !
93               trc2d(ji,jj,8) = trc2d(ji,jj,8) + ztra * fse3t(ji,jj,jk) * 86400.
94# endif
95            END DO
96         END DO
97      END DO
98
99#if defined key_trc_diabio
100      CALL lbc_lnk( trbio(:,:,1,8), 'T', 1. )    ! Lateral boundary conditions on trcbio
101#endif
102#if defined key_trc_diaadd
103      CALL lbc_lnk( trc2d(:,:,8), 'T', 1. )      ! Lateral boundary conditions on trc2d
104#endif
105      !
106   END SUBROUTINE trc_sed
107
108#else
109   !!======================================================================
110   !!  Dummy module :                                   No PISCES bio-model
111   !!======================================================================
112CONTAINS
113   SUBROUTINE trc_sed( kt )                   ! Empty routine
114      INTEGER, INTENT( in ) ::   kt
115      WRITE(*,*) 'trc_sed: You should not have seen this print! error?', kt
116   END SUBROUTINE trc_sed
117#endif 
118
119   !!======================================================================
120END MODULE  trcsed
Note: See TracBrowser for help on using the repository browser.