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 2830 for branches/2011/dev_r2802_TOP_substepping – NEMO

Ignore:
Timestamp:
2011-08-23T12:20:06+02:00 (13 years ago)
Author:
kpedwards
Message:

Updates to average physics variables for TOP substepping.

Location:
branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO
Files:
2 added
45 edited

Legend:

Unmodified
Added
Removed
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/OPA_SRC/TRA/traadv_cen2.F90

    r2715 r2830  
    3232   USE trc_oce         ! share passive tracers/Ocean variables 
    3333   USE lib_mpp         ! MPP library 
     34#if defined key_top 
     35   USE trc, ONLY: nittrc000  !get first time step for passive tracers 
     36#endif 
    3437 
    3538   IMPLICIT NONE 
     
    131134      !!---------------------------------------------------------------------- 
    132135 
    133       IF( wrk_in_use(2, 1) .OR. wrk_in_use(3, 1,2) ) THEN 
     136      IF( wrk_in_use(2, 35) .OR. wrk_in_use(3, 14,15) ) THEN 
    134137         CALL ctl_stop('tra_adv_cen2: requested workspace arrays unavailable')   ;   RETURN 
    135138      ENDIF 
    136139 
     140#if defined key_top 
     141      IF( kt == nit000 .OR. (kt == nittrc000 .AND. cdtype == 'TRC'))  THEN 
     142#else 
    137143      IF( kt == nit000 )  THEN 
     144#endif 
    138145         IF(lwp) WRITE(numout,*) 
    139146         IF(lwp) WRITE(numout,*) 'tra_adv_cen2 : 2nd order centered advection scheme on ', cdtype 
     
    141148         IF(lwp) WRITE(numout,*) 
    142149         ! 
    143          ALLOCATE( upsmsk(jpi,jpj), STAT=ierr ) 
    144          IF( ierr /= 0 )   CALL ctl_stop('STOP', 'tra_adv_cen2: unable to allocate array') 
     150         IF (.not. ALLOCATED(upsmsk))THEN 
     151             ALLOCATE( upsmsk(jpi,jpj), STAT=ierr ) 
     152             IF( ierr /= 0 )   CALL ctl_stop('STOP', 'tra_adv_cen2: unable to allocate array') 
     153         ENDIF 
     154 
    145155         ! 
    146156         upsmsk(:,:) = 0._wp                             ! not upstream by default 
     
    275285      ENDIF 
    276286      ! 
    277       IF( wrk_not_released(2, 1)   .OR.   & 
    278           wrk_not_released(3, 1,2) )   CALL ctl_stop('tra_adv_cen2: failed to release workspace arrays') 
     287      IF( wrk_not_released(2, 35)   .OR.   & 
     288          wrk_not_released(3, 14,15) )   CALL ctl_stop('tra_adv_cen2: failed to release workspace arrays') 
    279289      ! 
    280290   END SUBROUTINE tra_adv_cen2 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/OPA_SRC/TRA/traadv_muscl.F90

    r2715 r2830  
    2525   USE diaptr          ! poleward transport diagnostics 
    2626   USE trc_oce         ! share passive tracers/Ocean variables 
     27#if defined key_top 
     28   USE trc, ONLY: nittrc000  !get first time step for passive tracers 
     29#endif 
    2730 
    2831 
     
    8386      ENDIF 
    8487 
     88#if defined key_top 
     89      IF( kt == nit000 .OR. (kt == nittrc000 .AND. cdtype == 'TRC'))  THEN 
     90#else 
    8591      IF( kt == nit000 )  THEN 
     92#endif 
    8693         IF(lwp) WRITE(numout,*) 
    8794         IF(lwp) WRITE(numout,*) 'tra_adv : MUSCL advection scheme on ', cdtype 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/OPA_SRC/TRA/traadv_muscl2.F90

    r2715 r2830  
    2323   USE diaptr          ! poleward transport diagnostics 
    2424   USE trc_oce         ! share passive tracers/Ocean variables 
     25#if defined key_top 
     26   USE trc, ONLY: nittrc000  !get first time step for passive tracers 
     27#endif 
    2528 
    2629 
     
    8184      ENDIF 
    8285 
     86#if defined key_top 
     87      IF( kt == nit000 .OR. (kt == nittrc000 .AND. cdtype == 'TRC'))  THEN 
     88#else 
    8389      IF( kt == nit000 )  THEN 
     90#endif 
    8491         IF(lwp) WRITE(numout,*) 
    8592         IF(lwp) WRITE(numout,*) 'tra_adv_muscl2 : MUSCL2 advection scheme on ', cdtype 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/OPA_SRC/TRA/traadv_qck.F90

    r2715 r2830  
    2626   USE diaptr          ! poleward transport diagnostics 
    2727   USE trc_oce         ! share passive tracers/Ocean variables 
     28#if defined key_top 
     29   USE trc, ONLY: nittrc000  !get first time step for passive tracers 
     30#endif 
    2831 
    2932   IMPLICIT NONE 
     
    9093      !!---------------------------------------------------------------------- 
    9194 
     95#if defined key_top 
     96      IF( kt == nit000 .OR. (kt == nittrc000 .AND. cdtype == 'TRC'))  THEN 
     97#else 
    9298      IF( kt == nit000 )  THEN 
     99#endif 
    93100         IF(lwp) WRITE(numout,*) 
    94101         IF(lwp) WRITE(numout,*) 'tra_adv_qck : 3rd order quickest advection scheme on ', cdtype 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/OPA_SRC/TRA/traadv_tvd.F90

    r2715 r2830  
    3232   USE diaptr          ! poleward transport diagnostics 
    3333   USE trc_oce         ! share passive tracers/Ocean variables 
     34#if defined key_top 
     35   USE trc, ONLY: nittrc000  !get first time step for passive tracers 
     36#endif 
    3437 
    3538 
     
    8992      ENDIF 
    9093 
     94#if defined key_top 
     95      IF( kt == nit000 .OR. (kt == nittrc000 .AND. cdtype == 'TRC'))  THEN 
     96#else 
    9197      IF( kt == nit000 )  THEN 
     98#endif 
    9299         IF(lwp) WRITE(numout,*) 
    93100         IF(lwp) WRITE(numout,*) 'tra_adv_tvd : TVD advection scheme on ', cdtype 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/OPA_SRC/TRA/traadv_ubs.F90

    r2715 r2830  
    2222   USE dynspg_oce      ! choice/control of key cpp for surface pressure gradient 
    2323   USE trc_oce         ! share passive tracers/Ocean variables 
     24#if defined key_top 
     25   USE trc, ONLY: nittrc000  !get first time step for passive tracers 
     26#endif 
    2427 
    2528   IMPLICIT NONE 
     
    97100      ENDIF 
    98101 
     102#if defined key_top 
     103      IF( kt == nit000 .OR. (kt == nittrc000 .AND. cdtype == 'TRC'))  THEN 
     104#else 
    99105      IF( kt == nit000 )  THEN 
     106#endif 
    100107         IF(lwp) WRITE(numout,*) 
    101108         IF(lwp) WRITE(numout,*) 'tra_adv_ubs :  horizontal UBS advection scheme on ', cdtype 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/OPA_SRC/TRA/trabbl.F90

    r2715 r2830  
    3434   USE lbclnk         ! ocean lateral boundary conditions 
    3535   USE prtctl         ! Print control 
     36#if defined key_top 
     37   USE trc, ONLY: nittrc000  !get first time step for passive tracers 
     38#endif 
    3639 
    3740   IMPLICIT NONE 
     
    389392      ENDIF 
    390393      
     394#if defined key_top 
     395      IF( kt == nit000 .OR. (kt == nittrc000 .AND. cdtype == 'TRC'))  THEN 
     396#else 
    391397      IF( kt == nit000 )  THEN 
     398#endif 
    392399         IF(lwp)  WRITE(numout,*) 
    393400         IF(lwp)  WRITE(numout,*) 'trabbl:bbl : Compute bbl velocities and diffusive coefficients in ', cdtype 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/OPA_SRC/TRA/traldf_bilap.F90

    r2715 r2830  
    2929   USE trc_oce         ! share passive tracers/Ocean variables 
    3030   USE lib_mpp         ! MPP library 
     31#if defined key_top 
     32   USE trc, ONLY: nittrc000  !get first time step for passive tracers 
     33#endif 
    3134 
    3235   IMPLICIT NONE 
     
    9396      ENDIF 
    9497 
     98#if defined key_top 
     99      IF( kt == nit000 .OR. (kt == nittrc000 .AND. cdtype == 'TRC'))  THEN 
     100#else 
    95101      IF( kt == nit000 )  THEN 
     102#endif 
    96103         IF(lwp) WRITE(numout,*) 
    97104         IF(lwp) WRITE(numout,*) 'tra_ldf_bilap : iso-level biharmonic operator on ', cdtype 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/OPA_SRC/TRA/traldf_bilapg.F90

    r2715 r2830  
    2525   USE trc_oce         ! share passive tracers/Ocean variables 
    2626   USE lib_mpp         ! MPP library 
     27#if defined key_top 
     28   USE trc, ONLY: nittrc000  !get first time step for passive tracers 
     29#endif 
    2730 
    2831   IMPLICIT NONE 
     
    8285      ENDIF 
    8386 
     87#if defined key_top 
     88      IF( kt == nit000 .OR. (kt == nittrc000 .AND. cdtype == 'TRC'))  THEN 
     89#else 
    8490      IF( kt == nit000 )  THEN 
     91#endif 
    8592         IF(lwp) WRITE(numout,*) 
    8693         IF(lwp) WRITE(numout,*) 'tra_ldf_bilapg : horizontal biharmonic operator in s-coordinate on ', cdtype 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/OPA_SRC/TRA/traldf_iso.F90

    r2715 r2830  
    3232   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    3333#endif 
     34#if defined key_top 
     35   USE trc, ONLY: nittrc000  !get first time step for passive tracers 
     36#endif 
    3437 
    3538   IMPLICIT NONE 
     
    121124         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 
    122125      ENDIF 
     126#if defined key_top 
     127      IF( kt == nittrc000 .AND. cdtype == 'TRC' )  THEN 
     128         IF(lwp) WRITE(numout,*) 
     129         IF(lwp) WRITE(numout,*) 'tra_ldf_iso : rotated laplacian diffusion operator on ', cdtype 
     130         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 
     131      ENDIF 
     132#endif 
    123133      ! 
    124134      !                                                          ! =========== 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/OPA_SRC/TRA/traldf_iso_grif.F90

    r2715 r2830  
    2626   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    2727   USE lib_mpp         ! MPP library 
     28#if defined key_top 
     29   USE trc, ONLY: nittrc000  !get first time step for passive tracers 
     30#endif 
    2831 
    2932   IMPLICIT NONE 
     
    127130      !zdkt(1:jpi,1:jpj,0:1) => wrk_3d_9(:,:,1:2) 
    128131 
     132#if defined key_top 
     133      IF( kt == nit000 .OR. (kt == nittrc000 .AND. cdtype == 'TRC'))  THEN 
     134#else 
    129135      IF( kt == nit000 )  THEN 
     136#endif 
    130137         IF(lwp) WRITE(numout,*) 
    131138         IF(lwp) WRITE(numout,*) 'tra_ldf_iso_grif : rotated laplacian diffusion operator on ', cdtype 
    132139         IF(lwp) WRITE(numout,*) '                   WARNING: STILL UNDER TEST, NOT RECOMMENDED. USE AT YOUR OWN PERIL' 
    133140         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 
    134          ALLOCATE( ah_wslp2(jpi,jpj,jpk) , zdkt(jpi,jpj,0:1), STAT=ierr ) 
     141         IF (.not. ALLOCATED(ah_wslp2))THEN 
     142             ALLOCATE( ah_wslp2(jpi,jpj,jpk) , zdkt(jpi,jpj,0:1), STAT=ierr ) 
     143         ENDIF 
    135144         IF( lk_mpp   )   CALL mpp_sum ( ierr ) 
    136145         IF( ierr > 0 )   CALL ctl_stop('STOP', 'tra_ldf_iso_grif: unable to allocate arrays') 
    137146         IF( ln_traldf_gdia ) THEN 
    138             ALLOCATE( psix_eiv(jpi,jpj,jpk) , psiy_eiv(jpi,jpj,jpk) , STAT=ierr ) 
    139             IF( lk_mpp   )   CALL mpp_sum ( ierr ) 
    140             IF( ierr > 0 )   CALL ctl_stop('STOP', 'tra_ldf_iso_grif: unable to allocate diagnostics') 
     147            IF (.not. ALLOCATED(psix_eiv))THEN 
     148                ALLOCATE( psix_eiv(jpi,jpj,jpk) , psiy_eiv(jpi,jpj,jpk) , STAT=ierr ) 
     149                IF( lk_mpp   )   CALL mpp_sum ( ierr ) 
     150                IF( ierr > 0 )   CALL ctl_stop('STOP', 'tra_ldf_iso_grif: unable to allocate diagnostics') 
     151            ENDIF 
    141152         ENDIF 
    142153      ENDIF 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/OPA_SRC/TRA/tranxt.F90

    r2715 r2830  
    4848   USE agrif_opa_interp 
    4949#endif 
     50#if defined key_top 
     51   USE trc, ONLY: nittrc000  !get first time step for passive tracers 
     52#endif 
    5053 
    5154   IMPLICIT NONE 
     
    214217      !!---------------------------------------------------------------------- 
    215218 
     219#if defined key_top 
     220      IF( kt == nit000 .OR. (kt == nittrc000 .AND. cdtype == 'TRC'))  THEN 
     221#else 
    216222      IF( kt == nit000 )  THEN 
     223#endif 
    217224         IF(lwp) WRITE(numout,*) 
    218          IF(lwp) WRITE(numout,*) 'tra_nxt_fix : time stepping' 
     225         IF(lwp) WRITE(numout,*) 'tra_nxt_fix : time stepping', cdtype 
    219226         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 
    220227      ENDIF 
     
    282289      !!---------------------------------------------------------------------- 
    283290 
    284       IF( kt == nit000 ) THEN 
     291#if defined key_top 
     292      IF( kt == nit000 .OR. (kt == nittrc000 .AND. cdtype == 'TRC'))  THEN 
     293#else 
     294      IF( kt == nit000 )  THEN 
     295#endif 
    285296         IF(lwp) WRITE(numout,*) 
    286          IF(lwp) WRITE(numout,*) 'tra_nxt_vvl : time stepping' 
     297         IF(lwp) WRITE(numout,*) 'tra_nxt_vvl : time stepping', cdtype 
    287298         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 
    288299      ENDIF 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/OPA_SRC/TRA/trazdf_exp.F90

    r2715 r2830  
    3131   USE in_out_manager  ! I/O manager 
    3232   USE lib_mpp         ! MPP library 
     33#if defined key_top 
     34   USE trc, ONLY: nittrc000  !get first time step for passive tracers 
     35#endif 
    3336 
    3437   IMPLICIT NONE 
     
    9396      ENDIF 
    9497 
     98#if defined key_top 
     99      IF( kt == nit000 .OR. (kt == nittrc000 .AND. cdtype == 'TRC'))  THEN 
     100#else 
    95101      IF( kt == nit000 )  THEN 
     102#endif 
    96103         IF(lwp) WRITE(numout,*) 
    97104         IF(lwp) WRITE(numout,*) 'tra_zdf_exp : explicit vertical mixing on ', cdtype 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/OPA_SRC/TRA/trazdf_imp.F90

    r2715 r2830  
    3535   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    3636   USE lib_mpp         ! MPP library 
     37#if defined key_top 
     38   USE trc, ONLY: nittrc000  !get first time step for passive tracers 
     39#endif 
    3740 
    3841   IMPLICIT NONE 
     
    102105         ENDIF 
    103106      ENDIF 
     107#if defined key_top 
     108      IF( kt == nittrc000 .AND. cdtype == 'TRC' )  THEN 
     109         IF(lwp)WRITE(numout,*) 
     110         IF(lwp)WRITE(numout,*) 'tra_zdf_imp : implicit vertical mixing on ', cdtype 
     111         IF(lwp)WRITE(numout,*) '~~~~~~~~~~~ ' 
     112         ! 
     113         IF( lk_vvl ) THEN   ;    r_vvl = 1._wp       ! Variable volume indicator 
     114         ELSE                ;    r_vvl = 0._wp        
     115         ENDIF 
     116      ENDIF 
     117#endif 
    104118      ! 
    105119      !                                               ! ============= ! 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/C14b/trcsms_c14b.F90

    r2715 r2830  
    119119      ENDIF 
    120120 
    121       IF( kt == nit000 )  THEN         ! Computation of decay coeffcient 
     121      IF( kt == nittrc000 )  THEN         ! Computation of decay coeffcient 
    122122         zdemi   = 5730._wp 
    123123         xlambda = LOG(2.) / zdemi / ( nyear_len(1) * rday ) 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/CFC/trcnam_cfc.F90

    r2715 r2830  
    3737      !! 
    3838      !! ** Method  :   Read the namcfc namelist and check the parameter  
    39       !!       values called at the first timestep (nit000) 
     39      !!       values called at the first timestep (nittrc000) 
    4040      !! 
    4141      !! ** input   :   Namelist namcfc 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/CFC/trcsms_cfc.F90

    r2715 r2830  
    9797      ENDIF 
    9898 
    99       IF( kt == nit000 )   CALL trc_cfc_cst 
     99      IF( kt == nittrc000 )   CALL trc_cfc_cst 
    100100 
    101101      ! Temporal interpolation 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/LOBSTER/trcbio.F90

    r2715 r2830  
    9595#endif 
    9696 
    97       IF( kt == nit000 ) THEN 
     97      IF( kt == nittrc000 ) THEN 
    9898         IF(lwp) WRITE(numout,*) 
    9999         IF(lwp) WRITE(numout,*) ' trc_bio: LOBSTER bio-model' 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/LOBSTER/trcexp.F90

    r2715 r2830  
    6161      !!--------------------------------------------------------------------- 
    6262 
    63       IF( kt == nit000 ) THEN 
     63      IF( kt == nittrc000 ) THEN 
    6464         IF(lwp) WRITE(numout,*) 
    6565         IF(lwp) WRITE(numout,*) ' trc_exp: LOBSTER export' 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/LOBSTER/trcopt.F90

    r2715 r2830  
    7272      END IF 
    7373 
    74       IF( kt == nit000 ) THEN 
     74      IF( kt == nittrc000 ) THEN 
    7575         IF(lwp) WRITE(numout,*) 
    7676         IF(lwp) WRITE(numout,*) ' trc_opt : LOBSTER optic-model' 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/LOBSTER/trcsed.F90

    r2715 r2830  
    7474      END IF 
    7575 
    76       IF( kt == nit000 ) THEN 
     76      IF( kt == nittrc000 ) THEN 
    7777         IF(lwp) WRITE(numout,*) 
    7878         IF(lwp) WRITE(numout,*) ' trc_sed: LOBSTER sedimentation' 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/PISCES/p4zsed.F90

    r2774 r2830  
    329329 
    330330      ! Calendar computation 
    331       IF( kt == nit000 .OR. imois /= nflx1 ) THEN 
    332  
    333          IF( kt == nit000 )  nflx1  = 0 
     331      IF( kt == nittrc000 .OR. imois /= nflx1 ) THEN 
     332 
     333         IF( kt == nittrc000 )  nflx1  = 0 
    334334 
    335335         ! nflx1 number of the first file record used in the simulation 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/PISCES/trcrst_pisces.F90

    r2715 r2830  
    245245#if defined key_dtatrc 
    246246      ! Restore close seas values to initial data 
    247       CALL trc_dta( nit000 )  
     247      CALL trc_dta( nittrc000 )  
    248248      DO jn = 1, jptra 
    249249         IF( lutini(jn) ) THEN 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/PISCES/trcsms_pisces.F90

    r2715 r2830  
    7272      !!--------------------------------------------------------------------- 
    7373 
    74       IF( kt == nit000 )   CALL trc_sms_pisces_init    ! Initialization (first time-step only) 
     74      IF( kt == nittrc000 )   CALL trc_sms_pisces_init    ! Initialization (first time-step only) 
    7575 
    7676      IF( wrk_in_use(3,1) )  THEN 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/SED/sedini.F90

    r2761 r2830  
    449449 
    450450      dtsed = rdt 
    451       nitsed000 = nit000 
     451      nitsed000 = nittrc000 
    452452      nitsedend = nitend 
    453453#if ! defined key_sed_off 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/SED/sedmodel.F90

    r2528 r2830  
    3535 
    3636 
    37       IF( kt == nit000 ) CALL sed_init       ! Initialization of sediment model 
     37      IF( kt == nittrc000 ) CALL sed_init       ! Initialization of sediment model 
    3838 
    3939                         CALL sed_stp( kt )  ! Time stepping of Sediment model 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/SED/sedwri.F90

    r2761 r2830  
    5656      ! Initialisation 
    5757      ! -----------------  
    58       IF( kt == nit000 )   ALLOCATE( ndext52(jpij*jpksed), ndext51(jpij) ) 
     58      IF( kt == nittrc000 )   ALLOCATE( ndext52(jpij*jpksed), ndext51(jpij) ) 
    5959 
    6060      ! Define frequency of output and means 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/TRP/trcadv.F90

    r2715 r2830  
    3535   INTEGER ::   nadv   ! choice of the type of advection scheme 
    3636   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:) ::   r2dt  ! vertical profile time-step, = 2 rdttra 
    37    !                                                    ! except at nit000 (=rdttra) if neuler=0 
     37   !                                                    ! except at nitrrc000 (=rdttra) if neuler=0 
    3838 
    3939   !! * Substitutions 
     
    8080      ENDIF 
    8181 
    82       IF( kt == nit000 )   CALL trc_adv_ctl          ! initialisation & control of options 
     82      IF( kt == nittrc000 )   CALL trc_adv_ctl          ! initialisation & control of options 
    8383 
    8484#if ! defined key_pisces 
    85       IF( neuler == 0 .AND. kt == nit000 ) THEN     ! at nit000 
     85      IF( neuler == 0 .AND. kt == nittrc000 ) THEN     ! at nittrc000 
    8686         r2dt(:) =  rdttrc(:)           ! = rdttrc (restarting with Euler time stepping) 
    87       ELSEIF( kt <= nit000 + nn_dttrc ) THEN          ! at nit000 or nit000+1 
     87      ELSEIF( kt <= nittrc000 + nn_dttrc ) THEN          ! at nittrc000 or nittrc000+1 
    8888         r2dt(:) = 2. * rdttrc(:)       ! = 2 rdttrc (leapfrog) 
    8989      ENDIF 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/TRP/trcdmp.F90

    r2715 r2830  
    9494      ! 0. Initialization (first time-step only) 
    9595      !    -------------- 
    96       IF( kt == nit000 ) CALL trc_dmp_init 
     96      IF( kt == nittrc000 ) CALL trc_dmp_init 
    9797 
    9898      IF( l_trdtrc )   ALLOCATE( ztrtrd(jpi,jpj,jpk) )   ! temporary save of trends 
     
    173173      !! 
    174174      !! ** Method  :   read the nammbf namelist and check the parameters 
    175       !!              called by trc_dmp at the first timestep (nit000) 
     175      !!              called by trc_dmp at the first timestep (nittrc000) 
    176176      !!---------------------------------------------------------------------- 
    177177 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/TRP/trcldf.F90

    r2715 r2830  
    5959      !!---------------------------------------------------------------------- 
    6060 
    61       IF( kt == nit000 )   CALL ldf_ctl          ! initialisation & control of options 
     61      IF( kt == nittrc000 )   CALL ldf_ctl          ! initialisation & control of options 
    6262 
    6363      IF( l_trdtrc )  THEN  
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/TRP/trcnxt.F90

    r2715 r2830  
    9696      !!---------------------------------------------------------------------- 
    9797 
    98       IF( kt == nit000 .AND. lwp ) THEN 
     98      IF( kt == nittrc000 .AND. lwp ) THEN 
    9999         WRITE(numout,*) 
    100100         WRITE(numout,*) 'trc_nxt : time stepping on passive tracers' 
     
    119119 
    120120      ! set time step size (Euler/Leapfrog) 
    121       IF( neuler == 0 .AND. kt ==  nit000) THEN  ;  r2dt(:) =     rdttrc(:)   ! at nit000             (Euler) 
    122       ELSEIF( kt <= nit000 + 1 )           THEN  ;  r2dt(:) = 2.* rdttrc(:)   ! at nit000 or nit000+1 (Leapfrog) 
     121      IF( neuler == 0 .AND. kt ==  nittrc000) THEN  ;  r2dt(:) =     rdttrc(:)   ! at nittrc000             (Euler) 
     122      ELSEIF( kt <= nittrc000 +  nn_dttrc )           THEN  ;  r2dt(:) = 2.* rdttrc(:)   ! at nit000 or nit000+1 (Leapfrog) 
    123123      ENDIF 
    124124 
     
    129129      ENDIF 
    130130      ! Leap-Frog + Asselin filter time stepping 
    131       IF( neuler == 0 .AND. kt == nit000 ) THEN        ! Euler time-stepping at first time-step 
    132          !                                             ! (only swap) 
     131      IF( neuler == 0 .AND. kt == nittrc000 ) THEN        ! Euler time-stepping at first time-step 
     132         !                                                ! (only swap) 
    133133         DO jn = 1, jptra 
    134134            DO jk = 1, jpkm1 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/TRP/trcrad.F90

    r2715 r2830  
    5353      !!---------------------------------------------------------------------- 
    5454 
    55       IF( kt == nit000 ) THEN 
     55      IF( kt == nittrc000 ) THEN 
    5656         IF(lwp) WRITE(numout,*) 
    5757         IF(lwp) WRITE(numout,*) 'trc_rad : Correct artificial negative concentrations ' 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/TRP/trcsbc.F90

    r2715 r2830  
    7272      END IF 
    7373 
    74       IF( kt == nit000 ) THEN 
     74      IF( kt == nittrc000 ) THEN 
    7575         IF(lwp) WRITE(numout,*) 
    7676         IF(lwp) WRITE(numout,*) 'trc_sbc : Passive tracers surface boundary condition' 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/TRP/trczdf.F90

    r2715 r2830  
    3232      !                                ! defined from ln_zdf...  namlist logicals) 
    3333   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:) ::  r2dt   ! vertical profile time-step, = 2 rdttra 
    34       !                                                 ! except at nit000 (=rdttra) if neuler=0 
     34      !                                                 ! except at nittrc000 (=rdttra) if neuler=0 
    3535 
    3636   !! * Substitutions 
     
    6969      !!--------------------------------------------------------------------- 
    7070 
    71       IF( kt == nit000 )   CALL zdf_ctl          ! initialisation & control of options 
     71      IF( kt == nittrc000 )   CALL zdf_ctl          ! initialisation & control of options 
    7272 
    7373#if ! defined key_pisces 
    74       IF( neuler == 0 .AND. kt == nit000 ) THEN     ! at nit000 
     74      IF( neuler == 0 .AND. kt == nittrc000 ) THEN     ! at nittrc000 
    7575         r2dt(:) =  rdttrc(:)           ! = rdttrc (restarting with Euler time stepping) 
    76       ELSEIF( kt <= nit000 + nn_dttrc ) THEN          ! at nit000 or nit000+1 
     76      ELSEIF( kt <= nittrc000 + nn_dttrc ) THEN          ! at nittrc000 or nittrc000+nn_dttrc 
    7777         r2dt(:) = 2. * rdttrc(:)       ! = 2 rdttrc (leapfrog) 
    7878      ENDIF 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/TRP/trdmld_trc.F90

    r2715 r2830  
    475475      ! II.1 Set before values of vertically averages passive tracers 
    476476      ! ------------------------------------------------------------- 
    477       IF( kt > nit000 ) THEN 
     477      IF( kt > nittrc000 ) THEN 
    478478         DO jn = 1, jptra 
    479479            IF( ln_trdtrc(jn) ) THEN 
     
    497497      ! II.3 Initialize mixed-layer "before" arrays for the 1rst analysis window     
    498498      ! ------------------------------------------------------------------------ 
    499       IF( kt == 2 ) THEN  !  i.e. ( .NOT. ln_rstart ).AND.( kt == nit000 + 1)    ??? 
     499      IF( kt == nittrc000 + nn_dttrc ) THEN  !  i.e. ( .NOT. ln_rstart ).AND.( kt == nit000 + 1)    ??? 
    500500         ! 
    501501         DO jn = 1, jptra 
     
    560560      tmltrd_trc(:,:,:,:) = tmltrd_trc(:,:,:,:) * rn_ucf_trc 
    561561 
    562       itmod = kt - nit000 + 1 
     562      itmod = kt - nittrc000 + 1 
    563563      it    = kt 
    564564 
     
    980980      ! II.3 Initialize mixed-layer "before" arrays for the 1rst analysis window 
    981981      ! ------------------------------------------------------------------------ 
    982       IF( kt == 2 ) THEN  !  i.e. ( .NOT. ln_rstart ).AND.( kt == nit000 + 1) 
     982      IF( kt == nittrc000 + nn_dttrc ) THEN  !  i.e. ( .NOT. ln_rstart ).AND.( kt == nit000 + 1) 
    983983         ! 
    984984         tmltrd_csum_ub_bio (:,:,:) = 0.e0 
     
    10861086 
    10871087      ! define time axis 
    1088       itmod = kt - nit000 + 1 
     1088      itmod = kt - nittrc000 + 1 
    10891089      it    = kt 
    10901090 
     
    13311331      zjulian = zjulian - adatrj   !   set calendar origin to the beginning of the experiment 
    13321332      IF(lwp) WRITE(numout,*)' '   
    1333       IF(lwp) WRITE(numout,*)' Date 0 used :', nit000                  & 
     1333      IF(lwp) WRITE(numout,*)' Date 0 used :', nittrc000               & 
    13341334           &   ,' YEAR ', nyear, ' MONTH ', nmonth,' DAY ', nday       & 
    13351335           &   ,'Julian day : ', zjulian 
     
    13601360            CALL dia_nam( clhstnam, nn_trd_trc, csuff ) 
    13611361            CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,                                            & 
    1362                &        1, jpi, 1, jpj, nit000, zjulian, rdt, nh_t(jn), nidtrd(jn), domain_id=nidom, snc4chunks=snc4set ) 
     1362               &        1, jpi, 1, jpj, nittrc000, zjulian, rdt, nh_t(jn), nidtrd(jn), domain_id=nidom, snc4chunks=snc4set ) 
    13631363       
    13641364            !-- Define the ML depth variable 
     
    13731373          CALL dia_nam( clhstnam, nn_trd_trc, 'trdbio' ) 
    13741374          CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,                                            & 
    1375              &             1, jpi, 1, jpj, nit000, zjulian, rdt, nh_tb, nidtrdbio, domain_id=nidom, snc4chunks=snc4set ) 
     1375             &             1, jpi, 1, jpj, nittrc000, zjulian, rdt, nh_tb, nidtrdbio, domain_id=nidom, snc4chunks=snc4set ) 
    13761376#endif 
    13771377 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/TRP/trdmod_trc.F90

    r2528 r2830  
    5050      !!---------------------------------------------------------------------- 
    5151 
    52       IF( kt == nit000 ) THEN 
     52      IF( kt == nittrc000 ) THEN 
    5353!         IF(lwp)WRITE(numout,*) 
    5454!         IF(lwp)WRITE(numout,*) 'trd_mod_trc:' 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/oce_trc.F90

    r2787 r2830  
    192192   USE oce , ONLY :   rhd     =>    rhd     !: in situ density anomalie rhd=(rho-rau0)/rau0 (no units) 
    193193   USE oce , ONLY :   hdivn   =>    hdivn   !: horizontal divergence (1/s) 
     194   USE oce , ONLY :   rotn    =>    rotn    !: relative vorticity    [s-1] 
     195   USE oce , ONLY :   hdivb   =>    hdivb   !: horizontal divergence (1/s) 
     196   USE oce , ONLY :   rotb    =>    rotb    !: relative vorticity    [s-1] 
     197   USE oce , ONLY :   sshn    =>    sshn    !: sea surface height at t-point [m]    
     198   USE oce , ONLY :   sshb    =>    sshb    !: sea surface height at t-point [m]    
     199   USE oce , ONLY :   ssha    =>    ssha    !: sea surface height at t-point [m]    
     200   USE oce , ONLY :   sshu_n  =>    sshu_n  !: sea surface height at u-point [m]    
     201   USE oce , ONLY :   sshu_b  =>    sshu_b  !: sea surface height at u-point [m]    
     202   USE oce , ONLY :   sshu_a  =>    sshu_a  !: sea surface height at u-point [m]    
     203   USE oce , ONLY :   sshv_n  =>    sshv_n  !: sea surface height at v-point [m]    
     204   USE oce , ONLY :   sshv_b  =>    sshv_b  !: sea surface height at v-point [m]    
     205   USE oce , ONLY :   sshv_a  =>    sshv_a  !: sea surface height at v-point [m]    
     206   USE oce , ONLY :   sshf_n  =>    sshf_n  !: sea surface height at v-point [m]    
     207   USE oce , ONLY :   l_traldf_rot   =>   l_traldf_rot !: rotated laplacian operator for lateral diffusion     
    194208   USE oce , ONLY :   l_traldf_rot => l_traldf_rot  !: rotated laplacian operator for lateral diffusion 
    195209#if defined key_offline 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/trc.F90

    r2715 r2830  
    5858   CHARACTER(len=50), PUBLIC ::  cn_trcrst_in    !: suffix of pass. tracer restart name (input) 
    5959   CHARACTER(len=50), PUBLIC ::  cn_trcrst_out   !: suffix of pass. tracer restart name (output) 
     60 
     61   INTEGER          , PUBLIC ::  nittrc000       !: first time step of passive tracers model 
    6062    
    6163   !! information for outputs 
     
    99101# endif 
    100102 
     103   !! variables to average over physics over passive tracer sub-steps. 
     104   !! ---------------------------------------------------------------- 
     105  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:) ::  un_tm      !: i-horizontal velocity average     [m/s] 
     106  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:) ::  vn_tm      !: j-horizontal velocity average     [m/s] 
     107  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:) ::  wn_tm      !: k-vertical velocity average       [m/s] 
     108  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:) ::  avt_tm     !: vertical viscosity & diffusivity coeff. at  w-point   [m2/s] 
     109  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) ::    sshn_tm !: average ssh for the now step [m] 
     110  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) ::    sshb_hold !:hold sshb from the beginning of each sub-stepping[m]   
     111  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) ::    sshu_n_tm !: average ssh for the now step [m] 
     112  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) ::    sshu_b_hold !:hold sshb from the beginning of each sub-stepping[m]   
     113  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) ::    sshv_n_tm !: average ssh for the now step [m] 
     114  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) ::    sshv_b_hold !:hold sshb from the beginning of each sub-stepping[m]   
     115#if defined key_ldfslp 
     116  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION (:,:,:) ::   wslpi_tm !: i-direction slope at u-, w-points 
     117  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION (:,:,:) ::   wslpj_tm !: j-direction slope at u-, w-points 
     118  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION (:,:,:) ::   uslp_tm !: j-direction slope at u-, w-points 
     119  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION (:,:,:) ::   vslp_tm !: j-direction slope at u-, w-points 
     120#endif 
     121  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:)  ::   rnf_tm !: river runoff 
     122  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:)  ::   h_rnf_tm !: depth in metres to the bottom of the relevant grid box 
     123  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::    avt_temp,un_temp,vn_temp,wn_temp     !: hold current values of avt, un, vn, wn 
     124#if defined key_ldfslp 
     125  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::    wslpi_temp,wslpj_temp, uslp_temp, vslp_temp    !: hold current values  
     126#endif 
     127  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::    e3t_temp,e3u_temp,e3v_temp,e3w_temp     !: hold current values 
     128  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:)::       sshn_temp, sshb_temp, ssha_temp, rnf_temp,h_rnf_temp 
     129  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:)::       sshu_n_temp, sshu_b_temp, sshu_a_temp 
     130  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:)::       sshf_n_temp, sshf_b_temp, sshf_a_temp 
     131  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:)::       sshv_n_temp, sshv_b_temp, sshv_a_temp 
     132  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:)::       hu_temp, hv_temp, hur_temp, hvr_temp 
     133  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:,:)::     hdivn_temp, rotn_temp 
     134  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:,:)::     hdivb_temp, rotb_temp 
     135 
    101136   !!---------------------------------------------------------------------- 
    102137   !! NEMO/TOP 3.3.1 , NEMO Consortium (2010) 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/trcdia.F90

    r2715 r2830  
    8585      !! ** Purpose :   Standard output of passive tracer : concentration fields 
    8686      !! 
    87       !! ** Method  :   At the beginning of the first time step (nit000), define all 
     87      !! ** Method  :   At the beginning of the first time step (nittrc000), define all 
    8888      !!             the NETCDF files and fields for concentration of passive tracer 
    8989      !! 
     
    135135 
    136136      ! define time axis 
    137       itmod = kt - nit000 + 1 
     137      itmod = kt - nittrc000 + 1 
    138138      it    = kt 
    139139      iiter = ( nit000 - 1 ) / nn_dttrc 
     
    144144      IF(ll_print)WRITE(numout,*)'trcdit_wr kt=',kt,' kindic ',kindic 
    145145       
    146       IF( kt == nit000 ) THEN 
     146      IF( kt == nittrc000 ) THEN 
    147147 
    148148         ! Compute julian date from starting date of the run 
     
    150150         zjulian = zjulian - adatrj   !   set calendar origin to the beginning of the experiment 
    151151         IF(lwp)WRITE(numout,*)' '   
    152          IF(lwp)WRITE(numout,*)' Date 0 used :', nit000                         & 
     152         IF(lwp)WRITE(numout,*)' Date 0 used :', nittrc000                         & 
    153153            &                 ,' YEAR ', nyear, ' MONTH ', nmonth, ' DAY ', nday   & 
    154154            &                 ,'Julian day : ', zjulian   
     
    226226      !! ** Purpose :   output of passive tracer : additional 2D and 3D arrays 
    227227      !! 
    228       !! ** Method  :   At the beginning of the first time step (nit000), define all 
     228      !! ** Method  :   At the beginning of the first time step (nittrc000), define all 
    229229      !!             the NETCDF files and fields for concentration of passive tracer 
    230230      !! 
     
    275275 
    276276      ! define time axis 
    277       itmod = kt - nit000 + 1 
     277      itmod = kt - nittrc000 + 1 
    278278      it    = kt 
    279279      iiter = ( nit000 - 1 ) / nn_dttrc 
     
    284284      IF( ll_print ) WRITE(numout,*) 'trcdii_wr kt=', kt, ' kindic ', kindic 
    285285 
    286       IF( kt == nit000 ) THEN 
     286      IF( kt == nittrc000 ) THEN 
    287287 
    288288         ! Define the NETCDF files for additional arrays : 2D or 3D 
     
    375375      !! ** Purpose :   output of passive tracer : biological fields 
    376376      !! 
    377       !! ** Method  :   At the beginning of the first time step (nit000), define all 
     377      !! ** Method  :   At the beginning of the first time step (nittrc000), define all 
    378378      !!             the NETCDF files and fields for concentration of passive tracer 
    379379      !! 
     
    424424 
    425425      ! define time axis 
    426       itmod = kt - nit000 + 1 
     426      itmod = kt - nittrc000 + 1 
    427427      it    = kt 
    428428      iiter = ( nit000 - 1 ) / nn_dttrc 
     
    433433      IF(ll_print) WRITE(numout,*)'trcdib_wr kt=',kt,' kindic ',kindic 
    434434 
    435       IF( kt == nit000 ) THEN 
     435      IF( kt == nittrc000 ) THEN 
    436436 
    437437         ! Define the NETCDF files for biological trends 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/trcdta.F90

    r2715 r2830  
    7171         IF( lutini(jn) ) THEN  
    7272 
    73             IF ( kt == nit000 ) THEN 
     73            IF ( kt == nittrc000 ) THEN 
    7474               !! 3D tracer data 
    7575               IF(lwp)WRITE(numout,*) 
     
    8686 
    8787 
    88             ! First call kt=nit000 
     88            ! First call kt=nittrc000 
    8989            ! -------------------- 
    9090 
    91             IF ( kt == nit000 .AND. nlectr(jn) == 0 ) THEN 
     91            IF ( kt == nittrc000 .AND. nlectr(jn) == 0 ) THEN 
    9292               ntrc1(jn) = 0 
    9393               IF(lwp) WRITE(numout,*) ' trc_dta : Levitus tracer data monthly fields' 
     
    104104# if defined key_pisces 
    105105            ! Read montly file 
    106             IF( ( kt == nit000 .AND. nlectr(jn) == 0)  .OR. imois /= ntrc1(jn) ) THEN 
     106            IF( ( kt == nittrc000 .AND. nlectr(jn) == 0)  .OR. imois /= ntrc1(jn) ) THEN 
    107107               nlectr(jn) = 1 
    108108 
     
    186186# else 
    187187            ! Read init file only 
    188             IF( kt == nit000  ) THEN 
     188            IF( kt == nittrc000  ) THEN 
    189189               ntrc1(jn) = 1 
    190190               CALL iom_get ( numtr(jn), jpdom_data, ctrcnm(jn), trdta(:,:,:,jn), ntrc1(jn) ) 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/trcini.F90

    r2715 r2830  
    2929   USE zpshde          ! partial step: hor. derivative   (zps_hde routine) 
    3030   USE prtctl_trc      ! Print control passive tracers (prt_ctl_trc_init routine) 
     31   USE trcsubstp       ! variables to substep passive tracers 
    3132    
    3233   IMPLICIT NONE 
     
    122123      IF( ln_rsttr ) THEN 
    123124        ! 
    124         IF( lk_offline )  neuler = 1   ! Set time-step indicator at nit000 (leap-frog) 
     125        IF( lk_offline )  neuler = 1   ! Set time-step indicator at nittrc000 (leap-frog) 
    125126        CALL trc_rst_read              ! restart from a file 
    126127        ! 
    127128      ELSE 
    128129        IF( lk_offline )  THEN 
    129            neuler = 0                  ! Set time-step indicator at nit000 (euler) 
     130           neuler = 0                  ! Set time-step indicator at nittrc000 (euler) 
    130131           CALL day_init               ! set calendar 
    131132        ENDIF 
    132133#if defined key_dtatrc 
    133         CALL trc_dta( nit000 )      ! Initialization of tracer from a file that may also be used for damping 
     134        CALL trc_dta( nittrc000 )      ! Initialization of tracer from a file that may also be used for damping 
    134135        DO jn = 1, jptra 
    135136           IF( lutini(jn) )   trn(:,:,:,jn) = trdta(:,:,:,jn) * tmask(:,:,:)   ! initialisation from file if required 
     
    143144       
    144145      IF( ln_zps .AND. .NOT. lk_c1d )   &              ! Partial steps: before horizontal gradient of passive 
    145         &    CALL zps_hde( nit000, jptra, trn, gtru, gtrv )       ! tracers at the bottom ocean level 
     146        &    CALL zps_hde( nittrc000, jptra, trn, gtru, gtrv )       ! tracers at the bottom ocean level 
    146147 
    147148 
     
    170171         CALL prt_ctl_trc_info( charout ) 
    171172         CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm ) 
     173      ENDIF 
     174 
     175      IF(nn_dttrc .NE. 1) THEN 
     176          CALL trc_sub_stp_ini      !initialize variables for substepping passive tracers 
    172177      ENDIF 
    173178      ! 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/trcnam.F90

    r2715 r2830  
    109109      END DO 
    110110 
     111      !!KPE  computes the first time step of tracer model 
     112      nittrc000 = nit000 + nn_dttrc - 1 
     113  
    111114 
    112115      IF(lwp) THEN                   ! control print 
     
    114117         WRITE(numout,*) ' Namelist : namtrc' 
    115118         WRITE(numout,*) '    time step freq. for pass. trac. nn_dttrc             = ', nn_dttrc 
     119         WRITE(numout,*) '    first time step for pass. trac. nittrc000            = ', nittrc000 
    116120         WRITE(numout,*) '    frequency of outputs for passive tracers nn_writetrc = ', nn_writetrc   
    117121         WRITE(numout,*) '    restart LOGICAL for passive tr. ln_rsttr             = ', ln_rsttr 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/trcrst.F90

    r2715 r2830  
    6060      ! 
    6161      IF( lk_offline ) THEN 
    62          IF( kt == nit000 ) THEN 
     62         IF( kt == nittrc000 ) THEN 
    6363            lrst_trc = .FALSE. 
    6464            nitrst = nitend 
     
    7171         ENDIF 
    7272      ELSE 
    73          IF( kt == nit000 ) lrst_trc = .FALSE. 
     73         IF( kt == nittrc000 ) lrst_trc = .FALSE. 
    7474      ENDIF 
    7575 
     
    119119      ! Time domain : restart 
    120120      ! --------------------- 
    121       CALL trc_rst_cal( nit000, 'READ' )   ! calendar 
     121      CALL trc_rst_cal( nittrc000, 'READ' )   ! calendar 
    122122 
    123123      ! READ prognostic variables and computes diagnostic variable 
     
    196196      !! 
    197197      !!   According to namelist parameter nrstdt, 
    198       !!       nn_rsttr = 0  no control on the date (nit000 is  arbitrary). 
    199       !!       nn_rsttr = 1  we verify that nit000 is equal to the last 
     198      !!       nn_rsttr = 0  no control on the date (nittrc000 is  arbitrary). 
     199      !!       nn_rsttr = 1  we verify that nittrc000 is equal to the last 
    200200      !!                   time step of previous run + 1. 
    201201      !!       In both those options, the  exact duration of the experiment 
     
    223223            WRITE(numout,*) ' *** restart option' 
    224224            SELECT CASE ( nn_rsttr ) 
    225             CASE ( 0 )   ;   WRITE(numout,*) ' nn_rsttr = 0 : no control of nit000' 
    226             CASE ( 1 )   ;   WRITE(numout,*) ' nn_rsttr = 1 : no control the date at nit000 (use ndate0 read in the namelist)' 
     225            CASE ( 0 )   ;   WRITE(numout,*) ' nn_rsttr = 0 : no control of nittrc000' 
     226            CASE ( 1 )   ;   WRITE(numout,*) ' nn_rsttr = 1 : no control the date at nittrc000 (use ndate0 read in the namelist)' 
    227227            CASE ( 2 )   ;   WRITE(numout,*) ' nn_rsttr = 2 : calendar parameters read in restart' 
    228228            END SELECT 
     
    230230         ENDIF 
    231231         ! Control of date  
    232          IF( nit000  - NINT( zkt ) /= 1 .AND.  nn_rsttr /= 0 )                                  & 
    233             &   CALL ctl_stop( ' ===>>>> : problem with nit000 for the restart',                 & 
     232         IF( nittrc000  - NINT( zkt ) /= 1 .AND.  nn_rsttr /= 0 )                                  & 
     233            &   CALL ctl_stop( ' ===>>>> : problem with nittrc000 for the restart',                 & 
    234234            &                  ' verify the restart file or rerun with nn_rsttr = 0 (namelist)' ) 
    235235         IF( lk_offline ) THEN      ! set the date in offline mode 
     
    246246            ELSE 
    247247               ndastp = ndate0 - 1     ! ndate0 read in the namelist in dom_nam 
    248                adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
     248               adatrj = ( REAL( nittrc000-1, wp ) * rdttra(1) ) / rday 
    249249               ! note this is wrong if time step has changed during run 
    250250            ENDIF 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/trcstp.F90

    r2528 r2830  
    2222   USE iom 
    2323   USE in_out_manager 
     24   USE trcsubstp 
    2425 
    2526   IMPLICIT NONE 
     
    2728 
    2829   PUBLIC   trc_stp    ! called by step 
     30#  include "domzgr_substitute.h90" 
    2931    
    3032   !!---------------------------------------------------------------------- 
     
    4951      !!------------------------------------------------------------------- 
    5052 
    51       IF( MOD( kt - 1 , nn_dttrc ) == 0 ) THEN      ! only every nn_dttrc time step 
     53     IF(nn_dttrc .NE. 1) THEN 
     54        CALL trc_sub_stp(kt) 
     55     ENDIF 
     56     IF( MOD( kt , nn_dttrc ) == 0 ) THEN      ! only every nn_dttrc time step 
     57 
    5258         ! 
    5359         IF(ln_ctl) THEN 
     
    5864         tra(:,:,:,:) = 0.e0 
    5965         ! 
    60          IF( kt == nit000 .AND. lk_trdmld_trc  )  & 
     66         IF( kt == nittrc000 .AND. lk_trdmld_trc  )  & 
    6167            &                      CALL trd_mld_trc_init        ! trends: Mixed-layer 
    6268                                   CALL trc_rst_opn( kt )       ! Open tracer restart file  
     
    6672                                   CALL trc_sms( kt )           ! tracers: sink and source 
    6773                                   CALL trc_trp( kt )           ! transport of passive tracers 
    68          IF( kt == nit000 )     CALL iom_close( numrtr )     ! close input  passive tracers restart file 
     74         IF( kt == nittrc000 )     CALL iom_close( numrtr )     ! close input  passive tracers restart file 
    6975         IF( lrst_trc )            CALL trc_rst_wri( kt )       ! write tracer restart file 
    7076         IF( lk_trdmld_trc  )      CALL trd_mld_trc( kt )       ! trends: Mixed-layer 
    7177         ! 
     78         IF(nn_dttrc .NE. 1) THEN 
     79            CALL trc_sub_stp_reset(kt) 
     80         ENDIF 
    7281      ENDIF 
    7382 
  • branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/trcwri.F90

    r2567 r2830  
    5757      !!--------------------------------------------------------------------- 
    5858  
    59       IF( lk_offline .AND. kt == nit000 .AND. lwp ) THEN    ! WRITE root name in date.file for use by postpro 
     59      IF( lk_offline .AND. kt == nittrc000 .AND. lwp ) THEN    ! WRITE root name in date.file for use by postpro 
    6060         CALL dia_nam( clhstnam, nn_writetrc,' ' ) 
    6161         CALL ctl_opn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
Note: See TracChangeset for help on using the changeset viewer.