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/trcwri.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/trcwri.F90

    • Property svn:keywords set to Id
    r1836 r2528  
    55   !!==================================================================================== 
    66   !! History :   1.0  !  2009-05 (C. Ethe)  Original code 
    7    !!                  !  2010-03 (C. Ethe, R. Seferian ) Add the tracer transport trends 
    87   !!---------------------------------------------------------------------- 
    98#if defined key_top &&  defined key_iomput 
     
    1211   !!---------------------------------------------------------------------- 
    1312   !! trc_wri_trc   :  outputs of concentration fields 
    14    !! trc_wri_trd   :  outputs of transport trends 
    1513   !!---------------------------------------------------------------------- 
    1614   USE dom_oce         ! ocean space and time domain variables 
    1715   USE oce_trc 
    18    USE trp_trc 
    1916   USE trc 
    20    USE trdmld_trc_oce, ONLY : luttrd 
    2117   USE iom 
    22 #if defined key_off_tra 
    23    USE oce_trc 
    2418   USE dianam 
    25 #endif 
    2619 
    2720   IMPLICIT NONE 
     
    3225   !! * Substitutions 
    3326#  include "top_substitute.h90" 
    34    !!---------------------------------------------------------------------- 
    35    !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005)  
    36    !! $Id: trcdia.F90 1450 2009-05-15 14:12:12Z cetlod $  
    37    !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    38    !!---------------------------------------------------------------------- 
    3927 
    4028CONTAINS 
     
    5038 
    5139      ! 
    52       CALL iom_setkt  ( kt + ndttrc - 1 )       ! set the passive tracer time step 
     40      CALL iom_setkt  ( kt + nn_dttrc - 1 )       ! set the passive tracer time step 
    5341      CALL trc_wri_trc( kt              )       ! outputs for tracer concentration 
    54       CALL trc_wri_trd( kt              )       ! outputs for dynamical trends 
    5542      CALL iom_setkt  ( kt              )       ! set the model time step 
    5643      ! 
     
    6552      INTEGER, INTENT( in ) :: kt       ! ocean time-step 
    6653      INTEGER               :: jn 
    67       CHARACTER (len=20)    :: cltra, cltras 
    68 #if defined key_off_tra 
     54      CHARACTER (len=20)    :: cltra 
    6955      CHARACTER (len=40) :: clhstnam 
    7056      INTEGER ::   inum = 11            ! temporary logical unit 
    71 #endif 
    7257      !!--------------------------------------------------------------------- 
    7358  
    74 #if defined key_off_tra 
    75       IF( kt == nittrc000 ) THEN 
    76         ! WRITE root name in date.file for use by postpro 
    77          IF(lwp) THEN 
    78             CALL dia_nam( clhstnam, nwritetrc,' ' ) 
    79             CALL ctl_opn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    80             WRITE(inum,*) clhstnam 
    81             CLOSE(inum) 
    82          ENDIF 
     59      IF( lk_offline .AND. kt == nit000 .AND. lwp ) THEN    ! WRITE root name in date.file for use by postpro 
     60         CALL dia_nam( clhstnam, nn_writetrc,' ' ) 
     61         CALL ctl_opn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
     62         WRITE(inum,*) clhstnam 
     63         CLOSE(inum) 
    8364      ENDIF 
    84 #endif 
    8565      ! write the tracer concentrations in the file 
    8666      ! --------------------------------------- 
     
    9272   END SUBROUTINE trc_wri_trc 
    9373 
    94 # if defined key_trc_diatrd 
    95  
    96    SUBROUTINE trc_wri_trd( kt ) 
    97       !!---------------------------------------------------------------------- 
    98       !!                     ***  ROUTINE trc_wri_trd  *** 
    99       !! 
    100       !! ** Purpose :   output of passive tracer : advection-diffusion trends 
    101       !! 
    102       !!---------------------------------------------------------------------- 
    103       INTEGER, INTENT( in ) ::   kt          ! ocean time-step 
    104       !! 
    105       CHARACTER (len=3) ::   cltra 
    106       INTEGER  ::   jn, jl, ikn 
    107       !!---------------------------------------------------------------------- 
    108  
    109       DO jn = 1, jptra 
    110          IF( luttrd(jn) ) THEN 
    111             ikn = ikeep(jn) 
    112             DO jl = 1, jpdiatrc 
    113                IF( jl == jptrc_xad ) WRITE (cltra,"(3a)") 'XAD' ! x advection for tracer 
    114                IF( jl == jptrc_yad ) WRITE (cltra,"(3a)") 'YAD'  ! y advection for tracer 
    115                IF( jl == jptrc_zad ) WRITE (cltra,"(3a)") 'ZAD'  ! z advection for tracer 
    116                IF( jl == jptrc_xdf ) WRITE (cltra,"(3a)") 'XDF'  ! x diffusion for tracer 
    117                IF( jl == jptrc_ydf ) WRITE (cltra,"(3a)") 'YDF'  ! y diffusion for tracer 
    118                IF( jl == jptrc_zdf ) WRITE (cltra,"(3a)") 'ZDF'  ! z diffusion for tracer 
    119 # if defined key_trcldf_eiv 
    120                IF( jl == jptrc_xei ) WRITE (cltra,"(3a)") 'XGV'  ! x gent velocity for tracer 
    121                IF( jl == jptrc_yei ) WRITE (cltra,"(3a)") 'YGV'  ! y gent velocity for tracer 
    122                IF( jl == jptrc_zei ) WRITE (cltra,"(3a)") 'ZGV'  ! z gent velocity for tracer 
    123 # endif 
    124 # if defined key_trcdmp 
    125                IF( jl == jptrc_dmp ) WRITE (cltra,"(3a)") 'DMP'  ! damping 
    126 # endif 
    127                IF( jl == jptrc_sbc ) WRITE (cltra,"(3a)") 'SBC'  ! surface boundary conditions 
    128                ! write the trends 
    129                CALL iom_put( cltra, trtrd(:,:,:,ikn,jl) ) 
    130             END DO 
    131          END IF 
    132       END DO 
    133       ! 
    134    END SUBROUTINE trc_wri_trd 
    135  
    136 # else 
    137    SUBROUTINE trc_wri_trd( kt )                      ! Dummy routine 
    138       INTEGER, INTENT ( in ) ::   kt 
    139    END SUBROUTINE trc_wri_trd 
    140 #endif 
    14174#else 
    14275   !!---------------------------------------------------------------------- 
     
    15083#endif 
    15184 
     85   !!---------------------------------------------------------------------- 
     86   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
     87   !! $Id$  
     88   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    15289   !!====================================================================== 
    15390END MODULE trcwri 
Note: See TracChangeset for help on using the changeset viewer.