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.
Changeset 2528 for trunk/NEMOGCM/NEMO/TOP_SRC/TRP/trdmld_trc.F90 – NEMO

Ignore:
Timestamp:
2010-12-27T18:33:53+01:00 (13 years ago)
Author:
rblod
Message:

Update NEMOGCM from branch nemo_v3_3_beta

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/TOP_SRC/TRP/trdmld_trc.F90

    • Property svn:keywords set to Id
    r1685 r2528  
    1616   !!   trd_mld_trc_init : initialization step 
    1717   !!---------------------------------------------------------------------- 
    18    USE trp_trc           ! tracer definitions (trn, trb, tra, etc.) 
    19    USE oce_trc           ! needed for namelist logicals, and euphotic layer arrays 
    20    USE trctrp_lec 
    21    USE trdmld_trc_oce    ! definition of main arrays used for trends computations 
     18   USE trc               ! tracer definitions (trn, trb, tra, etc.) 
     19   USE dom_oce           ! domain definition 
     20   USE zdfmxl  , ONLY : nmln !: number of level in the mixed layer 
     21   USE zdf_oce , ONLY : avt  !: vert. diffusivity coef. at w-point for temp   
     22# if defined key_zdfddm    
     23   USE zdfddm  , ONLY : avs  !: salinity vertical diffusivity coeff. at w-point 
     24# endif 
     25   USE trcnam_trp      ! passive tracers transport namelist variables 
     26   USE trdmod_trc_oce    ! definition of main arrays used for trends computations 
    2227   USE in_out_manager    ! I/O manager 
    2328   USE dianam            ! build the name of file (routine) 
     
    2934   USE sms_pisces         
    3035   USE sms_lobster 
    31    USE trc 
    3236 
    3337   IMPLICIT NONE 
    3438   PRIVATE 
    3539 
    36    INTERFACE trd_mod_trc 
    37       MODULE PROCEDURE trd_mod_trc_trp, trd_mod_trc_bio 
    38    END INTERFACE 
    39  
    40    PUBLIC trd_mod_trc                                             ! routine called by step.F90 
    4140   PUBLIC trd_mld_trc 
    4241   PUBLIC trd_mld_bio 
    4342   PUBLIC trd_mld_trc_init 
     43   PUBLIC trd_mld_trc_zint 
     44   PUBLIC trd_mld_bio_zint 
    4445 
    4546   CHARACTER (LEN=40) ::  clhstnam                                ! name of the trends NetCDF file 
     
    6061#  include "top_substitute.h90" 
    6162   !!---------------------------------------------------------------------- 
    62    !!   TOP 1.0 , LOCEAN-IPSL (2007)  
     63   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    6364   !! $Header:  $  
    64    !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     65   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    6566   !!---------------------------------------------------------------------- 
    6667 
    6768CONTAINS 
    68  
    69    SUBROUTINE trd_mod_trc_trp( ptrtrd, kjn, ktrd, kt ) 
    70       !!---------------------------------------------------------------------- 
    71       !!                  ***  ROUTINE trd_mod_trc  *** 
    72       !!---------------------------------------------------------------------- 
    73 #if defined key_trcbbl_adv 
    74       REAL(wp), DIMENSION(jpi,jpj,jpk) ::  zun, zvn                   ! temporary arrays 
    75 #else 
    76       USE oce_trc,   zun => un                                            ! When no bbl, zun == un 
    77       USE oce_trc,   zvn => vn                                            ! When no bbl, zvn == vn 
    78 #endif 
    79       INTEGER, INTENT( in )  ::   kt                                  ! time step 
    80       INTEGER, INTENT( in )  ::   kjn                                 ! tracer index 
    81       INTEGER, INTENT( in )  ::   ktrd                                ! tracer trend index 
    82       REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout )  ::   ptrtrd  ! Temperature or U trend 
    83       !!---------------------------------------------------------------------- 
    84  
    85       IF( kt == nittrc000 ) THEN 
    86 !         IF(lwp)WRITE(numout,*) 
    87 !         IF(lwp)WRITE(numout,*) 'trd_mod_trc:' 
    88 !         IF(lwp)WRITE(numout,*) '~~~~~~~~~~~~' 
    89       ENDIF 
    90  
    91       !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    92       ! Mixed layer trends for passive tracers 
    93       !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    94  
    95       SELECT CASE ( ktrd ) 
    96          CASE ( jptrc_trd_xad     )   ;   CALL trd_mld_trc_zint( ptrtrd, jpmld_trc_xad    , '3D', kjn ) 
    97          CASE ( jptrc_trd_yad     )   ;   CALL trd_mld_trc_zint( ptrtrd, jpmld_trc_yad    , '3D', kjn ) 
    98          CASE ( jptrc_trd_zad     )   ;   CALL trd_mld_trc_zint( ptrtrd, jpmld_trc_zad    , '3D', kjn ) 
    99          CASE ( jptrc_trd_ldf     )   ;   CALL trd_mld_trc_zint( ptrtrd, jpmld_trc_ldf    , '3D', kjn ) 
    100          CASE ( jptrc_trd_xei     )   ;   CALL trd_mld_trc_zint( ptrtrd, jpmld_trc_xei    , '3D', kjn ) 
    101          CASE ( jptrc_trd_yei     )   ;   CALL trd_mld_trc_zint( ptrtrd, jpmld_trc_yei    , '3D', kjn ) 
    102          CASE ( jptrc_trd_bbl     )   ;   CALL trd_mld_trc_zint( ptrtrd, jpmld_trc_bbl    , '3D', kjn ) 
    103          CASE ( jptrc_trd_zdf     ) 
    104             IF( ln_trcldf_iso ) THEN 
    105                CALL trd_mld_trc_zint( ptrtrd, jpmld_trc_ldf, '3D', kjn ) 
    106             ELSE 
    107                CALL trd_mld_trc_zint( ptrtrd, jpmld_trc_zdf, '3D', kjn ) 
    108             ENDIF 
    109          CASE ( jptrc_trd_zei     )   ;   CALL trd_mld_trc_zint( ptrtrd, jpmld_trc_zei    , '3D', kjn ) 
    110          CASE ( jptrc_trd_dmp     )   ;   CALL trd_mld_trc_zint( ptrtrd, jpmld_trc_dmp    , '3D', kjn ) 
    111          CASE ( jptrc_trd_sbc     )   ;   CALL trd_mld_trc_zint( ptrtrd, jpmld_trc_sbc    , '2D', kjn ) 
    112          CASE ( jptrc_trd_sms     )   ;   CALL trd_mld_trc_zint( ptrtrd, jpmld_trc_sms    , '3D', kjn ) 
    113          CASE ( jptrc_trd_bbc     )   ;   CALL trd_mld_trc_zint( ptrtrd, jpmld_trc_bbc    , '3D', kjn ) 
    114          CASE ( jptrc_trd_radb    )   ;   CALL trd_mld_trc_zint( ptrtrd, jpmld_trc_radb   , '3D', kjn ) 
    115          CASE ( jptrc_trd_radn    )   ;   CALL trd_mld_trc_zint( ptrtrd, jpmld_trc_radn   , '3D', kjn ) 
    116          CASE ( jptrc_trd_atf     )   ;   CALL trd_mld_trc_zint( ptrtrd, jpmld_trc_atf    , '3D', kjn ) 
    117       END SELECT 
    118  
    119  
    120    END SUBROUTINE trd_mod_trc_trp 
    121  
    122    SUBROUTINE trd_mod_trc_bio( ptrbio, ktrd, kt ) 
    123       !!---------------------------------------------------------------------- 
    124       !!                  ***  ROUTINE trd_mod_bio  *** 
    125       !!---------------------------------------------------------------------- 
    126  
    127       INTEGER, INTENT( in )  ::   kt                                  ! time step 
    128       INTEGER, INTENT( in )  ::   ktrd                                ! bio trend index 
    129       REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout )  ::   ptrbio  ! Bio trend 
    130       !!---------------------------------------------------------------------- 
    131  
    132       CALL trd_mld_bio_zint( ptrbio, ktrd ) ! Verticaly integrated biological trends 
    133  
    134    END SUBROUTINE trd_mod_trc_bio 
    135  
    13669 
    13770   SUBROUTINE trd_mld_trc_zint( ptrc_trdmld, ktrd, ctype, kjn ) 
     
    170103           
    171104         ! ... Set nmld(ji,jj) = index of first T point below control surf. or outside mixed-layer 
    172          SELECT CASE ( nctls_trc )                                ! choice of the control surface 
     105         SELECT CASE ( nn_ctls_trc )                                ! choice of the control surface 
    173106            CASE ( -2  )   ;   STOP 'trdmld_trc : not ready '     !     -> isopycnal surface (see ???) 
    174107#if defined key_pisces || defined key_lobster 
     
    177110            CASE (  0  )   ;   nmld_trc(:,:) = nmln(:,:)          !     -> ML with density criterion (see zdfmxl) 
    178111            CASE (  1  )   ;   nmld_trc(:,:) = nbol_trc(:,:)          !     -> read index from file 
    179             CASE (  2: )   ;   nctls_trc = MIN( nctls_trc, jpktrd_trc - 1 ) 
    180                                nmld_trc(:,:) = nctls_trc + 1      !     -> model level 
     112            CASE (  2: )   ;   nn_ctls_trc = MIN( nn_ctls_trc, jpktrd_trc - 1 ) 
     113                               nmld_trc(:,:) = nn_ctls_trc + 1      !     -> model level 
    181114         END SELECT 
    182115 
     
    281214         tmltrd_bio(:,:,:) = 0.e0    ! <<< reset trend arrays to zero 
    282215         ! ... Set nmld(ji,jj) = index of first T point below control surf. or outside mixed-layer 
    283          SELECT CASE ( nctls_trc )                                    ! choice of the control surface 
     216         SELECT CASE ( nn_ctls_trc )                                    ! choice of the control surface 
    284217            CASE ( -2  )   ;   STOP 'trdmld_trc : not ready '     !     -> isopycnal surface (see ???) 
    285218            CASE ( -1  )   ;   nmld_trc(:,:) = neln(:,:)          !     -> euphotic layer with light criterion 
    286219            CASE (  0  )   ;   nmld_trc(:,:) = nmln(:,:)          !     -> ML with density criterion (see zdfmxl) 
    287220            CASE (  1  )   ;   nmld_trc(:,:) = nbol_trc(:,:)          !     -> read index from file 
    288             CASE (  2: )   ;   nctls_trc = MIN( nctls_trc, jpktrd_trc - 1 ) 
    289                                nmld_trc(:,:) = nctls_trc + 1          !     -> model level 
     221            CASE (  2: )   ;   nn_ctls_trc = MIN( nn_ctls_trc, jpktrd_trc - 1 ) 
     222                               nmld_trc(:,:) = nn_ctls_trc + 1          !     -> model level 
    290223         END SELECT 
    291224 
     
    380313      !!        of time-averaged mixed-layer fields, this residual WILL NOT BE ZERO 
    381314      !!        over the first two analysis windows (except if restart). 
    382       !!        N.B. For ORCA2_LIM, use e.g. ntrc_trc=5, ucf_trc=1., nctls_trc=8 
     315      !!        N.B. For ORCA2_LIM, use e.g. ntrc_trc=5, rn_ucf_trc=1., nctls_trc=8 
    383316      !!             for checking residuals. 
    384317      !!             On a NEC-SX5 computer, this typically leads to: 
     
    421354      REAL(wp), DIMENSION(jpi,jpj,jpltrd_trc,jptra) ::  ztmltrd2  ! -+ 
    422355      !! 
    423       REAL(wp), DIMENSION(jpi,jpj) ::   z2d                       ! temporary array, used for eiv arrays 
    424356      CHARACTER (LEN= 5) ::   clvar 
    425357#if defined key_dimgout 
     
    429361      !!---------------------------------------------------------------------- 
    430362 
    431       IF( llwarn ) THEN                                           ! warnings 
    432          IF(      ( nittrc000 /= nit000   ) & 
    433               .OR.( ndttrc    /= 1        )    ) THEN 
    434  
    435             WRITE(numout,*) 'Be careful, trends diags never validated' 
    436             STOP 'Uncomment this line to proceed' 
    437          ENDIF 
    438       ENDIF 
     363      IF( nn_dttrc  /= 1  ) CALL ctl_stop( " Be careful, trends diags never validated " ) 
    439364 
    440365      ! ====================================================================== 
     
    450375            DO ji = 1,jpi 
    451376               ik = nmld_trc(ji,jj) 
    452                zavt = avt(ji,jj,ik) 
     377               zavt = fsavs(ji,jj,ik) 
    453378               DO jn = 1, jptra 
    454                   IF( luttrd(jn) )    & 
     379                  IF( ln_trdtrc(jn) )    & 
    455380                  tmltrd_trc(ji,jj,jpmld_trc_zdf,jn) = - zavt / fse3w(ji,jj,ik) * tmask(ji,jj,ik)  & 
    456381                       &                    * ( trn(ji,jj,ik-1,jn) - trn(ji,jj,ik,jn) )            & 
     
    462387         DO jn = 1, jptra 
    463388         ! ... Remove this K_z trend from the iso-neutral diffusion term (if any) 
    464             IF( luttrd(jn) ) & 
     389            IF( ln_trdtrc(jn) ) & 
    465390                 tmltrd_trc(:,:,jpmld_trc_ldf,jn) = tmltrd_trc(:,:,jpmld_trc_ldf,jn) - tmltrd_trc(:,:,jpmld_trc_zdf,jn) 
    466391    
     
    473398      ! therefore we do not call lbc_lnk in GYRE config. (closed basin, no cyclic B.C.) 
    474399      DO jn = 1, jptra 
    475          IF( luttrd(jn) ) THEN 
     400         IF( ln_trdtrc(jn) ) THEN 
    476401            DO jl = 1, jpltrd_trc 
    477402               CALL lbc_lnk( tmltrd_trc(:,:,jl,jn), 'T', 1. )        ! lateral boundary conditions 
     
    490415      ! II.1 Set before values of vertically averages passive tracers 
    491416      ! ------------------------------------------------------------- 
    492       IF( kt > nittrc000 ) THEN 
     417      IF( kt > nit000 ) THEN 
    493418         DO jn = 1, jptra 
    494             IF( luttrd(jn) ) THEN 
     419            IF( ln_trdtrc(jn) ) THEN 
    495420               tmlb_trc   (:,:,jn) = tml_trc   (:,:,jn) 
    496421               tmlatfn_trc(:,:,jn) = tmltrd_trc(:,:,jpmld_trc_atf,jn) 
     
    505430      DO jk = 1, jpktrd_trc ! - 1 ??? 
    506431         DO jn = 1, jptra 
    507             IF( luttrd(jn) ) & 
     432            IF( ln_trdtrc(jn) ) & 
    508433               tml_trc(:,:,jn) = tml_trc(:,:,jn) + wkx_trc(:,:,jk) * trn(:,:,jk,jn) 
    509434         END DO 
     
    515440         ! 
    516441         DO jn = 1, jptra 
    517             IF( luttrd(jn) ) THEN 
     442            IF( ln_trdtrc(jn) ) THEN 
    518443               tmlbb_trc  (:,:,jn) = tmlb_trc   (:,:,jn)   ;   tmlbn_trc  (:,:,jn) = tml_trc    (:,:,jn) 
    519444               tmlatfb_trc(:,:,jn) = tmlatfn_trc(:,:,jn)   ;   tmlradb_trc(:,:,jn) = tmlradn_trc(:,:,jn) 
     
    544469         ! ... Cumulate over BOTH physical contributions AND over time steps 
    545470         DO jn = 1, jptra 
    546             IF( luttrd(jn) ) THEN 
     471            IF( ln_trdtrc(jn) ) THEN 
    547472               DO jl = 1, jpltrd_trc 
    548473                  tmltrdm_trc(:,:,jn) = tmltrdm_trc(:,:,jn) + tmltrd_trc(:,:,jl,jn) 
     
    552477 
    553478         DO jn = 1, jptra 
    554             IF( luttrd(jn) ) THEN 
     479            IF( ln_trdtrc(jn) ) THEN 
    555480               ! ... Special handling of the Asselin trend  
    556481               tmlatfm_trc(:,:,jn) = tmlatfm_trc(:,:,jn) + tmlatfn_trc(:,:,jn) 
     
    573498 
    574499      ! Convert to appropriate physical units 
    575       tmltrd_trc(:,:,:,:) = tmltrd_trc(:,:,:,:) * ucf_trc 
    576  
    577       itmod = kt - nittrc000 + 1 
     500      tmltrd_trc(:,:,:,:) = tmltrd_trc(:,:,:,:) * rn_ucf_trc 
     501 
     502      itmod = kt - nit000 + 1 
    578503      it    = kt 
    579504 
    580       MODULO_NTRD : IF( MOD( itmod, ntrd_trc ) == 0 ) THEN           ! nitend MUST be multiple of ntrd_trc 
     505      MODULO_NTRD : IF( MOD( itmod, nn_trd_trc ) == 0 ) THEN           ! nitend MUST be multiple of nn_trd_trc 
    581506         ! 
    582507         ztmltot (:,:,:) = 0.e0                                   ! reset arrays to zero 
     
    591516 
    592517         DO jn = 1, jptra 
    593             IF( luttrd(jn) ) THEN 
     518            IF( ln_trdtrc(jn) ) THEN 
    594519               !-- Compute total trends    (use rdttrc instead of rdt ???) 
    595                IF ( ln_trcadv_smolar .OR. ln_trcadv_muscl .OR. ln_trcadv_muscl2 ) THEN  ! EULER-FORWARD schemes 
     520               IF ( ln_trcadv_muscl .OR. ln_trcadv_muscl2 ) THEN  ! EULER-FORWARD schemes 
    596521                  ztmltot(:,:,jn) =  ( tml_trc(:,:,jn) - tmlbn_trc(:,:,jn) )/rdt 
    597522               ELSE                                                                     ! LEAP-FROG schemes 
     
    629554               !-- Compute passive tracer total trends 
    630555         DO jn = 1, jptra 
    631             IF( luttrd(jn) ) THEN 
     556            IF( ln_trdtrc(jn) ) THEN 
    632557               tml_sum_trc(:,:,jn) = tmlbn_trc(:,:,jn) + 2 * ( tml_sum_trc(:,:,jn) - tml_trc(:,:,jn) ) + tml_trc(:,:,jn) 
    633558               ztmltot2   (:,:,jn) = ( tml_sum_trc(:,:,jn) - tml_sumb_trc(:,:,jn) ) /  ( 2.*rdt )    ! now tracer unit is /sec 
     
    637562         !-- Compute passive tracer residuals 
    638563         DO jn = 1, jptra 
    639             IF( luttrd(jn) ) THEN 
     564            IF( ln_trdtrc(jn) ) THEN 
    640565               ! 
    641566               DO jl = 1, jpltrd_trc 
     
    680605            DO jn = 1, jptra 
    681606 
    682                IF( luttrd(jn) ) THEN 
     607               IF( ln_trdtrc(jn) ) THEN 
    683608                  WRITE(numout, *) 
    684609                  WRITE(numout, *) '>>>>>>>>>>>>>>>>>>  TRC TRACER jn =', jn, ' <<<<<<<<<<<<<<<<<<' 
     
    777702         rmld_sum_trc(:,:)     = rmld_sum_trc(:,:)     /      (2*zfn)  ! similar to tml_sum and sml_sum 
    778703         DO jn = 1, jptra 
    779             IF( luttrd(jn) ) THEN         
     704            IF( ln_trdtrc(jn) ) THEN         
    780705               ! For passive tracer instantaneous diagnostics 
    781706               tmlbb_trc  (:,:,jn) = tmlb_trc   (:,:,jn)   ;   tmlbn_trc  (:,:,jn) = tml_trc    (:,:,jn) 
     
    791716               ! III.4 Convert to appropriate physical units 
    792717               ! ------------------------------------------- 
    793                ztmltot     (:,:,jn)   = ztmltot     (:,:,jn)   * ucf_trc/zfn   ! instant diags 
    794                ztmlres     (:,:,jn)   = ztmlres     (:,:,jn)   * ucf_trc/zfn 
    795                ztmlatf     (:,:,jn)   = ztmlatf     (:,:,jn)   * ucf_trc/zfn 
    796                ztmlrad     (:,:,jn)   = ztmlrad     (:,:,jn)   * ucf_trc/zfn 
     718               ztmltot     (:,:,jn)   = ztmltot     (:,:,jn)   * rn_ucf_trc/zfn   ! instant diags 
     719               ztmlres     (:,:,jn)   = ztmlres     (:,:,jn)   * rn_ucf_trc/zfn 
     720               ztmlatf     (:,:,jn)   = ztmlatf     (:,:,jn)   * rn_ucf_trc/zfn 
     721               ztmlrad     (:,:,jn)   = ztmlrad     (:,:,jn)   * rn_ucf_trc/zfn 
    797722               tml_sum_trc (:,:,jn)   = tml_sum_trc (:,:,jn)   /      (2*zfn)  ! mean diags 
    798                ztmltot2    (:,:,jn)   = ztmltot2    (:,:,jn)   * ucf_trc/zfn2 
    799                ztmltrd2    (:,:,:,jn) = ztmltrd2    (:,:,:,jn) * ucf_trc/zfn2 
    800                ztmlatf2    (:,:,jn)   = ztmlatf2    (:,:,jn)   * ucf_trc/zfn2 
    801                ztmlrad2    (:,:,jn)   = ztmlrad2    (:,:,jn)   * ucf_trc/zfn2 
    802                ztmlres2    (:,:,jn)   = ztmlres2    (:,:,jn)   * ucf_trc/zfn2 
     723               ztmltot2    (:,:,jn)   = ztmltot2    (:,:,jn)   * rn_ucf_trc/zfn2 
     724               ztmltrd2    (:,:,:,jn) = ztmltrd2    (:,:,:,jn) * rn_ucf_trc/zfn2 
     725               ztmlatf2    (:,:,jn)   = ztmlatf2    (:,:,jn)   * rn_ucf_trc/zfn2 
     726               ztmlrad2    (:,:,jn)   = ztmlrad2    (:,:,jn)   * rn_ucf_trc/zfn2 
     727               ztmlres2    (:,:,jn)   = ztmlres2    (:,:,jn)   * rn_ucf_trc/zfn2 
    803728            ENDIF 
    804729         END DO 
     
    820745      ! ---------------------------------- 
    821746 
    822       IF( lwp .AND. MOD( itmod , ntrd_trc ) == 0 ) THEN 
     747      IF( lwp .AND. MOD( itmod , nn_trd_trc ) == 0 ) THEN 
    823748         WRITE(numout,*) ' ' 
    824749         WRITE(numout,*) 'trd_mld_trc : write passive tracer trends in the NetCDF file :' 
     
    834759         DO jn = 1, jptra 
    835760            ! 
    836             IF( luttrd(jn) ) THEN 
    837                !-- Specific treatment for EIV trends 
    838                !   WARNING : When eiv is switched on but key_diaeiv is not, we do NOT diagnose 
    839                !   u_eiv, v_eiv, and w_eiv : the exact eiv advective trends thus cannot be computed, 
    840                !   only their sum makes sense => mask directional contrib. to avoid confusion 
    841                z2d(:,:) = tmltrd_trc(:,:,jpmld_trc_xei,jn) + tmltrd_trc(:,:,jpmld_trc_yei,jn) & 
    842                     &   + tmltrd_trc(:,:,jpmld_trc_zei,jn) 
    843 #if ( defined key_trcldf_eiv && defined key_diaeiv ) 
    844                tmltrd_trc(:,:,jpmld_trc_xei,jn) = -999. 
    845                tmltrd_trc(:,:,jpmld_trc_yei,jn) = -999. 
    846                tmltrd_trc(:,:,jpmld_trc_zei,jn) = -999. 
    847 #endif    
     761            IF( ln_trdtrc(jn) ) THEN 
    848762               CALL histwrite( nidtrd(jn), "mxl_depth", it, rmld_trc(:,:), ndimtrd1, ndextrd1 ) 
    849763               !-- Output the fields 
     
    864778                    &          it, ztmlatf(:,:,jn), ndimtrd1, ndextrd1 ) 
    865779                      
    866                CALL histwrite( nidtrd(jn), trim(clvar//ctrd_trc( jpltrd_trc+1,2)),     &  ! now total EIV : jpltrd_trc + 1 
    867                     &          it, z2d(:,:), ndimtrd1, ndextrd1 )                      
    868             ! 
    869780            ENDIF 
    870781         END DO 
     
    872783         IF( kt == nitend ) THEN  
    873784            DO jn = 1, jptra 
    874                IF( luttrd(jn) )  CALL histclo( nidtrd(jn) ) 
     785               IF( ln_trdtrc(jn) )  CALL histclo( nidtrd(jn) ) 
    875786            END DO 
    876787         ENDIF 
     
    881792         DO jn = 1, jptra 
    882793            ! 
    883             IF( luttrd(jn) ) THEN 
    884                !-- Specific treatment for EIV trends 
    885                !   WARNING : see above 
    886                z2d(:,:) = ztmltrd2(:,:,jpmld_trc_xei,jn) + ztmltrd2(:,:,jpmld_trc_yei,jn) & 
    887                    &   + ztmltrd2(:,:,jpmld_trc_zei,jn) 
    888  
    889 #if ( defined key_trcldf_eiv && defined key_diaeiv ) 
    890                ztmltrd2(:,:,jpmld_trc_xei,jn) = -999. 
    891                ztmltrd2(:,:,jpmld_trc_yei,jn) = -999. 
    892                ztmltrd2(:,:,jpmld_trc_zei,jn) = -999. 
    893 #endif 
     794            IF( ln_trdtrc(jn) ) THEN 
    894795               CALL histwrite( nidtrd(jn), "mxl_depth", it, rmld_sum_trc(:,:), ndimtrd1, ndextrd1 )  
    895796               !-- Output the fields 
     
    911812                 &          it, ztmlatf2(:,:,jn), ndimtrd1, ndextrd1 ) 
    912813 
    913                CALL histwrite( nidtrd(jn), trim(clvar//ctrd_trc( jpltrd_trc+1,2)),    &  ! now total EIV : jpltrd_trc + 1 
    914                  &          it, z2d(:,:), ndimtrd1, ndextrd1 ) 
    915  
    916814            ENDIF  
    917815            ! 
     
    919817         IF( kt == nitend ) THEN  
    920818            DO jn = 1, jptra 
    921                IF( luttrd(jn) )  CALL histclo( nidtrd(jn) ) 
     819               IF( ln_trdtrc(jn) )  CALL histclo( nidtrd(jn) ) 
    922820            END DO 
    923821         ENDIF 
     
    931829# endif /* key_dimgout */ 
    932830 
    933       IF( MOD( itmod, ntrd_trc ) == 0 ) THEN 
     831      IF( MOD( itmod, nn_trd_trc ) == 0 ) THEN 
    934832         ! 
    935833         ! Reset cumulative arrays to zero 
     
    1010908      !!---------------------------------------------------------------------- 
    1011909      ! ... Warnings 
    1012       IF( llwarn ) THEN 
    1013          IF(      ( nittrc000 /= nit000   ) & 
    1014               .OR.( ndttrc    /= 1        )    ) THEN 
    1015  
    1016             WRITE(numout,*) 'Be careful, trends diags never validated' 
    1017             STOP 'Uncomment this line to proceed' 
    1018          END IF 
    1019       END IF 
     910      IF( nn_dttrc  /= 1  ) CALL ctl_stop( " Be careful, trends diags never validated " ) 
    1020911 
    1021912      ! ====================================================================== 
     
    1058949 
    1059950      ! Convert to appropriate physical units 
    1060       tmltrd_bio(:,:,:) = tmltrd_bio(:,:,:) * ucf_trc 
    1061  
    1062       MODULO_NTRD : IF( MOD( kt, ntrd_trc ) == 0 ) THEN      ! nitend MUST be multiple of ntrd 
     951      tmltrd_bio(:,:,:) = tmltrd_bio(:,:,:) * rn_ucf_trc 
     952 
     953      MODULO_NTRD : IF( MOD( kt, nn_trd_trc ) == 0 ) THEN      ! nitend MUST be multiple of ntrd 
    1063954         ! 
    1064955         zfn  = float(nmoymltrdbio)    ;    zfn2 = zfn * zfn 
     
    11141005         ! III.4 Convert to appropriate physical units 
    11151006         ! ------------------------------------------- 
    1116          ztmltrdbio2    (:,:,:) = ztmltrdbio2    (:,:,:) * ucf_trc/zfn2 
     1007         ztmltrdbio2    (:,:,:) = ztmltrdbio2    (:,:,:) * rn_ucf_trc/zfn2 
    11171008 
    11181009      END IF MODULO_NTRD 
     
    11331024 
    11341025      ! define time axis 
    1135       itmod = kt - nittrc000 + 1 
     1026      itmod = kt - nit000 + 1 
    11361027      it    = kt 
    11371028 
    1138       IF( lwp .AND. MOD( itmod , ntrd_trc ) == 0 ) THEN 
     1029      IF( lwp .AND. MOD( itmod , nn_trd_trc ) == 0 ) THEN 
    11391030         WRITE(numout,*) ' ' 
    11401031         WRITE(numout,*) 'trd_mld_bio : write ML bio trends in the NetCDF file :' 
     
    11761067# endif /* key_dimgout */ 
    11771068 
    1178       IF( MOD( itmod, ntrd_trc ) == 0 ) THEN 
     1069      IF( MOD( itmod, nn_trd_trc ) == 0 ) THEN 
    11791070         ! 
    11801071         ! III.5 Reset cumulative arrays to zero 
     
    12161107      INTEGER :: ilseq, jl, jn 
    12171108      REAL(wp) ::   zjulian, zsto, zout 
    1218       CHARACTER (LEN=40) ::   clop, cleiv 
     1109      CHARACTER (LEN=40) ::   clop 
    12191110      CHARACTER (LEN=15) ::   csuff 
    12201111      CHARACTER (LEN=12) ::   clmxl 
    12211112      CHARACTER (LEN=16) ::   cltrcu 
    12221113      CHARACTER (LEN= 5) ::   clvar 
    1223  
    1224       NAMELIST/namtoptrd/ ntrd_trc, nctls_trc, ucf_trc, & 
    1225                           ln_trdmld_trc_restart, ln_trdmld_trc_instant, luttrd 
    12261114 
    12271115      !!---------------------------------------------------------------------- 
     
    12411129      ! I.1 Check consistency of user defined preferences 
    12421130      ! ------------------------------------------------- 
    1243 #if defined key_trcldf_eiv 
    1244       IF( lk_trdmld_trc .AND. ln_trcldf_iso ) THEN 
    1245          WRITE(numout,cform_war) 
    1246          WRITE(numout,*) '                You asked for ML diagnostics with iso-neutral diffusion   ' 
    1247          WRITE(numout,*) '                and eiv physics.                                          ' 
    1248          WRITE(numout,*) '                Yet, key_diaeiv is NOT switched on, so the eddy induced   ' 
    1249          WRITE(numout,*) '                velocity is not diagnosed.                                ' 
    1250          WRITE(numout,*) '                Therefore, we cannot deduce the eiv advective trends.     ' 
    1251          WRITE(numout,*) '                Only THE SUM of the i,j,k directional contributions then  ' 
    1252          WRITE(numout,*) '                makes sense => To avoid any confusion, we choosed to mask ' 
    1253          WRITE(numout,*) '                these i,j,k directional contributions (with -999.)        ' 
    1254          nwarn = nwarn + 1 
    1255       ENDIF 
    1256 #  endif 
    1257  
    1258       IF( ( lk_trdmld_trc ) .AND. ( MOD( nitend, ntrd_trc ) /= 0 ) ) THEN 
     1131 
     1132      IF( ( lk_trdmld_trc ) .AND. ( MOD( nitend, nn_trd_trc ) /= 0 ) ) THEN 
    12591133         WRITE(numout,cform_err) 
    12601134         WRITE(numout,*) '                Your nitend parameter, nitend = ', nitend 
    12611135         WRITE(numout,*) '                is no multiple of the trends diagnostics frequency        ' 
    1262          WRITE(numout,*) '                          you defined, ntrd_trc   = ', ntrd_trc 
     1136         WRITE(numout,*) '                          you defined, nn_trd_trc   = ', nn_trd_trc 
    12631137         WRITE(numout,*) '                This will not allow you to restart from this simulation.  ' 
    12641138         WRITE(numout,*) '                You should reconsider this choice.                        '  
     
    12691143      ENDIF 
    12701144 
    1271       IF( ( lk_trdmld_trc ) .AND. ( n_cla == 1 ) ) THEN 
    1272          WRITE(numout,cform_war) 
    1273          WRITE(numout,*) '                You set n_cla = 1. Note that the Mixed-Layer diagnostics  ' 
    1274          WRITE(numout,*) '                are not exact along the corresponding straits.            ' 
    1275          nwarn = nwarn + 1 
    1276       ENDIF 
    1277  
    1278  
    12791145      ! * Debugging information * 
    12801146      IF( lldebug ) THEN 
    12811147         WRITE(numout,*) '               ln_trcadv_muscl = '      , ln_trcadv_muscl 
    1282          WRITE(numout,*) '               ln_trcadv_smolar = '     , ln_trcadv_smolar 
    12831148         WRITE(numout,*) '               ln_trdmld_trc_instant = ', ln_trdmld_trc_instant 
    1284       ENDIF 
    1285  
    1286       IF( ln_trcadv_smolar .AND. .NOT. ln_trdmld_trc_instant ) THEN 
    1287          WRITE(numout,cform_err) 
    1288          WRITE(numout,*) '                Currently, you can NOT use simultaneously tracer Smolark. ' 
    1289          WRITE(numout,*) '                advection and window averaged diagnostics of ML trends.   ' 
    1290          WRITE(numout,*) '                WHY? Everything in trdmld_trc is coded for leap-frog, and ' 
    1291          WRITE(numout,*) '                Smolarkiewicz scheme is Euler forward.                    ' 
    1292          WRITE(numout,*) '                In particuliar, entrainment trend would be FALSE. However ' 
    1293          WRITE(numout,*) '                this residual is correct for instantaneous ML diagnostics.' 
    1294          WRITE(numout,*)  
    1295          nstop = nstop + 1 
    12961149      ENDIF 
    12971150 
     
    13641217      ! I.3 Read control surface from file ctlsurf_idx 
    13651218      ! ---------------------------------------------- 
    1366       IF( nctls_trc == 1 ) THEN 
     1219      IF( nn_ctls_trc == 1 ) THEN 
    13671220         CALL ctl_opn( inum, 'ctlsurf_idx', 'OLD', 'UNFORMATTED', 'SEQUENTIAL', -1, numout, lwp ) 
    13681221         READ ( inum ) nbol_trc 
     
    13781231#else 
    13791232      ! clmxl = legend root for netCDF output 
    1380       IF( nctls_trc == 0 ) THEN                                   ! control surface = mixed-layer with density criterion 
     1233      IF( nn_ctls_trc == 0 ) THEN                                   ! control surface = mixed-layer with density criterion 
    13811234         clmxl = 'Mixed Layer ' 
    1382       ELSE IF( nctls_trc == 1 ) THEN                              ! control surface = read index from file  
     1235      ELSE IF( nn_ctls_trc == 1 ) THEN                              ! control surface = read index from file  
    13831236         clmxl = '      Bowl ' 
    1384       ELSE IF( nctls_trc >= 2 ) THEN                              ! control surface = model level 
    1385          WRITE(clmxl,'(A10,I2,1X)') 'Levels 1 -', nctls_trc 
     1237      ELSE IF( nn_ctls_trc >= 2 ) THEN                              ! control surface = model level 
     1238         WRITE(clmxl,'(A10,I2,1X)') 'Levels 1 -', nn_ctls_trc 
    13861239      ENDIF 
    13871240 
     
    13951248         STOP 'trd_mld_trc : this was never checked. Comment this line to proceed...' 
    13961249      ENDIF 
    1397       zsto = ntrd_trc * rdt 
     1250      zsto = nn_trd_trc * rdt 
    13981251      clop = "inst("//TRIM(clop)//")" 
    13991252#  else 
     
    14011254         zsto = rdt                                               ! inst. diags : we use IOIPSL time averaging 
    14021255      ELSE 
    1403          zsto = ntrd_trc * rdt                                    ! mean  diags : we DO NOT use any IOIPSL time averaging 
     1256         zsto = nn_trd_trc * rdt                                    ! mean  diags : we DO NOT use any IOIPSL time averaging 
    14041257      ENDIF 
    14051258      clop = "ave("//TRIM(clop)//")" 
    14061259#  endif 
    1407       zout = ntrd_trc * rdt 
     1260      zout = nn_trd_trc * rdt 
    14081261 
    14091262      IF(lwp) WRITE (numout,*) '                netCDF initialization' 
     
    14241277      !       ==> choose them according to trdmld_trc_oce.F90 <== 
    14251278 
    1426 #if defined key_diaeiv 
    1427       cleiv = " (*** only total EIV is meaningful ***)"           ! eiv advec. trends require u_eiv, v_eiv 
    1428 #else 
    1429       cleiv = " " 
    1430 #endif 
    14311279      ctrd_trc(jpmld_trc_xad    ,1) = " Zonal advection"                 ;   ctrd_trc(jpmld_trc_xad    ,2) = "_xad" 
    14321280      ctrd_trc(jpmld_trc_yad    ,1) = " Meridional advection"            ;   ctrd_trc(jpmld_trc_yad    ,2) = "_yad" 
     
    14341282      ctrd_trc(jpmld_trc_ldf    ,1) = " Lateral diffusion"               ;   ctrd_trc(jpmld_trc_ldf    ,2) = "_ldf" 
    14351283      ctrd_trc(jpmld_trc_zdf    ,1) = " Vertical diff. (Kz)"             ;   ctrd_trc(jpmld_trc_zdf    ,2) = "_zdf" 
    1436       ctrd_trc(jpmld_trc_xei    ,1) = " Zonal EIV advection"//cleiv      ;   ctrd_trc(jpmld_trc_xei    ,2) = "_xei" 
    1437       ctrd_trc(jpmld_trc_yei    ,1) = " Merid. EIV advection"//cleiv     ;   ctrd_trc(jpmld_trc_yei    ,2) = "_yei" 
    1438       ctrd_trc(jpmld_trc_zei    ,1) = " Vertical EIV advection"//cleiv   ;   ctrd_trc(jpmld_trc_zei    ,2) = "_zei" 
    1439       ctrd_trc(jpmld_trc_bbc    ,1) = " Geothermal flux"                 ;   ctrd_trc(jpmld_trc_bbc    ,2) = "_bbc" 
    14401284      ctrd_trc(jpmld_trc_bbl    ,1) = " Adv/diff. Bottom boundary layer" ;   ctrd_trc(jpmld_trc_bbl    ,2) = "_bbl" 
    14411285      ctrd_trc(jpmld_trc_dmp    ,1) = " Tracer damping"                  ;   ctrd_trc(jpmld_trc_dmp    ,2) = "_dmp" 
     
    14451289      ctrd_trc(jpmld_trc_radn   ,1) = " Correct negative concentrations" ;   ctrd_trc(jpmld_trc_radn   ,2) = "_radn" 
    14461290      ctrd_trc(jpmld_trc_atf    ,1) = " Asselin time filter"             ;   ctrd_trc(jpmld_trc_atf    ,2) = "_atf" 
    1447       ctrd_trc(jpltrd_trc+1     ,1) = " Total EIV"//cleiv                ;   ctrd_trc(jpltrd_trc+1     ,2) = "_tei" 
    14481291 
    14491292      DO jn = 1, jptra       
    14501293      !-- Create a NetCDF file and enter the define mode  
    1451          IF( luttrd(jn) ) THEN 
     1294         IF( ln_trdtrc(jn) ) THEN 
    14521295            csuff="ML_"//ctrcnm(jn) 
    1453             CALL dia_nam( clhstnam, ntrd_trc, csuff ) 
     1296            CALL dia_nam( clhstnam, nn_trd_trc, csuff ) 
    14541297            CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,                                            & 
    1455                &        1, jpi, 1, jpj, nittrc000-ndttrc, zjulian, rdt, nh_t(jn), nidtrd(jn), domain_id=nidom ) 
     1298               &        1, jpi, 1, jpj, nit000, zjulian, rdt, nh_t(jn), nidtrd(jn), domain_id=nidom, snc4chunks=snc4set ) 
    14561299       
    14571300            !-- Define the ML depth variable 
     
    14641307#if defined key_lobster 
    14651308          !-- Create a NetCDF file and enter the define mode 
    1466           CALL dia_nam( clhstnam, ntrd_trc, 'trdbio' ) 
     1309          CALL dia_nam( clhstnam, nn_trd_trc, 'trdbio' ) 
    14671310          CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,                                            & 
    1468              &             1, jpi, 1, jpj, nittrc000-ndttrc, zjulian, rdt, nh_tb, nidtrdbio, domain_id=nidom ) 
     1311             &             1, jpi, 1, jpj, nit000, zjulian, rdt, nh_tb, nidtrdbio, domain_id=nidom, snc4chunks=snc4set ) 
    14691312#endif 
    14701313 
    14711314      !-- Define physical units 
    1472       IF( ucf_trc == 1. ) THEN 
     1315      IF( rn_ucf_trc == 1. ) THEN 
    14731316         cltrcu = "(mmole-N/m3)/sec"                              ! all passive tracers have the same unit  
    1474       ELSEIF ( ucf_trc == 3600.*24.) THEN                         ! ??? trop long : seulement (mmole-N/m3) 
     1317      ELSEIF ( rn_ucf_trc == 3600.*24.) THEN                         ! ??? trop long : seulement (mmole-N/m3) 
    14751318         cltrcu = "(mmole-N/m3)/day"                              ! ??? apparait dans les sorties netcdf  
    14761319      ELSE 
     
    14851328      DO jn = 1, jptra 
    14861329         ! 
    1487          IF( luttrd(jn) ) THEN 
     1330         IF( ln_trdtrc(jn) ) THEN 
    14881331            clvar = trim(ctrcnm(jn))//"ml"                           ! e.g. detml, zooml, no3ml, etc. 
    14891332            CALL histdef(nidtrd(jn), clvar,           clmxl//" "//trim(ctrcnm(jn))//" Mixed Layer ",                         & 
     
    15041347            CALL histdef(nidtrd(jn), trim(clvar//ctrd_trc(jpmld_trc_atf,2)), clmxl//" "//clvar//ctrd_trc(jpmld_trc_atf,1),   &  
    15051348              &       cltrcu, jpi, jpj, nh_t(jn), 1  , 1, 1  , -99 , 32, clop, zout, zout ) ! IOIPSL: NO time mean 
    1506           
    1507             CALL histdef(nidtrd(jn), trim(clvar//ctrd_trc(jpltrd_trc+1,2)),  clmxl//" "//clvar//ctrd_trc(jpltrd_trc+1 ,1),   &  
    1508               &       cltrcu, jpi, jpj, nh_t(jn), 1  , 1, 1  , -99 , 32, clop, zsto, zout ) ! Total EIV  
    15091349         ! 
    15101350         ENDIF 
     
    15201360      !-- Leave IOIPSL/NetCDF define mode 
    15211361      DO jn = 1, jptra 
    1522          IF( luttrd(jn) )  CALL histend( nidtrd(jn) ) 
     1362         IF( ln_trdtrc(jn) )  CALL histend( nidtrd(jn), snc4set ) 
    15231363      END DO 
    15241364 
    15251365#if defined key_lobster 
    15261366      !-- Leave IOIPSL/NetCDF define mode 
    1527       CALL histend( nidtrdbio ) 
     1367      CALL histend( nidtrdbio, snc4set ) 
    15281368 
    15291369      IF(lwp) WRITE(numout,*) 
     
    15391379   !!---------------------------------------------------------------------- 
    15401380 
    1541    INTERFACE trd_mod_trc 
    1542       MODULE PROCEDURE trd_mod_trc_trp, trd_mod_trc_bio 
    1543    END INTERFACE 
    1544  
    15451381CONTAINS 
    15461382 
     
    15541390      WRITE(*,*) 'trd_mld_bio: You should not have seen this print! error?', kt 
    15551391   END SUBROUTINE trd_mld_bio 
    1556  
    1557    SUBROUTINE trd_mod_trc_bio( ptrbio, ktrd, kt ) 
    1558       INTEGER               , INTENT( in )     ::   kt      ! time step 
    1559       INTEGER               , INTENT( in )     ::   ktrd    ! bio trend index 
    1560       REAL, DIMENSION(:,:,:), INTENT( inout )  ::   ptrbio  ! Bio trend 
    1561       WRITE(*,*) 'trd_mod_trc_bio : You should not have seen this print! error?', ptrbio(1,1,1) 
    1562       WRITE(*,*) '  "      "      : You should not have seen this print! error?', ktrd 
    1563       WRITE(*,*) '  "      "      : You should not have seen this print! error?', kt 
    1564    END SUBROUTINE trd_mod_trc_bio 
    1565  
    1566    SUBROUTINE trd_mod_trc_trp( ptrtrd, kjn, ktrd, kt ) 
    1567       INTEGER               , INTENT( in )     ::   kt      ! time step 
    1568       INTEGER               , INTENT( in )     ::   kjn     ! tracer index 
    1569       INTEGER               , INTENT( in )     ::   ktrd    ! tracer trend index 
    1570       REAL, DIMENSION(:,:,:), INTENT( inout )  ::   ptrtrd  ! Temperature or U trend 
    1571       WRITE(*,*) 'trd_mod_trc_trp : You should not have seen this print! error?', ptrtrd(1,1,1) 
    1572       WRITE(*,*) '  "      "      : You should not have seen this print! error?', kjn 
    1573       WRITE(*,*) '  "      "      : You should not have seen this print! error?', ktrd 
    1574       WRITE(*,*) '  "      "      : You should not have seen this print! error?', kt 
    1575    END SUBROUTINE trd_mod_trc_trp 
    15761392 
    15771393   SUBROUTINE trd_mld_trc_zint( ptrc_trdmld, ktrd, ctype, kjn ) 
Note: See TracChangeset for help on using the changeset viewer.