MODULE trcsed !!====================================================================== !! *** MODULE p4sed *** !! TOP : PISCES Compute loss of organic matter in the sediments !!====================================================================== !! History : - ! 1995-06 (M. Levy) original code !! - ! 2000-12 (E. Kestenare) clean up !! 2.0 ! 2007-12 (C. Deltel, G. Madec) F90 + simplifications !!---------------------------------------------------------------------- #if defined key_lobster !!---------------------------------------------------------------------- !! 'key_lobster' LOBSTER bio-model !!---------------------------------------------------------------------- !! trc_sed : Compute loss of organic matter in the sediments !!---------------------------------------------------------------------- USE oce_trc ! USE trp_trc USE sms USE lbclnk IMPLICIT NONE PRIVATE PUBLIC trc_sed ! called in ??? !!* Substitution # include "domzgr_substitute.h90" !!---------------------------------------------------------------------- !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007) !! $Id$ !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE trc_sed( kt ) !!--------------------------------------------------------------------- !! *** ROUTINE trc_sed *** !! !! ** Purpose : compute the now trend due to the vertical sedimentation of !! detritus and add it to the general trend of detritus equations !! !! ** Method : this ROUTINE compute not exactly the advection but the !! transport term, i.e. dz(wt) and dz(ws)., dz(wtr) !! using an upstream scheme !! the now vertical advection of tracers is given by: !! dz(trn wn) = 1/bt dk+1( e1t e2t vsed (trn) ) !! add this trend now to the general trend of tracer (ta,sa,tra): !! tra = tra + dz(trn wn) !! !! IF 'key_trc_diabio' is defined, the now vertical advection !! trend of passive tracers is saved for futher diagnostics. !!--------------------------------------------------------------------- INTEGER, INTENT( in ) :: kt ! ocean time-step index !! INTEGER :: ji, jj, jk REAL(wp) :: ztra REAL(wp), DIMENSION(jpi,jpj,jpk) :: zwork !!--------------------------------------------------------------------- IF( kt == nit000 ) THEN IF(lwp) WRITE(numout,*) IF(lwp) WRITE(numout,*) ' trc_sed: LOBSTER sedimentation' IF(lwp) WRITE(numout,*) ' ~~~~~~~' ENDIF ! sedimentation of detritus : upstream scheme ! -------------------------------------------- ! for detritus sedimentation only - jpdet zwork(:,:,1 ) = 0.e0 ! surface value set to zero zwork(:,:,jpk) = 0.e0 ! bottom value set to zero ! tracer flux at w-point: we use -vsed (downward flux) with simplification : no e1*e2 DO jk = 2, jpkm1 zwork(:,:,jk) = -vsed * trn(:,:,jk-1,jpdet) END DO ! tracer flux divergence at t-point added to the general trend DO jk = 1, jpkm1 DO jj = 1, jpj DO ji = 1,jpi ztra = - ( zwork(ji,jj,jk) - zwork(ji,jj,jk+1) ) / fse3t(ji,jj,jk) tra(ji,jj,jk,jpdet) = tra(ji,jj,jk,jpdet) + ztra # if defined key_trc_diabio trbio(ji,jj,jk,8) = ztra # endif # if defined key_trc_diaadd !!gm bug introduced: no more mask below jpkb ! trc2d(ji,jj,8) = trc2d(ji,jj,8) + ztra * fse3t(ji,jj,jk) * 86400. # endif END DO END DO END DO #if defined key_trc_diabio CALL lbc_lnk( trbio(:,:,1,8), 'T', 1. ) ! Lateral boundary conditions on trcbio #endif #if defined key_trc_diaadd CALL lbc_lnk( trc2d(:,:,8), 'T', 1. ) ! Lateral boundary conditions on trc2d #endif ! END SUBROUTINE trc_sed #else !!====================================================================== !! Dummy module : No PISCES bio-model !!====================================================================== CONTAINS SUBROUTINE trc_sed( kt ) ! Empty routine INTEGER, INTENT( in ) :: kt WRITE(*,*) 'trc_sed: You should not have seen this print! error?', kt END SUBROUTINE trc_sed #endif !!====================================================================== END MODULE trcsed