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 13463 for NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/TOP/trcnam.F90 – NEMO

Ignore:
Timestamp:
2020-09-14T17:40:34+02:00 (4 years ago)
Author:
andmirek
Message:

Ticket #2195:update to trunk 13461

Location:
NEMO/branches/2019/dev_r11351_fldread_with_XIOS
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS

    • Property svn:externals
      •  

        old new  
        33^/utils/build/mk@HEAD         mk 
        44^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
         5^/vendors/AGRIF/dev_r12970_AGRIF_CMEMS      ext/AGRIF 
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
         8 
         9# SETTE 
         10^/utils/CI/sette@13382        sette 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/TOP/trcnam.F90

    r10425 r13463  
    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       
    82       !  
    8378      IF(lwp) THEN                              ! control print 
    8479        WRITE(numout,*)  
    85         WRITE(numout,*) '   ==>>>   Passive Tracer  time step    rdttrc = nn_dttrc*rdt = ', rdttrc 
     80        WRITE(numout,*) '   ==>>>   Passive Tracer time step = rn_Dt = ', rn_Dt 
    8681      ENDIF 
    8782      ! 
     
    10095      INTEGER  ::   ios   ! Local integer 
    10196      !! 
    102       NAMELIST/namtrc_run/ nn_dttrc, ln_rsttr, nn_rsttr, ln_top_euler, & 
     97      NAMELIST/namtrc_run/ ln_rsttr, nn_rsttr, ln_top_euler, & 
    10398        &                  cn_trcrst_indir, cn_trcrst_outdir, cn_trcrst_in, cn_trcrst_out 
    10499      !!--------------------------------------------------------------------- 
     
    108103      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 
    109104      ! 
    110       CALL ctl_opn( numnat_ref, 'namelist_top_ref'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
    111       CALL ctl_opn( numnat_cfg, 'namelist_top_cfg'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
     105      CALL load_nml( numnat_ref, 'namelist_top_ref' , numout, lwm ) 
     106      CALL load_nml( numnat_cfg, 'namelist_top_cfg' , numout, lwm ) 
    112107      IF(lwm) CALL ctl_opn( numont, 'output.namelist.top', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., 1 ) 
    113108      ! 
    114       REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables 
    115109      READ  ( numnat_ref, namtrc_run, IOSTAT = ios, ERR = 901) 
    116 901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp ) 
    117       REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables 
     110901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc in reference namelist' ) 
    118111      READ  ( numnat_cfg, namtrc_run, IOSTAT = ios, ERR = 902 ) 
    119 902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp ) 
     112902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrc in configuration namelist' ) 
    120113      IF(lwm) WRITE( numont, namtrc_run ) 
    121114 
    122       nittrc000 = nit000 + nn_dttrc - 1      ! first time step of tracer model 
     115      nittrc000 = nit000             ! first time step of tracer model 
    123116 
    124117      IF(lwp) THEN                   ! control print 
    125118         WRITE(numout,*) '   Namelist : namtrc_run' 
    126          WRITE(numout,*) '      time step freq. for passive tracer           nn_dttrc      = ', nn_dttrc 
    127119         WRITE(numout,*) '      restart  for passive tracer                  ln_rsttr      = ', ln_rsttr 
    128120         WRITE(numout,*) '      control of time step for passive tracer      nn_rsttr      = ', nn_rsttr 
     
    131123      ENDIF 
    132124      ! 
    133 #if defined key_mpp_mpi 
    134       ncom_dttrc = nn_dttrc    ! make nn_fsbc available for lib_mpp 
    135 #endif 
    136       ! 
    137125   END SUBROUTINE trc_nam_run 
    138126 
     
    148136      !! 
    149137      NAMELIST/namtrc/jp_bgc, ln_pisces, ln_my_trc, ln_age, ln_cfc11, ln_cfc12, ln_sf6, ln_c14, & 
    150          &            sn_tracer, ln_trcdta, ln_trcdmp, ln_trcdmp_clo, jp_dia3d, jp_dia2d 
     138         &            sn_tracer, ln_trcdta, ln_trcbc, ln_trcdmp, ln_trcdmp_clo, jp_dia3d, jp_dia2d 
    151139      !!--------------------------------------------------------------------- 
    152140      ! Dummy settings to fill tracers data structure 
     
    158146      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 
    159147 
    160       REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables 
    161148      READ  ( numnat_ref, namtrc, IOSTAT = ios, ERR = 901) 
    162 901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp ) 
    163       REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables 
     149901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc in reference namelist' ) 
    164150      READ  ( numnat_cfg, namtrc, IOSTAT = ios, ERR = 902 ) 
    165 902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp ) 
     151902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrc in configuration namelist' ) 
    166152      IF(lwm) WRITE( numont, namtrc ) 
    167153 
     
    222208         WRITE(numout,*) '      Simulating C14   passive tracer              ln_c14        = ', ln_c14 
    223209         WRITE(numout,*) '      Read inputs data from file (y/n)             ln_trcdta     = ', ln_trcdta 
     210         WRITE(numout,*) '      Enable surface, lateral or open boundaries conditions (y/n)  ln_trcbc  = ', ln_trcbc 
    224211         WRITE(numout,*) '      Damping of passive tracer (y/n)              ln_trcdmp     = ', ln_trcdmp 
    225212         WRITE(numout,*) '      Restoring of tracer on closed seas           ln_trcdmp_clo = ', ln_trcdmp_clo 
     
    228215      IF( ll_cfc .OR. ln_c14 ) THEN 
    229216        !                             ! Open namelist files 
    230         CALL ctl_opn( numtrc_ref, 'namelist_trc_ref'   ,     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
    231         CALL ctl_opn( numtrc_cfg, 'namelist_trc_cfg'   ,     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
     217        CALL load_nml( numtrc_ref, 'namelist_trc_ref' , numout, lwm ) 
     218        CALL load_nml( numtrc_cfg, 'namelist_trc_cfg' , numout, lwm ) 
    232219        IF(lwm) CALL ctl_opn( numonr, 'output.namelist.trc', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
    233220        ! 
     
    261248      ALLOCATE( ln_trdtrc(jptra) )  
    262249      ! 
    263       REWIND( numnat_ref )              ! Namelist namtrc_trd in reference namelist : Passive tracer trends 
    264250      READ  ( numnat_ref, namtrc_trd, IOSTAT = ios, ERR = 905) 
    265 905   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_trd in reference namelist', lwp ) 
    266       REWIND( numnat_cfg )              ! Namelist namtrc_trd in configuration namelist : Passive tracer trends 
     251905   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_trd in reference namelist' ) 
    267252      READ  ( numnat_cfg, namtrc_trd, IOSTAT = ios, ERR = 906 ) 
    268 906   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrc_trd in configuration namelist', lwp ) 
     253906   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrc_trd in configuration namelist' ) 
    269254      IF(lwm) WRITE( numont, namtrc_trd ) 
    270255 
Note: See TracChangeset for help on using the changeset viewer.