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/2011/dev_r2787_LOCEAN3_TRA_TRP/NEMOGCM/NEMO/TOP_SRC/LOBSTER – NEMO

source: branches/2011/dev_r2787_LOCEAN3_TRA_TRP/NEMOGCM/NEMO/TOP_SRC/LOBSTER/trcsed.F90 @ 2819

Last change on this file since 2819 was 2819, checked in by cetlod, 13 years ago

Improvment of branch dev_r2787_LOCEAN3_TRA_TRP

  • Property svn:keywords set to Id
File size: 6.1 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_oce
21   USE trdmod_trc
22   USE iom
23   USE prtctl_trc      ! Print control for debbuging
24
25   IMPLICIT NONE
26   PRIVATE
27
28   PUBLIC   trc_sed    ! called in ???
29
30   !!* Substitution
31#  include "top_substitute.h90"
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 trc_sed( kt )
41      !!---------------------------------------------------------------------
42      !!                     ***  ROUTINE trc_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      USE wrk_nemo, ONLY: wrk_in_use, wrk_not_released
59      USE wrk_nemo, ONLY: zw2d  => wrk_2d_1, zwork => wrk_3d_2
60      !!
61      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index     
62      !!
63      INTEGER  ::   ji, jj, jk, jl, ierr
64      REAL(wp) ::   ztra, ze3t
65      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  ztrbio
66      CHARACTER (len=25) :: charout
67      !!---------------------------------------------------------------------
68
69      IF( kt == nit000 ) THEN
70         IF(lwp) WRITE(numout,*)
71         IF(lwp) WRITE(numout,*) ' trc_sed: LOBSTER sedimentation'
72         IF(lwp) WRITE(numout,*) ' ~~~~~~~'
73      ENDIF
74
75      IF( wrk_in_use(2, 1) .OR. wrk_in_use(3, 2) ) THEN
76         CALL ctl_stop('trc_sed : requested workspace arrays unavailable.')  ;  RETURN
77      END IF
78
79      IF( l_trdtrc )  THEN
80         ALLOCATE( ztrbio(jpi,jpj,jpk) , STAT = ierr )   ! temporary save of trends
81         IF( ierr > 0 ) THEN
82            CALL ctl_stop( 'trc_sed: unable to allocate ztrbio array' )   ;   RETURN
83         ENDIF
84         ztrbio(:,:,:) = tra(:,:,:,jp_lob_det)
85      ENDIF
86
87      IF( ln_diatrc .AND. lk_iomput )  zw2d(:,:) = 0.
88
89      ! sedimentation of detritus  : upstream scheme
90      ! --------------------------------------------
91
92      ! for detritus sedimentation only - jp_lob_det
93      zwork(:,:,1  ) = 0.e0      ! surface value set to zero
94      zwork(:,:,jpk) = 0.e0      ! bottom value  set to zero
95
96      ! tracer flux at w-point: we use -vsed (downward flux)  with simplification : no e1*e2
97      DO jk = 2, jpkm1
98         zwork(:,:,jk) = -vsed * trn(:,:,jk-1,jp_lob_det)
99      END DO
100
101      ! tracer flux divergence at t-point added to the general trend
102      DO jk = 1, jpkm1
103         DO jj = 1, jpj
104            DO ji = 1, jpi
105               ztra  = - ( zwork(ji,jj,jk) - zwork(ji,jj,jk+1) ) / fse3t(ji,jj,jk)
106               tra(ji,jj,jk,jp_lob_det) = tra(ji,jj,jk,jp_lob_det) + ztra
107               !
108               IF( ln_diabio )  trbio(ji,jj,jk,jp_lob0_trd + 7) = ztra
109               IF( ln_diatrc ) THEN
110                  ze3t = ztra * fse3t(ji,jj,jk) * 86400.
111                  IF( lk_iomput ) THEN   ;  zw2d(ji,jj) = zw2d(ji,jj) + ze3t 
112                  ELSE                   ;  trc2d(ji,jj,jp_lob0_2d + 7) = trc2d(ji,jj,jp_lob0_2d + 7) + ze3t
113                  ENDIF
114               ENDIF
115               !
116            END DO
117         END DO
118      END DO
119
120      IF( ln_diatrc .AND. lk_iomput )  CALL iom_put( "TDETSED", zw2d )
121
122      IF( l_trdtrc ) THEN
123         ztrbio(:,:,:) = tra(:,:,:,jp_lob_det) - ztrbio(:,:,:)
124         jl = jp_lob0_trd + 7
125         CALL trd_mod_trc( ztrbio, jl, kt )   ! handle the trend
126         DEALLOCATE( ztrbio ) 
127      ENDIF
128
129      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
130         WRITE(charout, FMT="('sed')")
131         CALL prt_ctl_trc_info(charout)
132         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
133      ENDIF
134
135      IF( ( wrk_not_released(2, 1) ) .OR. ( wrk_not_released(3, 2) ) )  &
136       &         CALL ctl_stop('trc_sed : failed to release workspace arrays.')
137
138   END SUBROUTINE trc_sed
139
140#else
141   !!======================================================================
142   !!  Dummy module :                                   No PISCES bio-model
143   !!======================================================================
144CONTAINS
145   SUBROUTINE trc_sed( kt )                   ! Empty routine
146      INTEGER, INTENT( in ) ::   kt
147      WRITE(*,*) 'trc_sed: You should not have seen this print! error?', kt
148   END SUBROUTINE trc_sed
149#endif 
150
151   !!======================================================================
152END MODULE  trcsed
Note: See TracBrowser for help on using the repository browser.