MODULE trcini !!====================================================================== !! *** MODULE trcini *** !! TOP : Manage the passive tracer initialization !!====================================================================== !! History : - ! 1991-03 () original code !! 1.0 ! 2005-03 (O. Aumont, A. El Moussaoui) F90 !! - ! 2005-10 (C. Ethe) print control !! 2.0 ! 2005-10 (C. Ethe, G. Madec) revised architecture !!---------------------------------------------------------------------- #if defined key_top !!---------------------------------------------------------------------- !! 'key_top' TOP models !!---------------------------------------------------------------------- !!---------------------------------------------------------------------- !! trc_ini : Initialization for passive tracer !!---------------------------------------------------------------------- USE oce_trc USE trc USE trp_trc USE trcrst USE trcctl USE trclec USE trcini_cfc ! CFC initialisation USE trcini_lobster ! LOBSTER initialisation USE trcini_pisces ! PISCES initialisation USE trcini_c14b ! C14 bomb initialisation USE trcini_my_trc ! MY_TRC initialisation USE trcdta USE zpshde_trc ! partial step: hor. derivative USE in_out_manager ! I/O manager USE prtctl_trc ! Print control passive tracers (prt_ctl_trc_init routine) USE lib_mpp ! distributed memory computing library IMPLICIT NONE PRIVATE PUBLIC trc_ini ! called by opa !! * Substitutions # include "domzgr_substitute.h90" !!---------------------------------------------------------------------- !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005) !! $Id$ !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE trc_ini !!--------------------------------------------------------------------- !! *** ROUTINE trc_ini *** !! !! ** Purpose : Initialization of the passive tracer fields !! !! ** Method : - read namelist !! - control the consistancy !! - compute specific initialisations !! - set initial tracer fields (either read restart !! or read data or analytical formulation !!--------------------------------------------------------------------- INTEGER :: jk, jn ! dummy loop indices CHARACTER (len=25) :: charout !!--------------------------------------------------------------------- IF(lwp) WRITE(numout,*) IF(lwp) WRITE(numout,*) 'trc_ini : initial set up of the passive tracers' IF(lwp) WRITE(numout,*) '~~~~~~~' ! ! masked grid volume DO jk = 1, jpk cvol(:,:,jk) = e1t(:,:) * e2t(:,:) * fse3t(:,:,jk) * tmask(:,:,jk) * tmask_i(:,:) END DO ! total volume of the ocean #if ! defined key_off_degrad areatot = SUM( cvol(:,:,:) ) #else areatot = SUM( cvol(:,:,:) * facvol(:,:,:) ) ! degrad option: reduction by facvol #endif IF( lk_mpp ) CALL mpp_sum( areatot ) ! sum over the global domain CALL trc_lec ! READ passive tracers namelists CALL trc_ctl ! control consistency between parameters, cpp key IF( lk_lobster ) THEN ; CALL trc_ini_lobster ! LOBSTER bio-model ELSE ; IF(lwp) WRITE(numout,*) ' LOBSTER not used' ENDIF IF( lk_pisces ) THEN ; CALL trc_ini_pisces ! PISCES bio-model ELSE ; IF(lwp) WRITE(numout,*) ' PISCES not used' ENDIF IF( lk_cfc ) THEN ; CALL trc_ini_cfc ! CFC tracers ELSE ; IF(lwp) WRITE(numout,*) ' CFC not used' ENDIF IF( lk_c14b ) THEN ; CALL trc_ini_c14b ! C14 bomb tracer ELSE ; IF(lwp) WRITE(numout,*) ' C14 not used' ENDIF IF( lk_my_trc ) THEN ; CALL trc_ini_my_trc ! MY_TRC tracers ELSE ; IF(lwp) WRITE(numout,*) ' MY_TRC not used' ENDIF IF( .NOT. lrsttr ) THEN # if defined key_dtatrc ! Initialization of tracer from a file that may also be used for damping CALL trc_dta( nittrc000 ) DO jn = 1, jptra IF( lutini(jn) ) trn(:,:,:,jn) = trdta(:,:,:,jn) * tmask(:,:,:) ! initialisation from file if required END DO # endif trb(:,:,:,:) = trn(:,:,:,:) ELSE CALL trc_rst_read ! restart from a file ENDIF tra(:,:,:,:) = 0. IF( ln_zps .AND. .NOT. lk_trc_c1d ) & ! Partial steps: before horizontal gradient of passive & CALL zps_hde_trc( nittrc000, trb, gtru, gtrv ) ! tracers at the bottom ocean level ! ! Computation content of all tracers trai = 0.e0 DO jn = 1, jptra #if ! defined key_off_degrad trai = trai + SUM( trn(:,:,:,jn) * cvol(:,:,:) ) #else trai = trai + SUM( trn(:,:,:,jn) * cvol(:,:,:) * facvol(:,:,:) ) ! degrad option: reduction by facvol #endif END DO IF( lk_mpp ) CALL mpp_sum( trai ) ! sum over the global domain ! ! control print IF(lwp) WRITE(numout,*) ' *** Total number of passive tracer jptra = ', jptra IF(lwp) WRITE(numout,*) ' *** Total volume of ocean = ', areatot IF(lwp) WRITE(numout,*) ' *** Total inital content of all tracers = ', trai IF(lwp) WRITE(numout,*) IF( ln_ctl ) CALL prt_ctl_trc_init ! control print ! IF(ln_ctl) THEN ! print mean trends (used for debugging) WRITE(charout, FMT="('ini ')") CALL prt_ctl_trc_info( charout ) CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm ) ENDIF END SUBROUTINE trc_ini #else !!---------------------------------------------------------------------- !! Empty module : No passive tracer !!---------------------------------------------------------------------- CONTAINS SUBROUTINE trc_ini ! Dummy routine END SUBROUTINE trc_ini #endif !!====================================================================== END MODULE trcini