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 11504 for NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps – NEMO

Ignore:
Timestamp:
2019-09-06T09:23:31+02:00 (5 years ago)
Author:
davestorkey
Message:

2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps : Strip out all references to nn_dttrc
and the trcsub.F90 module. Notes:

  1. This version of the code currently breaks the GYRE_PISCES test in SETTE.
  2. With the removal of this option, TOP should use the OCE time index variables, eg. Nbb_trc -> Nbb, nittrc000 -> nit0000 etc.
Location:
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps
Files:
1 deleted
17 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/cfgs/SHARED/namelist_top_ref

    r10375 r11504  
    1414&namtrc_run      !   run information 
    1515!----------------------------------------------------------------------- 
    16    nn_dttrc      =  1        !  time step frequency for passive sn_tracers 
    1716   ln_top_euler  = .false.   !  use Euler time-stepping for TOP 
    1817   ln_rsttr      = .false.   !  start from a restart file (T) or not (F) 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/NST/agrif_user.F90

    r11047 r11504  
    625625      ENDIF 
    626626 
    627       ! Check passive tracer cell 
    628       IF( nn_dttrc .NE. 1 ) THEN 
    629          WRITE(*,*) 'nn_dttrc should be equal to 1' 
    630       ENDIF 
    631627   ENDIF 
    632628   ! 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/IOM/iom.F90

    r10989 r11504  
    3030#if defined key_iomput 
    3131   USE sbc_oce  , ONLY :   nn_fsbc         ! ocean space and time domain 
    32    USE trc_oce  , ONLY :   nn_dttrc        !  !: frequency of step on passive tracers 
    3332   USE icb_oce  , ONLY :   nclasses, class_num       !  !: iceberg classes 
    3433#if defined key_si3 
     
    21132112      f_op%timestep = nn_fsbc  ;  f_of%timestep =  0  ; CALL iom_set_field_attr('SBC'             , freq_op=f_op, freq_offset=f_of) 
    21142113      f_op%timestep = nn_fsbc  ;  f_of%timestep =  0  ; CALL iom_set_field_attr('SBC_scalar'      , freq_op=f_op, freq_offset=f_of) 
    2115       f_op%timestep = nn_dttrc ;  f_of%timestep =  0  ; CALL iom_set_field_attr('ptrc_T'          , freq_op=f_op, freq_offset=f_of) 
    2116       f_op%timestep = nn_dttrc ;  f_of%timestep =  0  ; CALL iom_set_field_attr('diad_T'          , freq_op=f_op, freq_offset=f_of) 
     2114      f_op%timestep = 1        ;  f_of%timestep =  0  ; CALL iom_set_field_attr('ptrc_T'          , freq_op=f_op, freq_offset=f_of) 
     2115      f_op%timestep = 1        ;  f_of%timestep =  0  ; CALL iom_set_field_attr('diad_T'          , freq_op=f_op, freq_offset=f_of) 
    21172116 
    21182117      ! output file names (attribut: name) 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/LBC/lib_mpp.F90

    r10538 r11504  
    157157   INTEGER, PUBLIC                               ::   ncom_stp = 0                 !: copy of time step # istp 
    158158   INTEGER, PUBLIC                               ::   ncom_fsbc = 1                !: copy of sbc time step # nn_fsbc 
    159    INTEGER, PUBLIC                               ::   ncom_dttrc = 1               !: copy of top time step # nn_dttrc 
    160159   INTEGER, PUBLIC                               ::   ncom_freq                    !: frequency of comm diagnostic 
    161160   INTEGER, PUBLIC , DIMENSION(:,:), ALLOCATABLE ::   ncomm_sequence               !: size of communicated arrays (halos) 
     
    14921491      ! 
    14931492      ! find the smallest common frequency: default = frequency product, if multiple, choose the larger of the 2 frequency 
    1494       IF( ncom_dttrc /= 1 )   CALL ctl_stop( 'STOP', 'mpp_report, ncom_dttrc /= 1 not coded...' )  
    14951493      ncom_freq = ncom_fsbc 
    14961494      ! 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/trc_oce.F90

    r10068 r11504  
    2626   LOGICAL , PUBLIC ::   l_co2cpl  = .false.   !: atmospheric pco2 recieved from oasis 
    2727   LOGICAL , PUBLIC ::   l_offline = .false.   !: offline passive tracers flag 
    28    INTEGER , PUBLIC ::   nn_dttrc              !: frequency of step on passive tracers 
    2928   REAL(wp), PUBLIC ::   r_si2                 !: largest depth of extinction (blue & 0.01 mg.m-3)  (RGB) 
    3029   ! 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/PISCES/P4Z/p4zsms.F90

    r10975 r11504  
    8282      ENDIF 
    8383      ! 
    84       IF( ln_pisdmp .AND. MOD( kt - nn_dttrc, nn_pisdmp ) == 0 )   CALL p4z_dmp( kt, Kbb, Kmm )      ! Relaxation of some tracers 
     84      IF( ln_pisdmp .AND. MOD( kt - 1, nn_pisdmp ) == 0 )   CALL p4z_dmp( kt, Kbb, Kmm )      ! Relaxation of some tracers 
    8585      ! 
    8686      rfact = r2dttrc 
    8787      ! 
    88       IF( ( ln_top_euler .AND. kt == nittrc000 )  .OR. ( .NOT.ln_top_euler .AND. kt <= nittrc000 + nn_dttrc ) ) THEN 
     88      IF( ( ln_top_euler .AND. kt == nittrc000 )  .OR. ( .NOT.ln_top_euler .AND. kt <= nittrc000 + 1 ) ) THEN 
    8989         rfactr  = 1. / rfact 
    9090         rfact2  = rfact / REAL( nrdttrc, wp ) 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/PISCES/SED/sedini.F90

    r10362 r11504  
    1313   USE sedarr 
    1414   USE sedadv 
    15    USE trc_oce, ONLY : nn_dttrc 
    1615   USE trcdmp_sed 
    1716   USE trcdta 
     
    684683         WRITE(numsed,*) ' ' 
    685684      ENDIF 
    686       nn_dtsed = nn_dttrc 
     685      nn_dtsed = 1 
    687686 
    688687      CLOSE( numnamsed_cfg ) 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/PISCES/SED/sedrst.F90

    r10425 r11504  
    1010   USE sed 
    1111   USE sedarr 
    12    USE trc_oce, ONLY : l_offline, nn_dttrc 
     12   USE trc_oce, ONLY : l_offline 
    1313   USE phycst , ONLY : rday 
    1414   USE iom 
     
    6464 
    6565      ! to get better performances with NetCDF format: 
    66       ! we open and define the tracer restart file one tracer time step before writing the data (-> at nitrst - 2*nn_dttrc + 1) 
    67       ! except if we write tracer restart files every tracer time step or if a tracer restart file was writen at nitend - 2*nn_dttrc + 1 
     66      ! we open and define the tracer restart file one tracer time step before writing the data (-> at nitrst - 1) 
     67      ! except if we write tracer restart files every tracer time step or if a tracer restart file was writen at nitend - 1 
    6868      IF( kt == nitrst - 2*nn_dtsed .OR. nstock == nn_dtsed .OR. ( kt == nitend - nn_dtsed .AND. .NOT. lrst_sed ) ) THEN 
    6969         ! beware of the format used to write kt (default is i8.8, that should be large enough) 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcbbl.F90

    r10985 r11504  
    5555      IF( ln_timing )   CALL timing_start('trc_bbl') 
    5656      ! 
    57       IF( .NOT. l_offline .AND. nn_dttrc == 1 ) THEN 
     57      IF( .NOT. l_offline ) THEN 
    5858         CALL bbl( kt, nittrc000, 'TRC', Kbb, Kmm )  ! Online coupling with dynamics  : Computation of bbl coef and bbl transport 
    5959         l_bbl = .FALSE.                             ! Offline coupling with dynamics : Read bbl coef and bbl transport from input files 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcrad.F90

    r11483 r11504  
    147147     ! 
    148148     IF( l_trdtrc )   ALLOCATE( ztrtrd(jpi,jpj,jpk) ) 
    149      zs2rdt = 1. / ( 2. * rdt * REAL( nn_dttrc, wp ) ) 
     149     zs2rdt = 1. / ( 2. * rdt ) 
    150150     ! 
    151151     DO jt = 1,2  ! Loop over time indices since exactly the same fix is applied to "now" and "after" fields 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcsbc.F90

    r11480 r11504  
    8484         IF( ln_rsttr .AND. .NOT.ln_top_euler .AND.   &                     ! Restart: read in restart  file 
    8585            iom_varid( numrtr, 'sbc_'//TRIM(ctrcnm(1))//'_b', ldstop = .FALSE. ) > 0 ) THEN 
    86             IF(lwp) WRITE(numout,*) '          nittrc000-nn_dttrc surface tracer content forcing fields red in the restart file' 
     86            IF(lwp) WRITE(numout,*) '          nittrc000-1 surface tracer content forcing fields read in the restart file' 
    8787            zfact = 0.5_wp 
    8888            DO jn = 1, jptra 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trdmxl_trc.F90

    r10966 r11504  
    1717   !!---------------------------------------------------------------------- 
    1818   USE trc               ! tracer definitions (tr etc.) 
    19    USE trc_oce, ONLY :   nn_dttrc  ! frequency of step on passive tracers 
    2019   USE dom_oce           ! domain definition 
    2120   USE zdfmxl  , ONLY : nmln ! number of level in the mixed layer 
     
    253252 
    254253 
    255       IF( nn_dttrc  /= 1  )   CALL ctl_stop( " Be careful, trends diags never validated " ) 
    256  
    257254      ! ====================================================================== 
    258255      ! I. Diagnose the purely vertical (K_z) diffusion trend 
     
    330327      ! II.3 Initialize mixed-layer "before" arrays for the 1rst analysis window     
    331328      ! ------------------------------------------------------------------------ 
    332       IF( kt == nittrc000 + nn_dttrc ) THEN  !  i.e. ( .NOT. ln_rstart ).AND.( kt == nit000 + 1)    ??? 
     329      IF( kt == nittrc000 + 1 ) THEN  !  i.e. ( .NOT. ln_rstart ).AND.( kt == nit000 + 1)    ??? 
    333330         ! 
    334331         DO jn = 1, jptra 
     
    872869#  endif 
    873870      zout = nn_trd_trc * rdt 
    874       iiter = ( nittrc000 - 1 ) / nn_dttrc 
     871      iiter = nittrc000 - 1 
    875872 
    876873      IF(lwp) WRITE (numout,*) '                netCDF initialization' 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trdmxl_trc_rst.F90

    r10425 r11504  
    1111   USE in_out_manager  ! I/O manager 
    1212   USE iom             ! I/O module 
    13    USE trc             ! for nn_dttrc ctrcnm 
     13   USE trc             ! for ctrcnm 
    1414   USE trdmxl_trc_oce  ! for lk_trdmxl_trc 
    1515 
     
    4444      !!-------------------------------------------------------------------------------- 
    4545 
    46       IF( kt == nitrst - nn_dttrc .OR. nitend - nit000 + 1 < 2 * nn_dttrc ) THEN ! idem trcrst.F90 
     46      IF( kt == nitrst - 1 .OR. nitend - nit000 + 1 < 2 ) THEN ! idem trcrst.F90 
    4747         IF( nitrst > 1.0e9 ) THEN 
    4848            WRITE(clkt,*) nitrst 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/trcini.F90

    r11480 r11504  
    2121   USE daymod          ! calendar manager 
    2222   USE prtctl_trc      ! Print control passive tracers (prt_ctl_trc_init routine) 
    23    USE trcsub          ! variables to substep passive tracers 
    2423   USE trcrst 
    2524   USE lib_mpp         ! distribued memory computing library 
     
    8281      ! 
    8382      CALL trc_ini_state( Nbb_trc, Nnn_trc, Naa_trc )  !  passive tracers initialisation : from a restart or from clim 
    84       IF( nn_dttrc /= 1 ) & 
    85       CALL trc_sub_ini( Nnn_trc )    ! Initialize variables for substepping passive tracers 
    8683      ! 
    8784      CALL trc_ini_inv( Nnn_trc )    ! Inventories 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/trcnam.F90

    r10425 r11504  
    2323   USE trdtrc_oce  ! 
    2424   USE iom         ! I/O manager 
    25 #if defined key_mpp_mpi 
    26    USE lib_mpp, ONLY: ncom_dttrc 
    27 #endif 
    2825 
    2926   IMPLICIT NONE 
     
    7976      ENDIF 
    8077      ! 
    81       rdttrc = rdt * FLOAT( nn_dttrc )          ! passive tracer time-step       
     78      rdttrc = rdt                              ! passive tracer time-step       
    8279      !  
    8380      IF(lwp) THEN                              ! control print 
    8481        WRITE(numout,*)  
    85         WRITE(numout,*) '   ==>>>   Passive Tracer  time step    rdttrc = nn_dttrc*rdt = ', rdttrc 
     82        WRITE(numout,*) '   ==>>>   Passive Tracer  time step    rdttrc = rdt = ', rdttrc 
    8683      ENDIF 
    8784      ! 
     
    10097      INTEGER  ::   ios   ! Local integer 
    10198      !! 
    102       NAMELIST/namtrc_run/ nn_dttrc, ln_rsttr, nn_rsttr, ln_top_euler, & 
     99      NAMELIST/namtrc_run/ ln_rsttr, nn_rsttr, ln_top_euler, & 
    103100        &                  cn_trcrst_indir, cn_trcrst_outdir, cn_trcrst_in, cn_trcrst_out 
    104101      !!--------------------------------------------------------------------- 
     
    120117      IF(lwm) WRITE( numont, namtrc_run ) 
    121118 
    122       nittrc000 = nit000 + nn_dttrc - 1      ! first time step of tracer model 
     119      nittrc000 = nit000             ! first time step of tracer model 
    123120 
    124121      IF(lwp) THEN                   ! control print 
    125122         WRITE(numout,*) '   Namelist : namtrc_run' 
    126          WRITE(numout,*) '      time step freq. for passive tracer           nn_dttrc      = ', nn_dttrc 
    127123         WRITE(numout,*) '      restart  for passive tracer                  ln_rsttr      = ', ln_rsttr 
    128124         WRITE(numout,*) '      control of time step for passive tracer      nn_rsttr      = ', nn_rsttr 
     
    130126         WRITE(numout,*) '      Use euler integration for TRC (y/n)          ln_top_euler  = ', ln_top_euler 
    131127      ENDIF 
    132       ! 
    133 #if defined key_mpp_mpi 
    134       ncom_dttrc = nn_dttrc    ! make nn_fsbc available for lib_mpp 
    135 #endif 
    136128      ! 
    137129   END SUBROUTINE trc_nam_run 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/trcrst.F90

    r10963 r11504  
    7474 
    7575      ! to get better performances with NetCDF format: 
    76       ! we open and define the tracer restart file one tracer time step before writing the data (-> at nitrst - 2*nn_dttrc + 1) 
    77       ! except if we write tracer restart files every tracer time step or if a tracer restart file was writen at nitend - 2*nn_dttrc + 1 
    78       IF( kt == nitrst - 2*nn_dttrc .OR. nstock == nn_dttrc .OR. ( kt == nitend - nn_dttrc .AND. .NOT. lrst_trc ) ) THEN 
     76      ! we open and define the tracer restart file one tracer time step before writing the data (-> at nitrst - 1) 
     77      ! except if we write tracer restart files every tracer time step or if a tracer restart file was writen at nitend - 1 
     78      IF( kt == nitrst - 1 .OR. nstock == 1 .OR. ( kt == nitend - 1 .AND. .NOT. lrst_trc ) ) THEN 
    7979         ! beware of the format used to write kt (default is i8.8, that should be large enough) 
    8080         IF( nitrst > 1.0e9 ) THEN   ;   WRITE(clkt,*       ) nitrst 
     
    219219            ENDIF 
    220220            ! Control of date  
    221             IF( nittrc000  - NINT( zkt ) /= nn_dttrc .AND.  nn_rsttr /= 0 )                                  & 
     221            IF( nittrc000  - NINT( zkt ) /= 1 .AND.  nn_rsttr /= 0 )                                  & 
    222222               &   CALL ctl_stop( ' ===>>>> : problem with nittrc000 for the restart',                 & 
    223223               &                  ' verify the restart file or rerun with nn_rsttr = 0 (namelist)' ) 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/trcstp.F90

    r11483 r11504  
    1818   USE trcwri 
    1919   USE trcrst 
    20    USE trcsub         ! 
    2120   USE trdtrc_oce 
    2221   USE trdmxl_trc 
     
    7271      IF( ( neuler == 0 .AND. kt == nittrc000 ) .OR. ln_top_euler ) THEN     ! at nittrc000 
    7372         r2dttrc =  rdttrc           ! = rdttrc (use or restarting with Euler time stepping) 
    74       ELSEIF( kt <= nittrc000 + nn_dttrc ) THEN          ! at nittrc000 or nittrc000+1 
    75          r2dttrc = 2. * rdttrc       ! = 2 rdttrc (leapfrog) 
    7673      ENDIF 
    7774      ! 
     
    9289      IF( l_trcdm2dc )   CALL trc_mean_qsr( kt ) 
    9390      !     
    94       IF( nn_dttrc == 1 )  THEN 
    95          IF( Kmm_oce /= Nnn_trc .OR. Kaa_oce /= Naa_trc .OR. Krhs_oce /= Nrhs_trc ) THEN 
    96             ! The nn_dttrc == 1 case depends on the OCE and TRC time indices being the same always.  
    97             ! If this is not the case then something has gone wrong. 
    98             CALL ctl_stop( 'trc_stp : nn_dttrc = 1 but OCE and TRC time indices are different! Something has gone wrong.' ) 
    99          ENDIF 
    100       ELSE 
    101          CALL trc_sub_stp( kt, Nbb_trc, Nnn_trc, Nrhs_trc )  ! averaging physical variables for sub-stepping 
     91      IF( Kmm_oce /= Nnn_trc .OR. Kaa_oce /= Naa_trc .OR. Krhs_oce /= Nrhs_trc ) THEN 
     92         ! The OCE and TRC time indices should be the same always.  
     93         ! If this is not the case then something has gone wrong. 
     94         CALL ctl_stop( 'trc_stp : OCE and TRC time indices are different! Something has gone wrong.' ) 
    10295      ENDIF 
    10396      !     
    104       IF( MOD( kt , nn_dttrc ) == 0 ) THEN      ! only every nn_dttrc time step 
    105          ! 
    106          IF(ln_ctl) THEN 
    107             WRITE(charout,FMT="('kt =', I4,'  d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear 
    108             CALL prt_ctl_trc_info(charout) 
    109          ENDIF 
    110          ! 
    111          tr(:,:,:,:,Nrhs_trc) = 0.e0 
    112          ! 
    113                                    CALL trc_rst_opn  ( kt )       ! Open tracer restart file  
    114          IF( lrst_trc )            CALL trc_rst_cal  ( kt, 'WRITE' )   ! calendar 
    115                                    CALL trc_wri      ( kt,          Nnn_trc                    )  ! output of passive tracers with iom I/O manager 
    116                                    CALL trc_sms      ( kt, Nbb_trc, Nnn_trc, Nrhs_trc          )  ! tracers: sinks and sources 
    117                                    CALL trc_trp      ( kt, Nbb_trc, Nnn_trc, Nrhs_trc, Naa_trc )  ! transport of passive tracers 
    118          IF( kt == nittrc000 ) THEN 
    119             CALL iom_close( numrtr )       ! close input tracer restart file 
    120             IF(lwm) CALL FLUSH( numont )   ! flush namelist output 
    121          ENDIF 
    122          IF( lrst_trc )            CALL trc_rst_wri  ( kt, Nbb_trc, Nnn_trc, Nrhs_trc )       ! write tracer restart file 
    123          IF( lk_trdmxl_trc  )      CALL trd_mxl_trc  ( kt,          Nnn_trc           )       ! trends: Mixed-layer 
    124          ! 
    125          IF( nn_dttrc /= 1   )     CALL trc_sub_reset( kt, Nbb_trc, Nnn_trc, Nrhs_trc )       ! resetting physical variables when sub-stepping 
    126          ! 
    127       ENDIF 
     97      ! 
     98      IF(ln_ctl) THEN 
     99         WRITE(charout,FMT="('kt =', I4,'  d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear 
     100         CALL prt_ctl_trc_info(charout) 
     101      ENDIF 
     102      ! 
     103      tr(:,:,:,:,Nrhs_trc) = 0.e0 
     104      ! 
     105      CALL trc_rst_opn  ( kt )       ! Open tracer restart file  
     106      IF( lrst_trc )            CALL trc_rst_cal  ( kt, 'WRITE' )   ! calendar 
     107      CALL trc_wri      ( kt,          Nnn_trc                    )  ! output of passive tracers with iom I/O manager 
     108      CALL trc_sms      ( kt, Nbb_trc, Nnn_trc, Nrhs_trc          )  ! tracers: sinks and sources 
     109      CALL trc_trp      ( kt, Nbb_trc, Nnn_trc, Nrhs_trc, Naa_trc )  ! transport of passive tracers 
     110      IF( kt == nittrc000 ) THEN 
     111         CALL iom_close( numrtr )       ! close input tracer restart file 
     112         IF(lwm) CALL FLUSH( numont )   ! flush namelist output 
     113      ENDIF 
     114      IF( lrst_trc )            CALL trc_rst_wri  ( kt, Nbb_trc, Nnn_trc, Nrhs_trc )       ! write tracer restart file 
     115      IF( lk_trdmxl_trc  )      CALL trd_mxl_trc  ( kt,          Nnn_trc           )       ! trends: Mixed-layer 
    128116      ! 
    129117      IF (ll_trcstat) THEN 
Note: See TracChangeset for help on using the changeset viewer.