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 11358 for NEMO – NEMO

Changeset 11358 for NEMO


Ignore:
Timestamp:
2019-07-26T16:10:19+02:00 (5 years ago)
Author:
smasson
Message:

dev_r10984_HPC-13 : supress output files with nn_stock and nn_write = -1, see #2285

Location:
NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization
Files:
1 deleted
18 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/cfgs/SHARED/namelist_ref

    r11317 r11358  
    5050      cn_ocerst_indir = "."         !  directory from which to read input ocean restarts 
    5151      cn_ocerst_out   = "restart"   !  suffix of ocean restart name (output) 
    52       cn_ocerst_outdir = "."         !  directory in which to write output ocean restarts 
     52      cn_ocerst_outdir = "."        !  directory in which to write output ocean restarts 
    5353   ln_iscpl    = .false.   !  cavity evolution forcing or coupling to ice sheet model 
    5454   nn_istate   =       0   !  output the initial state (1) or not (0) 
    5555   ln_rst_list = .false.   !  output restarts at list of times using nn_stocklist (T) or at set frequency with nn_stock (F) 
    56    nn_stock    =    5840   !  frequency of creation of a restart file (modulo referenced to 1) 
     56   nn_stock    =       0   !  used only if ln_rst_list = F: output restart freqeuncy (modulo referenced to 1) 
     57      !                          !    =  0 force to write restart files only at the end of the run 
     58      !                          !    = -1 do not do any restart 
    5759   nn_stocklist = 0,0,0,0,0,0,0,0,0,0 ! List of timesteps when a restart file is to be written 
    58    nn_write    =    5840   !  frequency of write in the output file   (modulo referenced to nn_it000) 
    59    ln_mskland  = .false.   !  mask land points in NetCDF outputs (costly: + ~15%) 
     60   nn_write    =       0   !  used only if key_iomput is not defined: output frequency (modulo referenced to nn_it000) 
     61      !                          !    =  0 force to write output files only at the end of the run 
     62      !                          !    = -1 do not do any output file 
     63   ln_mskland  = .false.   !  mask land points in NetCDF outputs 
    6064   ln_cfmeta   = .false.   !  output additional data to netCDF files required for compliance with the CF metadata standard 
    6165   ln_clobber  = .true.    !  clobber (overwrite) an existing file 
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/ICE/icerst.F90

    r10425 r11358  
    5353      IF( kt == nit000 )   lrst_ice = .FALSE.   ! default definition 
    5454 
     55      IF( ln_rst_list .OR. nn_stock /= -1 ) THEN 
    5556      ! in order to get better performances with NetCDF format, we open and define the ice restart file  
    5657      ! one ice time step before writing the data (-> at nitrst - 2*nn_fsbc + 1), except if we write ice  
    5758      ! restart files every ice time step or if an ice restart file was writen at nitend - 2*nn_fsbc + 1 
    58       IF( kt == nitrst - 2*nn_fsbc + 1 .OR. nstock == nn_fsbc    & 
     59      IF( kt == nitrst - 2*nn_fsbc + 1 .OR. nn_stock == nn_fsbc    & 
    5960         &                             .OR. ( kt == nitend - nn_fsbc + 1 .AND. .NOT. lrst_ice ) ) THEN 
    6061         IF( nitrst <= nitend .AND. nitrst > 0 ) THEN 
     
    8182         ENDIF 
    8283      ENDIF 
     84      ENDIF 
    8385      ! 
    8486      IF( ln_icectl )   CALL ice_prt( kt, iiceprt, jiceprt, 1, ' - Beginning the time step - ' )   ! control print 
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/OCE/BDY/bdyvol.F90

    r11234 r11358  
    143143      ! Check the cumulated transport through unstructured OBC once barotropic velocities corrected 
    144144      ! ------------------------------------------------------ 
    145       IF( MOD( kt, nwrite ) == 0 .AND. ( kc == 1 ) ) THEN 
     145      IF( MOD( kt, nn_write ) == 0 .AND. ( kc == 1 ) ) THEN 
    146146         ! 
    147147         ! compute residual transport across boundary 
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/OCE/DIA/diawri.F90

    r11325 r11358  
    426426      !!      define all the NETCDF files and fields 
    427427      !!      At each time step call histdef to compute the mean if ncessary 
    428       !!      Each nwrite time step, output the instantaneous or mean fields 
     428      !!      Each nn_write time step, output the instantaneous or mean fields 
    429429      !!---------------------------------------------------------------------- 
    430430      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
     
    442442      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zw3d       ! 3D workspace 
    443443      !!---------------------------------------------------------------------- 
    444       !  
    445       IF( ln_timing )   CALL timing_start('dia_wri') 
    446444      ! 
    447445      IF( ninist == 1 ) THEN     !==  Output the initial state and forcings  ==! 
     
    450448      ENDIF 
    451449      ! 
     450      IF( nn_write == -1 )   RETURN   ! we will never do any output 
     451      !  
     452      IF( ln_timing )   CALL timing_start('dia_wri') 
     453      ! 
    452454      ! 0. Initialisation 
    453455      ! ----------------- 
     
    459461      clop = "x"         ! no use of the mask value (require less cpu time and otherwise the model crashes) 
    460462#if defined key_diainstant 
    461       zsto = nwrite * rdt 
     463      zsto = nn_write * rdt 
    462464      clop = "inst("//TRIM(clop)//")" 
    463465#else 
     
    465467      clop = "ave("//TRIM(clop)//")" 
    466468#endif 
    467       zout = nwrite * rdt 
     469      zout = nn_write * rdt 
    468470      zmax = ( nitend - nit000 + 1 ) * rdt 
    469471 
     
    496498         ! WRITE root name in date.file for use by postpro 
    497499         IF(lwp) THEN 
    498             CALL dia_nam( clhstnam, nwrite,' ' ) 
     500            CALL dia_nam( clhstnam, nn_write,' ' ) 
    499501            CALL ctl_opn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    500502            WRITE(inum,*) clhstnam 
     
    504506         ! Define the T grid FILE ( nid_T ) 
    505507 
    506          CALL dia_nam( clhstnam, nwrite, 'grid_T' ) 
     508         CALL dia_nam( clhstnam, nn_write, 'grid_T' ) 
    507509         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam    ! filename 
    508510         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,           &  ! Horizontal grid: glamt and gphit 
     
    540542         ! Define the U grid FILE ( nid_U ) 
    541543 
    542          CALL dia_nam( clhstnam, nwrite, 'grid_U' ) 
     544         CALL dia_nam( clhstnam, nn_write, 'grid_U' ) 
    543545         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam    ! filename 
    544546         CALL histbeg( clhstnam, jpi, glamu, jpj, gphiu,           &  ! Horizontal grid: glamu and gphiu 
     
    553555         ! Define the V grid FILE ( nid_V ) 
    554556 
    555          CALL dia_nam( clhstnam, nwrite, 'grid_V' )                   ! filename 
     557         CALL dia_nam( clhstnam, nn_write, 'grid_V' )                   ! filename 
    556558         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam 
    557559         CALL histbeg( clhstnam, jpi, glamv, jpj, gphiv,           &  ! Horizontal grid: glamv and gphiv 
     
    566568         ! Define the W grid FILE ( nid_W ) 
    567569 
    568          CALL dia_nam( clhstnam, nwrite, 'grid_W' )                   ! filename 
     570         CALL dia_nam( clhstnam, nn_write, 'grid_W' )                   ! filename 
    569571         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam 
    570572         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,           &  ! Horizontal grid: glamt and gphit 
     
    741743      ! donne le nombre d'elements, et ndex la liste des indices a sortir 
    742744 
    743       IF( lwp .AND. MOD( itmod, nwrite ) == 0 ) THEN  
     745      IF( lwp .AND. MOD( itmod, nn_write ) == 0 ) THEN  
    744746         WRITE(numout,*) 'dia_wri : write model outputs in NetCDF files at ', kt, 'time-step' 
    745747         WRITE(numout,*) '~~~~~~ ' 
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/OCE/DOM/domain.F90

    r11320 r11358  
    336336            WRITE(numout,*) '      frequency of restart file       nn_stock        = ', nn_stock 
    337337         ENDIF 
     338#if ! defined key_iomput 
    338339         WRITE(numout,*) '      frequency of output file        nn_write        = ', nn_write 
     340#endif 
    339341         WRITE(numout,*) '      mask land points                ln_mskland      = ', ln_mskland 
    340342         WRITE(numout,*) '      additional CF standard metadata ln_cfmeta       = ', ln_cfmeta 
     
    358360      nleapy = nn_leapy 
    359361      ninist = nn_istate 
    360       nstock = nn_stock 
    361       nstocklist = nn_stocklist 
    362       nwrite = nn_write 
    363362      neuler = nn_euler 
    364363      IF( neuler == 1 .AND. .NOT. ln_rstart ) THEN 
     
    369368      ENDIF 
    370369      !                             ! control of output frequency 
    371       IF( nstock == 0 .OR. nstock > nitend ) THEN 
    372          WRITE(ctmp1,*) 'nstock = ', nstock, ' it is forced to ', nitend 
     370      IF( .NOT. ln_rst_list ) THEN     ! we use nn_stock 
     371         IF( nn_stock == -1 )   CALL ctl_warn( 'nn_stock = -1 --> no restart will be done' ) 
     372         IF( nn_stock == 0 .OR. nn_stock > nitend ) THEN 
     373            WRITE(ctmp1,*) 'nn_stock = ', nn_stock, ' it is forced to ', nitend 
     374            CALL ctl_warn( ctmp1 ) 
     375            nn_stock = nitend 
     376         ENDIF 
     377      ENDIF 
     378#if ! defined key_iomput 
     379      IF( nn_write == -1 )   CALL ctl_warn( 'nn_write = -1 --> no output files will be done' ) 
     380      IF ( nn_write == 0 ) THEN 
     381         WRITE(ctmp1,*) 'nn_write = ', nn_write, ' it is forced to ', nitend 
    373382         CALL ctl_warn( ctmp1 ) 
    374          nstock = nitend 
    375       ENDIF 
    376       IF ( nwrite == 0 ) THEN 
    377          WRITE(ctmp1,*) 'nwrite = ', nwrite, ' it is forced to ', nitend 
    378          CALL ctl_warn( ctmp1 ) 
    379          nwrite = nitend 
    380       ENDIF 
     383         nn_write = nitend 
     384      ENDIF 
     385#endif 
    381386 
    382387#if defined key_agrif 
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/OCE/IOM/in_out_manager.F90

    r11317 r11358  
    8080   INTEGER       ::   nleapy                      !: Leap year calendar flag (0/1 or 30) 
    8181   INTEGER       ::   ninist                      !: initial state output flag (0/1) 
    82    INTEGER       ::   nwrite                      !: model standard output frequency 
    83    INTEGER       ::   nstock                      !: restart file frequency 
    84    INTEGER, DIMENSION(10) :: nstocklist           !: restart dump times 
    8582 
    8683   !!---------------------------------------------------------------------- 
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/OCE/IOM/restart.F90

    r10425 r11358  
    7070         IF( ln_rst_list ) THEN 
    7171            nrst_lst = 1 
    72             nitrst = nstocklist( nrst_lst ) 
     72            nitrst = nn_stocklist( nrst_lst ) 
    7373         ELSE 
    7474            nitrst = nitend 
    7575         ENDIF 
    7676      ENDIF 
     77       
     78      IF( .NOT. ln_rst_list .AND. nn_stock == -1 )   RETURN   ! we will never do any restart 
    7779 
    7880      ! frequency-based restart dumping (nn_stock) 
    79       IF( .NOT. ln_rst_list .AND. MOD( kt - 1, nstock ) == 0 ) THEN    
     81      IF( .NOT. ln_rst_list .AND. MOD( kt - 1, nn_stock ) == 0 ) THEN    
    8082         ! we use kt - 1 and not kt - nit000 to keep the same periodicity from the beginning of the experiment 
    81          nitrst = kt + nstock - 1                  ! define the next value of nitrst for restart writing 
     83         nitrst = kt + nn_stock - 1                  ! define the next value of nitrst for restart writing 
    8284         IF( nitrst > nitend )   nitrst = nitend   ! make sure we write a restart at the end of the run 
    8385      ENDIF 
     
    8587      ! we open and define the ocean restart file one time step before writing the data (-> at nitrst - 1) 
    8688      ! except if we write ocean restart files every time step or if an ocean restart file was writen at nitend - 1 
    87       IF( kt == nitrst - 1 .OR. nstock == 1 .OR. ( kt == nitend .AND. .NOT. lrst_oce ) ) THEN 
     89      IF( kt == nitrst - 1 .OR. nn_stock == 1 .OR. ( kt == nitend .AND. .NOT. lrst_oce ) ) THEN 
    8890         IF( nitrst <= nitend .AND. nitrst > 0 ) THEN  
    8991            ! beware of the format used to write kt (default is i8.8, that should be large enough...) 
     
    184186         lrst_oce = .FALSE. 
    185187            IF( ln_rst_list ) THEN 
    186                nrst_lst = MIN(nrst_lst + 1, SIZE(nstocklist,1)) 
    187                nitrst = nstocklist( nrst_lst ) 
     188               nrst_lst = MIN(nrst_lst + 1, SIZE(nn_stocklist,1)) 
     189               nitrst = nn_stocklist( nrst_lst ) 
    188190            ENDIF 
    189191      ENDIF 
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/OCE/SBC/sbcmod.F90

    r11317 r11358  
    307307      ! 
    308308      !                             !* check consistency between model timeline and nn_fsbc 
    309       IF( MOD( nitend - nit000 + 1, nn_fsbc) /= 0 .OR.   & 
    310           MOD( nstock             , nn_fsbc) /= 0 ) THEN 
    311          WRITE(ctmp1,*) 'sbc_init : experiment length (', nitend - nit000 + 1, ') or nstock (', nstock,   & 
    312             &           ' is NOT a multiple of nn_fsbc (', nn_fsbc, ')' 
    313          CALL ctl_stop( ctmp1, 'Impossible to properly do model restart' ) 
     309      IF( ln_rst_list .OR. nn_stock /= -1 ) THEN   ! we will do restart files 
     310         IF( MOD( nitend - nit000 + 1, nn_fsbc) /= 0 ) THEN 
     311            WRITE(ctmp1,*) 'sbc_init : experiment length (', nitend - nit000 + 1, ') is NOT a multiple of nn_fsbc (', nn_fsbc, ')' 
     312            CALL ctl_stop( ctmp1, 'Impossible to properly do model restart' ) 
     313         ENDIF 
     314         IF( .NOT. ln_rst_list .AND. MOD( nn_stock, nn_fsbc) /= 0 ) THEN   ! we don't use nn_stock if ln_rst_list 
     315            WRITE(ctmp1,*) 'sbc_init : nn_stock (', nn_stock, ') is NOT a multiple of nn_fsbc (', nn_fsbc, ')' 
     316            CALL ctl_stop( ctmp1, 'Impossible to properly do model restart' ) 
     317         ENDIF 
    314318      ENDIF 
    315319      ! 
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/OCE/STO/stopar.F90

    r11353 r11358  
    750750      CHARACTER(LEN=9)    ::   clsto3d='sto3d_000' ! stochastic parameter variable name 
    751751      CHARACTER(LEN=10)   ::   clseed='seed0_0000' ! seed variable name 
    752  
     752      !!---------------------------------------------------------------------- 
     753 
     754      IF( .NOT. ln_rst_list .AND. nn_stock == -1 ) RETURN   ! we will never do any restart 
     755       
    753756      IF ( jpsto2d > 0 .OR. jpsto3d > 0 ) THEN 
    754757 
     
    790793         ! Open the restart file one timestep before writing restart 
    791794         IF( kt < nitend) THEN 
    792          IF( kt == nitrst - 1 .OR. nstock == 1 .OR. kt == nitend-1 ) THEN 
     795         IF( kt == nitrst - 1 .OR. nn_stock == 1 .OR. kt == nitend-1 ) THEN 
    793796            ! create the filename 
    794797            IF( nitrst > 999999999 ) THEN   ;   WRITE(clkt, *       ) nitrst 
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/OCE/TRD/trdmxl_rst.F90

    r10425 r11358  
    4747      !!-------------------------------------------------------------------------------- 
    4848 
     49      IF( .NOT. ln_rst_list .AND. nn_stock == -1 )   RETURN   ! we will never do any restart 
     50 
    4951      ! to get better performances with NetCDF format: 
    5052      ! we open and define the ocean restart_mxl file one time step before writing the data (-> at nitrst - 1) 
    5153      ! except if we write ocean restart_mxl files every time step or if an ocean restart_mxl file was writen at nitend - 1 
    52       IF( kt == nitrst - 1 .OR. nstock == 1 .OR. ( kt == nitend .AND. MOD( nitend - 1, nstock ) == 0 ) ) THEN 
     54      IF( kt == nitrst - 1 .OR. nn_stock == 1 .OR. ( kt == nitend .AND. MOD( nitend - 1, nn_stock ) == 0 ) ) THEN 
    5355         ! beware of the format used to write kt (default is i8.8, that should be large enough...) 
    5456         IF( nitrst > 999999999 ) THEN   ;   WRITE(clkt, *       ) nitrst 
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/OCE/TRD/trdvor.F90

    r10425 r11358  
    4646   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   vor_avr      ! average 
    4747   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   vor_avrb     ! before vorticity (kt-1) 
    48    REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   vor_avrbb    ! vorticity at begining of the nwrite-1 timestep averaging period 
     48   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   vor_avrbb    ! vorticity at begining of the nn_write-1 timestep averaging period 
    4949   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   vor_avrbn    ! after vorticity at time step after the 
    50    REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   rotot        ! begining of the NWRITE-1 timesteps 
     50   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   rotot        ! begining of the NN_WRITE-1 timesteps 
    5151   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   vor_avrtot   ! 
    5252   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   vor_avrres   ! 
     
    129129      !!              from ocean surface down to control surface (NetCDF output) 
    130130      !! 
    131       !! ** Method/usage :   integration done over nwrite-1 time steps 
     131      !! ** Method/usage :   integration done over nn_write-1 time steps 
    132132      !! 
    133133      !! ** Action :   trends : 
     
    143143      !!                  vortrd (,,10) = forcing term 
    144144      !!                  vortrd (,,11) = bottom friction term 
    145       !!                  rotot(,) : total cumulative trends over nwrite-1 time steps 
     145      !!                  rotot(,) : total cumulative trends over nn_write-1 time steps 
    146146      !!                  vor_avrtot(,) : first membre of vrticity equation 
    147147      !!                  vor_avrres(,) : residual = dh/dt entrainment 
     
    214214      !!              from ocean surface down to control surface (NetCDF output) 
    215215      !! 
    216       !! ** Method/usage :   integration done over nwrite-1 time steps 
     216      !! ** Method/usage :   integration done over nn_write-1 time steps 
    217217      !! 
    218218      !! ** Action :     trends : 
     
    228228      !!                  vortrd (,,10) = forcing term 
    229229      !!      vortrd (,,11) = bottom friction term 
    230       !!                  rotot(,) : total cumulative trends over nwrite-1 time steps 
     230      !!                  rotot(,) : total cumulative trends over nn_write-1 time steps 
    231231      !!                  vor_avrtot(,) : first membre of vrticity equation 
    232232      !!                  vor_avrres(,) : residual = dh/dt entrainment 
     
    360360      ENDIF 
    361361 
    362       ! II.2 cumulated trends over analysis period (kt=2 to nwrite) 
     362      ! II.2 cumulated trends over analysis period (kt=2 to nn_write) 
    363363      ! ---------------------- 
    364       ! trends cumulated over nwrite-2 time steps 
     364      ! trends cumulated over nn_write-2 time steps 
    365365 
    366366      IF( kt >= nit000+2 ) THEN 
     
    376376      !   III. Output in netCDF + residual computation 
    377377      !  ============================================= 
    378  
     378       
    379379      ! define time axis 
    380380      it    = kt 
     
    504504      ENDIF 
    505505#if defined key_diainstant 
    506       zsto = nwrite*rdt 
     506      zsto = nn_write*rdt 
    507507      clop = "inst("//TRIM(clop)//")" 
    508508#else 
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/SAS/diawri.F90

    r10425 r11358  
    125125      !!      define all the NETCDF files and fields 
    126126      !!      At each time step call histdef to compute the mean if ncessary 
    127       !!      Each nwrite time step, output the instantaneous or mean fields 
     127      !!      Each nn_write time step, output the instantaneous or mean fields 
    128128      !!---------------------------------------------------------------------- 
    129129      !! 
     
    138138      REAL(wp) ::   zsto, zout, zmax, zjulian                ! local scalars 
    139139      !!---------------------------------------------------------------------- 
    140       !  
    141       IF( ln_timing )   CALL timing_start('dia_wri') 
    142140      ! 
    143141      ! Output the initial state and forcings 
     
    147145      ENDIF 
    148146      ! 
     147      IF( nn_write == -1 )   RETURN   ! we will never do any output 
     148      !  
     149      IF( ln_timing )   CALL timing_start('dia_wri') 
     150      ! 
    149151      ! 0. Initialisation 
    150152      ! ----------------- 
     
    159161      ENDIF 
    160162#if defined key_diainstant 
    161       zsto = nwrite * rdt 
     163      zsto = nn_write * rdt 
    162164      clop = "inst("//TRIM(clop)//")" 
    163165#else 
     
    165167      clop = "ave("//TRIM(clop)//")" 
    166168#endif 
    167       zout = nwrite * rdt 
     169      zout = nn_write * rdt 
    168170      zmax = ( nitend - nit000 + 1 ) * rdt 
    169171 
     
    196198         ! WRITE root name in date.file for use by postpro 
    197199         IF(lwp) THEN 
    198             CALL dia_nam( clhstnam, nwrite,' ' ) 
     200            CALL dia_nam( clhstnam, nn_write,' ' ) 
    199201            CALL ctl_opn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    200202            WRITE(inum,*) clhstnam 
     
    204206         ! Define the T grid FILE ( nid_T ) 
    205207 
    206          CALL dia_nam( clhstnam, nwrite, 'grid_T' ) 
     208         CALL dia_nam( clhstnam, nn_write, 'grid_T' ) 
    207209         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam    ! filename 
    208210         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,           &  ! Horizontal grid: glamt and gphit 
     
    216218         ! Define the U grid FILE ( nid_U ) 
    217219 
    218          CALL dia_nam( clhstnam, nwrite, 'grid_U' ) 
     220         CALL dia_nam( clhstnam, nn_write, 'grid_U' ) 
    219221         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam    ! filename 
    220222         CALL histbeg( clhstnam, jpi, glamu, jpj, gphiu,           &  ! Horizontal grid: glamu and gphiu 
     
    228230         ! Define the V grid FILE ( nid_V ) 
    229231 
    230          CALL dia_nam( clhstnam, nwrite, 'grid_V' )                   ! filename 
     232         CALL dia_nam( clhstnam, nn_write, 'grid_V' )                   ! filename 
    231233         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam 
    232234         CALL histbeg( clhstnam, jpi, glamv, jpj, gphiv,           &  ! Horizontal grid: glamv and gphiv 
     
    291293      ! donne le nombre d'elements, et ndex la liste des indices a sortir 
    292294 
    293       IF( lwp .AND. MOD( itmod, nwrite ) == 0 ) THEN  
     295      IF( lwp .AND. MOD( itmod, nn_write ) == 0 ) THEN  
    294296         WRITE(numout,*) 'dia_wri : write model outputs in NetCDF files at ', kt, 'time-step' 
    295297         WRITE(numout,*) '~~~~~~ ' 
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/TOP/PISCES/SED/sedrst.F90

    r10425 r11358  
    4949            IF( ln_rst_list ) THEN 
    5050               nrst_lst = 1 
    51                nitrst = nstocklist( nrst_lst ) 
     51               nitrst = nn_stocklist( nrst_lst ) 
    5252            ELSE 
    5353               nitrst = nitend 
    5454            ENDIF 
    5555         ENDIF 
    56          IF( .NOT. ln_rst_list .AND. MOD( kt - 1, nstock ) == 0 ) THEN 
     56         IF( .NOT. ln_rst_list .AND. MOD( kt - 1, nn_stock ) == 0 ) THEN 
    5757            ! we use kt - 1 and not kt - nittrc000 to keep the same periodicity from the beginning of the experiment 
    58             nitrst = kt + nstock - 1                  ! define the next value of nitrst for restart writing 
     58            nitrst = kt + nn_stock - 1                  ! define the next value of nitrst for restart writing 
    5959            IF( nitrst > nitend )   nitrst = nitend   ! make sure we write a restart at the end of the run 
    6060         ENDIF 
     
    6262         IF( kt == nittrc000 ) lrst_sed = .FALSE. 
    6363      ENDIF 
     64 
     65      IF( .NOT. ln_rst_list .AND. nn_stock == -1 )   RETURN   ! we will never do any restart 
    6466 
    6567      ! to get better performances with NetCDF format: 
    6668      ! we open and define the tracer restart file one tracer time step before writing the data (-> at nitrst - 2*nn_dttrc + 1) 
    6769      ! 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 
    68       IF( kt == nitrst - 2*nn_dtsed .OR. nstock == nn_dtsed .OR. ( kt == nitend - nn_dtsed .AND. .NOT. lrst_sed ) ) THEN 
     70      IF( kt == nitrst - 2*nn_dtsed .OR. nn_stock == nn_dtsed .OR. ( kt == nitend - nn_dtsed .AND. .NOT. lrst_sed ) ) THEN 
    6971         ! beware of the format used to write kt (default is i8.8, that should be large enough) 
    7072         IF( nitrst > 1.0e9 ) THEN   ;   WRITE(clkt,*       ) nitrst 
     
    300302          IF( l_offline .AND. ln_rst_list ) THEN 
    301303             nrst_lst = nrst_lst + 1 
    302              nitrst = nstocklist( nrst_lst ) 
     304             nitrst = nn_stocklist( nrst_lst ) 
    303305          ENDIF 
    304306      ENDIF 
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/TOP/trcrst.F90

    r10425 r11358  
    5858            IF( ln_rst_list ) THEN 
    5959               nrst_lst = 1 
    60                nitrst = nstocklist( nrst_lst ) 
     60               nitrst = nn_stocklist( nrst_lst ) 
    6161            ELSE 
    6262               nitrst = nitend 
     
    6464         ENDIF 
    6565 
    66          IF( .NOT. ln_rst_list .AND. MOD( kt - 1, nstock ) == 0 ) THEN 
     66         IF( .NOT. ln_rst_list .AND. MOD( kt - 1, nn_stock ) == 0 ) THEN 
    6767            ! we use kt - 1 and not kt - nittrc000 to keep the same periodicity from the beginning of the experiment 
    68             nitrst = kt + nstock - 1                  ! define the next value of nitrst for restart writing 
     68            nitrst = kt + nn_stock - 1                  ! define the next value of nitrst for restart writing 
    6969            IF( nitrst > nitend )   nitrst = nitend   ! make sure we write a restart at the end of the run 
    7070         ENDIF 
     
    7272         IF( kt == nittrc000 ) lrst_trc = .FALSE. 
    7373      ENDIF 
     74 
     75      IF( .NOT. ln_rst_list .AND. nn_stock == -1 )   RETURN   ! we will never do any restart 
    7476 
    7577      ! to get better performances with NetCDF format: 
    7678      ! we open and define the tracer restart file one tracer time step before writing the data (-> at nitrst - 2*nn_dttrc + 1) 
    7779      ! 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 
     80      IF( kt == nitrst - 2*nn_dttrc .OR. nn_stock == nn_dttrc .OR. ( kt == nitend - nn_dttrc .AND. .NOT. lrst_trc ) ) THEN 
    7981         ! beware of the format used to write kt (default is i8.8, that should be large enough) 
    8082         IF( nitrst > 1.0e9 ) THEN   ;   WRITE(clkt,*       ) nitrst 
     
    153155          IF( l_offline .AND. ln_rst_list ) THEN 
    154156             nrst_lst = nrst_lst + 1 
    155              nitrst = nstocklist( nrst_lst ) 
     157             nitrst = nn_stocklist( nrst_lst ) 
    156158          ENDIF 
    157159      ENDIF 
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/tests/BENCH/EXPREF/namelist_cfg_orca025_like

    r10539 r11358  
    99   nn_it000    =       1   !  first time step 
    1010   nn_itend    =    1000   !  last time step  
    11    nn_stock    =       0   !  frequency of creation of a restart file (modulo referenced to 1) 
    12    nn_write    =       0   !  frequency of write in the output file   (modulo referenced to nn_it000) 
     11   nn_stock    =      -1   !  frequency of creation of a restart file (modulo referenced to 1) 
     12   nn_write    =      -1   !  frequency of write in the output file   (modulo referenced to nn_it000) 
    1313/ 
    1414!----------------------------------------------------------------------- 
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/tests/BENCH/EXPREF/namelist_cfg_orca12_like

    r10539 r11358  
    99   nn_it000    =       1   !  first time step 
    1010   nn_itend    =    1000   !  last time step  
    11    nn_stock    =       0   !  frequency of creation of a restart file (modulo referenced to 1) 
    12    nn_write    =       0   !  frequency of write in the output file   (modulo referenced to nn_it000) 
     11   nn_stock    =      -1   !  frequency of creation of a restart file (modulo referenced to 1) 
     12   nn_write    =      -1   !  frequency of write in the output file   (modulo referenced to nn_it000) 
    1313/ 
    1414!----------------------------------------------------------------------- 
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/tests/BENCH/EXPREF/namelist_cfg_orca1_like

    r10539 r11358  
    99   nn_it000    =       1   !  first time step 
    1010   nn_itend    =    1000   !  last time step  
    11    nn_stock    =       0   !  frequency of creation of a restart file (modulo referenced to 1) 
    12    nn_write    =       0   !  frequency of write in the output file   (modulo referenced to nn_it000) 
     11   nn_stock    =      -1   !  frequency of creation of a restart file (modulo referenced to 1) 
     12   nn_write    =      -1   !  frequency of write in the output file   (modulo referenced to nn_it000) 
    1313/ 
    1414!----------------------------------------------------------------------- 
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/tests/CANAL/MY_SRC/diawri.F90

    r10425 r11358  
    531531      !!      define all the NETCDF files and fields 
    532532      !!      At each time step call histdef to compute the mean if ncessary 
    533       !!      Each nwrite time step, output the instantaneous or mean fields 
     533      !!      Each nn_write time step, output the instantaneous or mean fields 
    534534      !!---------------------------------------------------------------------- 
    535535      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
     
    547547      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zw3d       ! 3D workspace 
    548548      !!---------------------------------------------------------------------- 
    549       !  
    550       IF( ln_timing )   CALL timing_start('dia_wri') 
    551549      ! 
    552550      IF( ninist == 1 ) THEN     !==  Output the initial state and forcings  ==! 
     
    555553      ENDIF 
    556554      ! 
     555      IF( nn_write == -1 )   RETURN   ! we will never do any output 
     556      !  
     557      IF( ln_timing )   CALL timing_start('dia_wri') 
     558      ! 
    557559      ! 0. Initialisation 
    558560      ! ----------------- 
     
    564566      clop = "x"         ! no use of the mask value (require less cpu time and otherwise the model crashes) 
    565567#if defined key_diainstant 
    566       zsto = nwrite * rdt 
     568      zsto = nn_write * rdt 
    567569      clop = "inst("//TRIM(clop)//")" 
    568570#else 
     
    570572      clop = "ave("//TRIM(clop)//")" 
    571573#endif 
    572       zout = nwrite * rdt 
     574      zout = nn_write * rdt 
    573575      zmax = ( nitend - nit000 + 1 ) * rdt 
    574576 
     
    601603         ! WRITE root name in date.file for use by postpro 
    602604         IF(lwp) THEN 
    603             CALL dia_nam( clhstnam, nwrite,' ' ) 
     605            CALL dia_nam( clhstnam, nn_write,' ' ) 
    604606            CALL ctl_opn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    605607            WRITE(inum,*) clhstnam 
     
    609611         ! Define the T grid FILE ( nid_T ) 
    610612 
    611          CALL dia_nam( clhstnam, nwrite, 'grid_T' ) 
     613         CALL dia_nam( clhstnam, nn_write, 'grid_T' ) 
    612614         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam    ! filename 
    613615         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,           &  ! Horizontal grid: glamt and gphit 
     
    645647         ! Define the U grid FILE ( nid_U ) 
    646648 
    647          CALL dia_nam( clhstnam, nwrite, 'grid_U' ) 
     649         CALL dia_nam( clhstnam, nn_write, 'grid_U' ) 
    648650         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam    ! filename 
    649651         CALL histbeg( clhstnam, jpi, glamu, jpj, gphiu,           &  ! Horizontal grid: glamu and gphiu 
     
    658660         ! Define the V grid FILE ( nid_V ) 
    659661 
    660          CALL dia_nam( clhstnam, nwrite, 'grid_V' )                   ! filename 
     662         CALL dia_nam( clhstnam, nn_write, 'grid_V' )                   ! filename 
    661663         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam 
    662664         CALL histbeg( clhstnam, jpi, glamv, jpj, gphiv,           &  ! Horizontal grid: glamv and gphiv 
     
    671673         ! Define the W grid FILE ( nid_W ) 
    672674 
    673          CALL dia_nam( clhstnam, nwrite, 'grid_W' )                   ! filename 
     675         CALL dia_nam( clhstnam, nn_write, 'grid_W' )                   ! filename 
    674676         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam 
    675677         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,           &  ! Horizontal grid: glamt and gphit 
     
    762764         ENDIF 
    763765 
    764          IF( .NOT. ln_cpl ) THEN 
     766         IF( ln_ssr ) THEN 
    765767            CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp 
    766768               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     
    770772               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    771773         ENDIF 
    772  
    773          IF( ln_cpl .AND. nn_ice <= 1 ) THEN 
    774             CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp 
    775                &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    776             CALL histdef( nid_T, "sowafldp", "Surface Water Flux: Damping"        , "Kg/m2/s",   &  ! erp 
    777                &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    778             CALL histdef( nid_T, "sosafldp", "Surface salt flux: Damping"         , "Kg/m2/s",   &  ! erp * sn 
    779                &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    780          ENDIF 
    781           
     774        
    782775         clmx ="l_max(only(x))"    ! max index on a period 
    783776!         CALL histdef( nid_T, "sobowlin", "Bowl Index"                         , "W-point",   &  ! bowl INDEX  
     
    855848      ! donne le nombre d'elements, et ndex la liste des indices a sortir 
    856849 
    857       IF( lwp .AND. MOD( itmod, nwrite ) == 0 ) THEN  
     850      IF( lwp .AND. MOD( itmod, nn_write ) == 0 ) THEN  
    858851         WRITE(numout,*) 'dia_wri : write model outputs in NetCDF files at ', kt, 'time-step' 
    859852         WRITE(numout,*) '~~~~~~ ' 
     
    919912      ENDIF 
    920913 
    921       IF( .NOT. ln_cpl ) THEN 
     914      IF( ln_ssr ) THEN 
    922915         CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping 
    923916         CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping 
    924          IF( ln_ssr ) zw2d(:,:) = erp(:,:) * tsn(:,:,1,jp_sal) * tmask(:,:,1) 
    925          CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping 
    926       ENDIF 
    927       IF( ln_cpl .AND. nn_ice <= 1 ) THEN 
    928          CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping 
    929          CALL histwrite( nid_T, "sowafldp", it, erp           , ndim_hT, ndex_hT )   ! freshwater flux damping 
    930          IF( ln_ssr ) zw2d(:,:) = erp(:,:) * tsn(:,:,1,jp_sal) * tmask(:,:,1) 
     917         zw2d(:,:) = erp(:,:) * tsn(:,:,1,jp_sal) * tmask(:,:,1) 
    931918         CALL histwrite( nid_T, "sosafldp", it, zw2d          , ndim_hT, ndex_hT )   ! salt flux damping 
    932919      ENDIF 
Note: See TracChangeset for help on using the changeset viewer.