MODULE trcwri !!=================================================================================== !! *** MODULE trcwri *** !! TOP : Output of passive tracers !!==================================================================================== !! History : 1.0 ! 2009-05 (C. Ethe) Original code !! ! 2010-03 (C. Ethe, R. Seferian ) Add the tracer transport trends !!---------------------------------------------------------------------- #if defined key_top && defined key_iomput !!---------------------------------------------------------------------- !! 'key_top' && 'key_iomput' TOP models !!---------------------------------------------------------------------- !! trc_wri_trc : outputs of concentration fields !! trc_wri_trd : outputs of transport trends !!---------------------------------------------------------------------- USE dom_oce ! ocean space and time domain variables USE oce_trc USE trp_trc USE trc USE trdmld_trc_oce, ONLY : luttrd USE iom #if defined key_off_tra USE oce_trc USE dianam #endif IMPLICIT NONE PRIVATE PUBLIC trc_wri !! * Substitutions # include "top_substitute.h90" !!---------------------------------------------------------------------- !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005) !! $Id: trcdia.F90 1450 2009-05-15 14:12:12Z cetlod $ !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE trc_wri( kt ) !!--------------------------------------------------------------------- !! *** ROUTINE trc_wri *** !! !! ** Purpose : output passive tracers fields and dynamical trends !!--------------------------------------------------------------------- INTEGER, INTENT( in ) :: kt !!--------------------------------------------------------------------- ! CALL iom_setkt ( kt + ndttrc - 1 ) ! set the passive tracer time step CALL trc_wri_trc( kt ) ! outputs for tracer concentration CALL trc_wri_trd( kt ) ! outputs for dynamical trends CALL iom_setkt ( kt ) ! set the model time step ! END SUBROUTINE trc_wri SUBROUTINE trc_wri_trc( kt ) !!--------------------------------------------------------------------- !! *** ROUTINE trc_wri_trc *** !! !! ** Purpose : output passive tracers fields !!--------------------------------------------------------------------- INTEGER, INTENT( in ) :: kt ! ocean time-step INTEGER :: jn CHARACTER (len=20) :: cltra, cltras #if defined key_off_tra CHARACTER (len=40) :: clhstnam INTEGER :: inum = 11 ! temporary logical unit #endif #if defined key_diaar5 && defined key_pisces INTEGER :: ji, jj, jk ! dummy loop indices REAL(wp) :: zoxy ! oxygen concentration REAL(wp), DIMENSION(jpi,jpj) :: zdic ! DIC content REAL(wp), DIMENSION(jpi,jpj) :: zo2min ! O2 minimum concentration REAL(wp), DIMENSION(jpi,jpj) :: zdepo2min ! Depth of O2 minimum concentration #endif !!--------------------------------------------------------------------- #if defined key_off_tra IF( kt == nittrc000 ) THEN ! WRITE root name in date.file for use by postpro IF(lwp) THEN CALL dia_nam( clhstnam, nwritetrc,' ' ) CALL ctl_opn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) WRITE(inum,*) clhstnam CLOSE(inum) ENDIF ENDIF #endif ! write the tracer concentrations in the file ! --------------------------------------- DO jn = 1, jptra cltra = ctrcnm(jn) ! short title for tracer CALL iom_put( cltra, trn(:,:,:,jn) ) END DO #if defined key_diaar5 && defined key_pisces ! DIC content in kg/m2 zdic(:,:) = 0. DO jk = 1, jpkm1 zdic(:,:) = zdic(:,:) + trn(:,:,jk,jpdic) * fse3t(:,:,jk) * tmask(:,:,jk) * 12. ENDDO ! Oxygen minimum concentration and depth zo2min (:,:) = trn(:,:,1,jpoxy) * tmask(:,:,1) zdepo2min(:,:) = fsdepw(:,:,1) * tmask(:,:,1) DO jk = 2, jpkm1 DO jj = 1, jpj DO ji = 1, jpi IF( tmask(ji,jj,jk) == 1 ) then IF( trn(ji,jj,jk,jpoxy) < zo2min(ji,jj) ) then zo2min (ji,jj) = trn(ji,jj,jk,jpoxy) zdepo2min(ji,jj) = fsdepw(ji,jj,jk) ENDIF ENDIF END DO END DO END DO ! CALL iom_put('INTDIC', zdic ) ! DIC content CALL iom_put('O2MIN' , zo2min ) ! oxygen minimum concentration CALL iom_put('ZO2MIN', zdepo2min ) ! depth of oxygen minimum concentration CALL iom_put('PHYT' , trn(:,:,:,jpphy) + trn(:,:,:,jpdia) ) ! total phytoplankton CALL iom_put('ZOOT' , trn(:,:,:,jpzoo) + trn(:,:,:,jpmes) ) ! total zooplankton CALL iom_put('CHLT' , trn(:,:,:,jpnch) + trn(:,:,:,jpdch) ) ! total chlorophyll CALL iom_put('POCT' , trn(:,:,:,jppoc) + trn(:,:,:,jpgoc) ) ! total carbon particles CALL iom_put('PFET' , trn(:,:,:,jpnfe) + trn(:,:,:,jpdfe) ) ! total biogenic iron ! passive tracers at surface DO jn = 1, jptra cltras = TRIM(ctrcnm(jn))//'SFC' ! short title for tracer CALL iom_put( cltras, trn(:,:,1,jn) ) END DO CALL iom_put('PHYTSFC',trn(:,:,1,jpphy) + trn(:,:,1,jpdia) ) CALL iom_put('ZOOTSFC',trn(:,:,1,jpzoo) + trn(:,:,1,jpmes) ) CALL iom_put('CHLTSFC',trn(:,:,1,jpnch) + trn(:,:,1,jpdch) ) CALL iom_put('POCTSFC',trn(:,:,1,jppoc) + trn(:,:,1,jpgoc) ) CALL iom_put('PFETSFC',trn(:,:,1,jpnfe) + trn(:,:,1,jpdfe) ) #endif ! END SUBROUTINE trc_wri_trc # if defined key_trc_diatrd SUBROUTINE trc_wri_trd( kt ) !!---------------------------------------------------------------------- !! *** ROUTINE trc_wri_trd *** !! !! ** Purpose : output of passive tracer : advection-diffusion trends !! !!---------------------------------------------------------------------- INTEGER, INTENT( in ) :: kt ! ocean time-step !! CHARACTER (len=3) :: cltra INTEGER :: jn, jl, ikn !!---------------------------------------------------------------------- DO jn = 1, jptra IF( luttrd(jn) ) THEN ikn = ikeep(jn) DO jl = 1, jpdiatrc IF( jl == jptrc_xad ) WRITE (cltra,"(3a)") 'XAD' ! x advection for tracer IF( jl == jptrc_yad ) WRITE (cltra,"(3a)") 'YAD' ! y advection for tracer IF( jl == jptrc_zad ) WRITE (cltra,"(3a)") 'ZAD' ! z advection for tracer IF( jl == jptrc_xdf ) WRITE (cltra,"(3a)") 'XDF' ! x diffusion for tracer IF( jl == jptrc_ydf ) WRITE (cltra,"(3a)") 'YDF' ! y diffusion for tracer IF( jl == jptrc_zdf ) WRITE (cltra,"(3a)") 'ZDF' ! z diffusion for tracer # if defined key_trcldf_eiv IF( jl == jptrc_xei ) WRITE (cltra,"(3a)") 'XGV' ! x gent velocity for tracer IF( jl == jptrc_yei ) WRITE (cltra,"(3a)") 'YGV' ! y gent velocity for tracer IF( jl == jptrc_zei ) WRITE (cltra,"(3a)") 'ZGV' ! z gent velocity for tracer # endif # if defined key_trcdmp IF( jl == jptrc_dmp ) WRITE (cltra,"(3a)") 'DMP' ! damping # endif IF( jl == jptrc_sbc ) WRITE (cltra,"(3a)") 'SBC' ! surface boundary conditions ! write the trends CALL iom_put( cltra, trtrd(:,:,:,ikn,jl) ) END DO END IF END DO ! END SUBROUTINE trc_wri_trd # else SUBROUTINE trc_wri_trd( kt ) ! Dummy routine INTEGER, INTENT ( in ) :: kt END SUBROUTINE trc_wri_trd #endif #else !!---------------------------------------------------------------------- !! Dummy module : No passive tracer !!---------------------------------------------------------------------- PUBLIC trc_wri CONTAINS SUBROUTINE trc_wri( kt ) ! Empty routine INTEGER, INTENT(in) :: kt END SUBROUTINE trc_wri #endif !!====================================================================== END MODULE trcwri