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_r2006_merge_TRA_TRC/NEMO/TOP_SRC/LOBSTER – NEMO

source: branches/DEV_r2006_merge_TRA_TRC/NEMO/TOP_SRC/LOBSTER/trcsed.F90 @ 2082

Last change on this file since 2082 was 2082, checked in by cetlod, 14 years ago

Improve the merge of TRA-TRC, see ticket #717

  • Property svn:keywords set to Id
File size: 6.0 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 trc
18   USE sms_lobster
19   USE lbclnk
20   USE trdmod_trc
21   USE iom
22   USE prtctl_trc      ! Print control for debbuging
23
24   IMPLICIT NONE
25   PRIVATE
26
27   PUBLIC   trc_sed    ! called in ???
28
29   !!* Substitution
30#  include "top_substitute.h90"
31   !!----------------------------------------------------------------------
32   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
33   !! $Id$
34   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
35   !!----------------------------------------------------------------------
36
37CONTAINS
38
39   SUBROUTINE trc_sed( kt )
40      !!---------------------------------------------------------------------
41      !!                     ***  ROUTINE trc_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
60      REAL(wp) ::   ztra
61      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zwork
62#if defined key_diatrc && defined key_iomput
63      REAL(wp), DIMENSION(jpi,jpj) ::  zw2d
64#endif
65      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   ztrbio
66      CHARACTER (len=25) :: charout
67      !!---------------------------------------------------------------------
68
69      IF( kt == nittrc000 ) THEN
70         IF(lwp) WRITE(numout,*)
71         IF(lwp) WRITE(numout,*) ' trc_sed: LOBSTER sedimentation'
72         IF(lwp) WRITE(numout,*) ' ~~~~~~~'
73      ENDIF
74
75      ! sedimentation of detritus  : upstream scheme
76      ! --------------------------------------------
77
78      ! for detritus sedimentation only - jp_lob_det
79      zwork(:,:,1  ) = 0.e0      ! surface value set to zero
80      zwork(:,:,jpk) = 0.e0      ! bottom value  set to zero
81
82#if defined key_diatrc && defined key_iomput
83      zw2d(:,:) = 0.
84# endif
85
86      IF( l_trdtrc )THEN
87         ALLOCATE( ztrbio(jpi,jpj,jpk) )
88         ztrbio(:,:,:) = tra(:,:,:,jp_lob_det)
89      ENDIF
90
91      ! tracer flux at w-point: we use -vsed (downward flux)  with simplification : no e1*e2
92      DO jk = 2, jpkm1
93         zwork(:,:,jk) = -vsed * trn(:,:,jk-1,jp_lob_det)
94      END DO
95
96      ! tracer flux divergence at t-point added to the general trend
97      DO jk = 1, jpkm1
98         DO jj = 1, jpj
99            DO ji = 1,jpi
100               ztra  = - ( zwork(ji,jj,jk) - zwork(ji,jj,jk+1) ) / fse3t(ji,jj,jk)
101               tra(ji,jj,jk,jp_lob_det) = tra(ji,jj,jk,jp_lob_det) + ztra
102#if defined key_diabio
103               trbio(ji,jj,jk,jp_lob0_trd + 7) = ztra
104#endif
105#if defined key_diatrc
106# if ! defined key_iomput
107               trc2d(ji,jj,jp_lob0_2d + 7) = trc2d(ji,jj,jp_lob0_2d + 7) + ztra * fse3t(ji,jj,jk) * 86400.
108# else
109               zw2d(ji,jj) = zw2d(ji,jj) + ztra * fse3t(ji,jj,jk) * 86400.
110# endif
111#endif
112            END DO
113         END DO
114      END DO
115
116#if defined key_diabio
117      jl = jp_lob0_trd + 7
118      CALL lbc_lnk (trbio(:,:,1,jl), 'T', 1. )    ! Lateral boundary conditions on trcbio
119#endif
120#if defined key_diatrc
121# if ! defined key_iomput
122      jl = jp_lob0_2d + 7
123      CALL lbc_lnk( trc2d(:,:,jl), 'T', 1. )      ! Lateral boundary conditions on trc2d
124# else
125      CALL lbc_lnk( zw2d(:,:), 'T', 1. )      ! Lateral boundary conditions on zw2d
126      CALL iom_put( "TDETSED", zw2d )
127# endif
128#endif
129      !
130
131      IF( l_trdtrc ) THEN
132         ztrbio(:,:,:) = tra(:,:,:,jp_lob_det) - ztrbio(:,:,:)
133         jl = jp_lob0_trd + 7
134         CALL trd_mod_trc( ztrbio, jl, kt )   ! handle the trend
135      ENDIF
136
137      IF( l_trdtrc ) DEALLOCATE( ztrbio )
138
139      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
140         WRITE(charout, FMT="('sed')")
141         CALL prt_ctl_trc_info(charout)
142         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
143      ENDIF
144
145   END SUBROUTINE trc_sed
146
147#else
148   !!======================================================================
149   !!  Dummy module :                                   No PISCES bio-model
150   !!======================================================================
151CONTAINS
152   SUBROUTINE trc_sed( kt )                   ! Empty routine
153      INTEGER, INTENT( in ) ::   kt
154      WRITE(*,*) 'trc_sed: You should not have seen this print! error?', kt
155   END SUBROUTINE trc_sed
156#endif 
157
158   !!======================================================================
159END MODULE  trcsed
Note: See TracBrowser for help on using the repository browser.