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/NEMOGCM/NEMO/TOP_SRC/TRP – 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/TOP_SRC/TRP
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • 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:' 
Note: See TracChangeset for help on using the changeset viewer.