MODULE trc !!====================================================================== !! *** MODULE trc *** !! Passive tracers : module for tracers defined !!====================================================================== !! History : OPA ! 1996-01 (M. Levy) Original code !! - ! 1999-07 (M. Levy) for LOBSTER1 or NPZD model !! - ! 2000-04 (O. Aumont, M.A. Foujols) HAMOCC3 and P3ZD !! NEMO 1.0 ! 2004-03 (C. Ethe) Free form and module !!---------------------------------------------------------------------- #if defined key_top !!---------------------------------------------------------------------- !! 'key_top' TOP models !!---------------------------------------------------------------------- USE par_oce USE par_trc IMPLICIT NONE PUBLIC PUBLIC trc_alloc ! called by nemogcm.F90 !! passive tracers names and units (read in namelist) !! -------------------------------------------------- CHARACTER(len=12), PUBLIC, DIMENSION(jptra) :: ctrcnm !: tracer name CHARACTER(len=12), PUBLIC, DIMENSION(jptra) :: ctrcun !: tracer unit CHARACTER(len=80), PUBLIC, DIMENSION(jptra) :: ctrcnl !: tracer long name !! parameters for the control of passive tracers !! -------------------------------------------------- INTEGER, PUBLIC :: numnat !: the number of the passive tracer NAMELIST LOGICAL, PUBLIC, DIMENSION(jptra) :: lutini !: initialisation from FILE or not (NAMELIST) LOGICAL, PUBLIC, DIMENSION(jptra) :: lutsav !: save the tracer or not !! passive tracers fields (before,now,after) !! -------------------------------------------------- REAL(wp), PUBLIC :: trai !: initial total tracer REAL(wp), PUBLIC :: areatot !: total volume REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: cvol !: volume correction -degrad option- REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:,:) :: trn !: traceur concentration for now time step REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:,:) :: tra !: traceur concentration for next time step REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:,:) :: trb !: traceur concentration for before time step !! interpolated gradient !!-------------------------------------------------- REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: gtru !: hor. gradient at u-points at bottom ocean level REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: gtrv !: hor. gradient at v-points at bottom ocean level !! passive tracers restart (input and output) !! ------------------------------------------ LOGICAL , PUBLIC :: ln_rsttr !: boolean term for restart i/o for passive tracers (namelist) LOGICAL , PUBLIC :: lrst_trc !: logical to control the trc restart write INTEGER , PUBLIC :: nn_dttrc !: frequency of step on passive tracers INTEGER , PUBLIC :: nutwrs !: output FILE for passive tracers restart INTEGER , PUBLIC :: nutrst !: logical unit for restart FILE for passive tracers INTEGER , PUBLIC :: nn_rsttr !: control of the time step ( 0 or 1 ) for pass. tr. CHARACTER(len=50), PUBLIC :: cn_trcrst_in !: suffix of pass. tracer restart name (input) CHARACTER(len=50), PUBLIC :: cn_trcrst_out !: suffix of pass. tracer restart name (output) INTEGER , PUBLIC :: nittrc000 !: first time step of passive tracers model !! information for outputs !! -------------------------------------------------- INTEGER , PUBLIC :: nn_writetrc !: time step frequency for concentration outputs (namelist) REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: rdttrc !: vertical profile of passive tracer time step # if defined key_diatrc && ! defined key_iomput !! additional 2D/3D outputs namelist !! -------------------------------------------------- INTEGER , PUBLIC :: nn_writedia !: frequency of additional arrays outputs(namelist) CHARACTER(len= 8), PUBLIC, DIMENSION(jpdia2d) :: ctrc2d !: 2d output field name CHARACTER(len= 8), PUBLIC, DIMENSION(jpdia2d) :: ctrc2u !: 2d output field unit CHARACTER(len= 8), PUBLIC, DIMENSION(jpdia3d) :: ctrc3d !: 3d output field name CHARACTER(len= 8), PUBLIC, DIMENSION(jpdia3d) :: ctrc3u !: 3d output field unit CHARACTER(len=80), PUBLIC, DIMENSION(jpdia2d) :: ctrc2l !: 2d output field long name CHARACTER(len=80), PUBLIC, DIMENSION(jpdia3d) :: ctrc3l !: 3d output field long name REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:, :) :: trc2d !: additional 2d outputs REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) :: trc3d !: additional 3d outputs # endif # if defined key_diabio || defined key_trdmld_trc ! !!* namtop_XXX namelist * INTEGER , PUBLIC :: nn_writebio !: time step frequency for biological outputs CHARACTER(len=8 ), PUBLIC, DIMENSION(jpdiabio) :: ctrbio !: biological trends name CHARACTER(len=20), PUBLIC, DIMENSION(jpdiabio) :: ctrbiu !: biological trends unit CHARACTER(len=80), PUBLIC, DIMENSION(jpdiabio) :: ctrbil !: biological trends long name # endif # if defined key_diabio !! Biological trends !! ----------------- REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) :: trbio !: biological trends # endif !! passive tracers data read and at given time_step !! -------------------------------------------------- # if defined key_dtatrc INTEGER , PUBLIC, DIMENSION(jptra) :: numtr !: logical unit for passive tracers data # endif !! variables to average over physics over passive tracer sub-steps. !! ---------------------------------------------------------------- REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: un_tm !: i-horizontal velocity average [m/s] REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: vn_tm !: j-horizontal velocity average [m/s] REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: wn_tm !: k-vertical velocity average [m/s] REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: avt_tm !: vertical viscosity & diffusivity coeff. at w-point [m2/s] REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) :: sshn_tm !: average ssh for the now step [m] REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) :: sshb_hold !:hold sshb from the beginning of each sub-stepping[m] REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) :: sshu_n_tm !: average ssh for the now step [m] REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) :: sshu_b_hold !:hold sshb from the beginning of each sub-stepping[m] REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) :: sshv_n_tm !: average ssh for the now step [m] REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) :: sshv_b_hold !:hold sshb from the beginning of each sub-stepping[m] #if defined key_ldfslp REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: wslpi_tm !: i-direction slope at u-, w-points REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: wslpj_tm !: j-direction slope at u-, w-points REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: uslp_tm !: j-direction slope at u-, w-points REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: vslp_tm !: j-direction slope at u-, w-points #endif REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:,:) :: tsn_tm !: t/s average [m/s] REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) :: fr_i_tm !: average ice fraction [m/s] REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) :: hmld_tm !: mixed layer depth average [m] REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) :: qsr_tm !: solar radiation average [m] REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) :: wndm_tm !: 10m wind average [m] REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) :: emp_tm !: freshwater budget: volume flux [Kg/m2/s] REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) :: emp_b_hold !:hold emp from the beginning of each sub-stepping[m] REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) :: emps_tm !: freshwater budget:concentration/dilution [Kg/m2/s] # if defined key_zdfddm REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: avs_tm !: salinity vertical diffusivity coeff. at w-point [m/s] # endif #if defined key_traldf_c3d REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: ahtt_tm, ahtu_tm, ahtv_tm, ahtw_tm !: ** 3D coefficients ** at T-,U-,V-,W-points #elif defined key_traldf_c2d REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: ahtt_tm, ahtu_tm, ahtv_tm, ahtw_tm !: ** 2D coefficients ** at T-,U-,V-,W-points #elif defined key_traldf_c1d REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: ahtt_tm, ahtu_tm, ahtv_tm, ahtw_tm !: ** 1D coefficients ** at T-,U-,V-,W-points #else REAL(wp), PUBLIC :: ahtt_tm, ahtu_tm, ahtv_tm, ahtw_tm !: ** 0D coefficients ** at T-,U-,V-,W-points #endif #if defined key_traldf_eiv # if defined key_traldf_c3d REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: aeiu_tm , aeiv_tm , aeiw_tm !: ** 3D coefficients ** # elif defined key_traldf_c2d REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: aeiu_tm , aeiv_tm , aeiw_tm !: ** 2D coefficients ** # elif defined key_traldf_c1d REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: aeiu_tm , aeiv_tm, aeiw_tm !: ** 1D coefficients ** # else REAL(wp), PUBLIC :: aeiu_tm , aeiv_tm , aeiw_tm !: ** 0D coefficients ** # endif # endif REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) :: rnf_tm !: river runoff REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) :: h_rnf_tm !: depth in metres to the bottom of the relevant grid box REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: avt_temp,un_temp,vn_temp,wn_temp !: hold current values of avt, un, vn, wn #if defined key_ldfslp REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: wslpi_temp,wslpj_temp, uslp_temp, vslp_temp !: hold current values #endif REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: e3t_temp,e3u_temp,e3v_temp,e3w_temp !: hold current values REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:):: sshn_temp, sshb_temp, ssha_temp, rnf_temp,h_rnf_temp REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:):: sshu_n_temp, sshu_b_temp, sshu_a_temp REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:):: sshf_n_temp, sshf_b_temp, sshf_a_temp REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:):: sshv_n_temp, sshv_b_temp, sshv_a_temp REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:):: hu_temp, hv_temp, hur_temp, hvr_temp REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:,:):: hdivn_temp, rotn_temp REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:,:):: hdivb_temp, rotb_temp REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) :: tsn_temp REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:):: hmld_temp, qsr_temp, emp_temp, emps_temp,fr_i_temp,wndm_temp,emp_b_temp # if defined key_zdfddm REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: avs_temp !: salinity vertical diffusivity coeff. at w-point [m/s] # endif #if defined key_traldf_c3d REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: ahtt_temp, ahtu_temp, ahtv_temp, ahtw_temp !: ** 3D coefficients ** at T-,U-,V-,W-points #elif defined key_traldf_c2d REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: ahtt_temp, ahtu_temp, ahtv_temp, ahtw_temp !: ** 2D coefficients ** at T-,U-,V-,W-points #elif defined key_traldf_c1d REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: ahtt_temp, ahtu_temp, ahtv_temp, ahtw_temp !: ** 1D coefficients ** at T-,U-,V-,W-points #else REAL(wp), PUBLIC :: ahtt_temp, ahtu_temp, ahtv_temp, ahtw_temp !: ** 0D coefficients ** at T-,U-,V-,W-points #endif #if defined key_traldf_eiv # if defined key_traldf_c3d REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: aeiu_temp , aeiv_temp , aeiw_temp !: ** 3D coefficients ** # elif defined key_traldf_c2d REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: aeiu_temp , aeiv_temp , aeiw_temp !: ** 2D coefficients ** # elif defined key_traldf_c1d REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: aeiu_temp , aeiv_temp, aeiw_temp !: ** 1D coefficients ** # else REAL(wp), PUBLIC :: aeiu_temp , aeiv_temp , aeiw_temp !: ** 0D coefficients ** # endif # endif !!---------------------------------------------------------------------- !! NEMO/TOP 3.3.1 , NEMO Consortium (2010) !! $Id$ !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS INTEGER FUNCTION trc_alloc() !!------------------------------------------------------------------- !! *** ROUTINE trc_alloc *** !!------------------------------------------------------------------- USE lib_mpp, ONLY: ctl_warn !!------------------------------------------------------------------- ! ALLOCATE( cvol(jpi,jpj,jpk ) , & & trn (jpi,jpj,jpk,jptra) , & & tra (jpi,jpj,jpk,jptra) , & & trb (jpi,jpj,jpk,jptra) , & & gtru(jpi,jpj ,jptra) , gtrv(jpi,jpj,jptra) , & # if defined key_diatrc && ! defined key_iomput & trc2d(jpi,jpj,jpdia2d), trc3d(jpi,jpj,jpk,jpdia3d), & # endif # if defined key_diabio & trbio(jpi,jpj,jpk,jpdiabio), & #endif rdttrc(jpk) , STAT=trc_alloc ) IF( trc_alloc /= 0 ) CALL ctl_warn('trc_alloc: failed to allocate arrays') ! END FUNCTION trc_alloc #else !!---------------------------------------------------------------------- !! Empty module : No passive tracer !!---------------------------------------------------------------------- #endif !!====================================================================== END MODULE trc