= ''ENHANCE-04_AndrewC-reporting'' Last edition: '''[[Wikinfo(changed_ts)]]''' by '''[[Wikinfo(changed_by)]]''' The PI is responsible to closely follow the progress of the action, and especially to contact NEMO project manager if the delay on preview (or review) are longer than the 2 weeks expected. [[PageOutline(2, , inline)]] == Summary Investigate ways of improving the code's reporting facilities. Currently, errors away from the lead process are not fully reported and the ln_ctl mechanism produces an overwhelming volume of output for large processor counts. Options are needed to produce more selective output (either by output type or processor range). This is an un-started task from the 2018WP (formerly ROBUST-06_AndrewC-reporting) that has been carried forward to 2019. ''#2167'' == Preview '''(version 2 following initial preview by Sebastien ( see his comments below))''' {{{#!box help [[Include(wiki:Developers/DevProcess#preview_)]] }}} One of the features of NEMO 4.0 is the large reduction in global communications at the cost of suppressing some global diagnostics which tend to be useful only during SETTE testing, debugging or new configuration development. Such diagnostics can be re-activated using the ln_ctl namelist variable but this is a rather blunt instrument in that it activates all extra output for all processing elements. This list can include: {{{ run.stat run.stat.nc tracer.stat ocean.output_XXXX layout.dat_XXXX mpp.output_XXXX mpp.top.output_XXX <---- correct this to 4-digits for consistency EMPave.dat_XXXX <---- These are all identical, suppress writing to write-master only icebergs.stat_XXXX }}} and possibly others depending on runtime options. One of the 2019 NEMO workplan entries (ENHANCE-04_AndrewC-reporting) plans to introduce more control over the choice of output created but it may be best to introduce the basic structure prior to the v4.0 release. Below is a summary of the overall plans and what can be implemented immediately if there is consensus. At this stage, the plan is to leave ln_ctl as an all-or-nothing switch but to add the basic structure for finer control. For the v4.0 release, this new structure will only be capable of activating the global stats files (run.stat, run.stat.nc and tracer.stat) independently of ln_ctl but the placeholders will be there for extended control over other outputs. Minimal changes to achieve this will affect: {{{ 1. OCE/IOM/in_out_manager.F90 cfgs/SHARED/namelist_ref 2. OCE/nemogcm.F90 OFF/nemogcm.F90 SAO/nemogcm.F90 SAS/nemogcm.F90 3. OCE/stpctl.F90 4. TOP/prtctl_trc.F90 TOP/trcini.F90 TOP/trcstp.F90 5. OCE/LBC/mppini.F90 OCE/SBC/sbcfwb.F90 6. sette/sette.sh }}} To reiterate, these changes allow run.stat and tracer.stat to be produced even when ln_ctl is .false.. They also introduce additional controls such as updating run.stat, tracer.stat and time.step at integer multiples of time step rather than every time step and for restricting the production of some types of output (e.g. layout.dat) to a subset of processing regions. There are good arguments for separating out the multiple uses that ln_ctl has grown to support (see Sebastien's comments on its history) but I propose these changes , as a quick, pre-release addition. ''' 1. OCE/IOM/in_out_manager.F90 cfgs/SHARED/namelist_ref ''' These changes introduce a derived-type structure into the in_out_manager module and populates the reference namelist with default values. There are 5 basic sets of parameters in this structure: {{{ * l_config Activates use of the settings in the rest of the structure (specifically for when ln_ctl is false) * l_runstat, l_trcstat Activates production of global stats files. Only a single file of each of these is ever produced. * l_oceout, l_layout Normal operation is to produce a single version of each of these. If true then a version for each area is produced * l_mppout, l_mpptrc, l_icbstat Suppressed if false, otherwise produce a version for each area. * procmin, procmax, procincr Allow subsetting of areas when producing output in the previous two categories. Default values will ensure all areas report. * ptimincr Timestep increment for outputting of time step status information less frequently (affects run.stat, tracer.stat and time.step only) }}} {{{#!diff Index: OCE/IOM/in_out_manager.F90 =================================================================== --- OCE/IOM/in_out_manager.F90 (revision 10530) +++ OCE/IOM/in_out_manager.F90 (working copy) @@ -99,6 +99,27 @@ !! output monitoring !!---------------------------------------------------------------------- LOGICAL :: ln_ctl !: run control for debugging + TYPE :: sn_ctl !: optional use structure for finer control over output selection + LOGICAL :: l_config = .FALSE. !: activate/deactivate finer control + ! Note if l_config is True then ln_ctl is ignored. + ! Otherwise setting ln_ctl True is equivalent to setting + ! all the following logicals in this structure True + LOGICAL :: l_runstat = .FALSE. !: Produce/do not produce run.stat file (T/F) + LOGICAL :: l_trcstat = .FALSE. !: Produce/do not produce tracer.stat file (T/F) + LOGICAL :: l_oceout = .FALSE. !: Produce all ocean.outputs (T) or just one (F) + LOGICAL :: l_layout = .FALSE. !: Produce all layout.dat files (T) or just one (F) + LOGICAL :: l_mppout = .FALSE. !: Produce/do not produce mpp.output_XXXX files (T/F) + LOGICAL :: l_mpptop = .FALSE. !: Produce/do not produce mpp.top.output_XXXX files (T/F) + LOGICAL :: l_icbstat = .FALSE. !: Produce/do not produce icebergs.stat_XXXX files (T/F) + ! Optional subsetting of processor report files + ! Default settings of 0/1000000/1 should ensure all areas report. + ! Set to a more restrictive range to select specific areas + INTEGER :: procmin = 0 !: Minimum narea to output + INTEGER :: procmax = 1000000 !: Maximum narea to output + INTEGER :: procincr = 1 !: narea increment to output + INTEGER :: ptimincr = 1 !: timestep increment to output (time.step and run.stat) + END TYPE + TYPE (sn_ctl) :: sn_cfctl !: run control structure for selective output LOGICAL :: ln_timing !: run control for timing LOGICAL :: ln_diacfl !: flag whether to create CFL diagnostics INTEGER :: nn_print !: level of print (0 no print) Index: cfgs/SHARED/namelist_ref =================================================================== --- cfgs/SHARED/namelist_ref (revision 10530) +++ cfgs/SHARED/namelist_ref (working copy) @@ -1303,7 +1303,19 @@ !----------------------------------------------------------------------- &namctl ! Control prints (default: OFF) !----------------------------------------------------------------------- - ln_ctl = .false. ! trends control print (expensive!) + ln_ctl = .FALSE. ! Toggle all report printing on/off (T/F); Ignored if sn_cfctl%l_config is T + sn_cfctl%l_config = .TRUE. ! IF .true. then control which reports are written with the following + sn_cfctl%l_runstat = .FALSE. ! switches and which areas produce reports with the proc integer settings. + sn_cfctl%l_trcstat = .FALSE. ! The default settings for the proc integers should ensure + sn_cfctl%l_oceout = .FALSE. ! that all areas report. + sn_cfctl%l_layout = .FALSE. ! + sn_cfctl%l_mppout = .FALSE. ! + sn_cfctl%l_mpptop = .FALSE. ! + sn_cfctl%l_icbstat = .FALSE. ! + sn_cfctl%procmin = 0 ! Minimum area number for reporting [default:0] + sn_cfctl%procmax = 1000000 ! Maximum area number for reporting [default:1000000] + sn_cfctl%procincr = 1 ! Increment for optional subsetting of areas [default:1] + sn_cfctl%ptimincr = 1 ! Timestep increment for writing time step progress info nn_print = 0 ! level of print (0 no extra print) nn_ictls = 0 ! start i indice of control sum (use to compare mono versus nn_ictle = 0 ! end i indice of control sum multi processor runs }}} ''' 2. OCE/nemogcm.F90, OFF/nemogcm.F90, SAO/nemogcm.F90, SAS/nemogcm.F90 ''' The new structure is read and reported in nemogcm.F90. Changes for all variants are similar OCE/nemogcm.F90 is shown here: {{{#!diff Index: OCE/nemogcm.F90 =================================================================== --- OCE/nemogcm.F90 (revision 10530) +++ OCE/nemogcm.F90 (working copy) @@ -256,8 +256,8 @@ INTEGER :: ios, ilocal_comm ! local integers CHARACTER(len=120), DIMENSION(60) :: cltxt, cltxt2, clnam !! - NAMELIST/namctl/ ln_ctl , nn_print, nn_ictls, nn_ictle, & - & nn_isplt , nn_jsplt, nn_jctls, nn_jctle, & + NAMELIST/namctl/ ln_ctl , sn_cfctl, nn_print, nn_ictls, nn_ictle, & + & nn_isplt , nn_jsplt, nn_jctls, nn_jctle, & & ln_timing, ln_diacfl NAMELIST/namcfg/ ln_read_cfg, cn_domcfg, ln_closea, ln_write_cfg, cn_domcfg_out, ln_use_jattr !!---------------------------------------------------------------------- @@ -327,6 +327,18 @@ narea = narea + 1 ! mynode return the rank of proc (0 --> jpnij -1 ) + IF( sn_cfctl%l_config ) THEN + ! Activate finer control of report outputs + ! optionally switch off output from selected areas (note this only + ! applies to output which does not involve global communications) + IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax ) .OR. & + & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) ) & + & CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) + ELSE + ! Use ln_ctl to turn on or off all options. + CALL nemo_set_cfctl( sn_cfctl, ln_ctl, .TRUE. ) + ENDIF + lwm = (narea == 1) ! control of output namelists lwp = (narea == 1) .OR. ln_ctl ! control of all listing output print @@ -503,6 +515,18 @@ WRITE(numout,*) '~~~~~~~~' WRITE(numout,*) ' Namelist namctl' WRITE(numout,*) ' run control (for debugging) ln_ctl = ', ln_ctl + WRITE(numout,*) ' finer control over o/p sn_cfctl%l_config = ', sn_cfctl%l_config + WRITE(numout,*) ' sn_cfctl%l_runstat = ', sn_cfctl%l_runstat + WRITE(numout,*) ' sn_cfctl%l_trcstat = ', sn_cfctl%l_trcstat + WRITE(numout,*) ' sn_cfctl%l_oceout = ', sn_cfctl%l_oceout + WRITE(numout,*) ' sn_cfctl%l_layout = ', sn_cfctl%l_layout + WRITE(numout,*) ' sn_cfctl%l_mppout = ', sn_cfctl%l_mppout + WRITE(numout,*) ' sn_cfctl%l_mpptop = ', sn_cfctl%l_mpptop + WRITE(numout,*) ' sn_cfctl%l_icbstat = ', sn_cfctl%l_icbstat + WRITE(numout,*) ' sn_cfctl%procmin = ', sn_cfctl%procmin + WRITE(numout,*) ' sn_cfctl%procmax = ', sn_cfctl%procmax + WRITE(numout,*) ' sn_cfctl%procincr = ', sn_cfctl%procincr + WRITE(numout,*) ' sn_cfctl%ptimincr = ', sn_cfctl%ptimincr WRITE(numout,*) ' level of print nn_print = ', nn_print WRITE(numout,*) ' Start i indice for SUM control nn_ictls = ', nn_ictls WRITE(numout,*) ' End i indice for SUM control nn_ictle = ', nn_ictle @@ -649,6 +673,34 @@ ! END SUBROUTINE nemo_alloc + SUBROUTINE nemo_set_cfctl(sn_cfctl, setto, for_all ) + !!---------------------------------------------------------------------- + !! *** ROUTINE nemo_set_cfctl *** + !! + !! ** Purpose : Set elements of the output control structure to setto. + !! for_all should be .false. unless all areas are to be + !! treated identically. + !! + !! ** Method : Note this routine can be used to switch on/off some + !! types of output for selected areas but any output types + !! that involve global communications (e.g. mpp_max, glob_sum) + !! should be protected from selective switching by the + !! for_all argument + !!---------------------------------------------------------------------- + LOGICAL :: setto, for_all + TYPE (sn_ctl) :: sn_cfctl + !!---------------------------------------------------------------------- + IF( for_all ) THEN + sn_cfctl%l_runstat = setto + sn_cfctl%l_trcstat = setto + ENDIF + sn_cfctl%l_oceout = setto + sn_cfctl%l_layout = setto + sn_cfctl%l_mppout = setto + sn_cfctl%l_mpptop = setto + sn_cfctl%l_icbstat = setto + END SUBROUTINE nemo_set_cfctl + !!====================================================================== END MODULE nemogcm }}} Eventually, setting sn_cfctl%l_config true will force ln_ctl to be false but the current implementation is incomplete and can only be used the activate run.stat, tracer.stat and multiple layout.dats independently of ln_ctl. ln_ctl, therefore, remains as the overriding control for all outputs. ''' 3. OCE/stpctl.F90 ''' The logic changes required in stpctl.F90 to control the production of run.stat are relatively simple. Two new local logicals are introduced to avoid having to evaluate logical constructs repeatedly. These determine whether or not to collect the global maximums (lcolruns) and whether or not to handle the actual writing (lwrtruns). {{{#!diff Index: OCE/stpctl.F90 =================================================================== --- OCE/stpctl.F90 (revision 10530) +++ OCE/stpctl.F90 (working copy) @@ -66,17 +66,22 @@ INTEGER, DIMENSION(3) :: iu, is1, is2 ! min/max loc indices REAL(wp) :: zzz ! local real REAL(wp), DIMENSION(9) :: zmax + LOGICAL :: ll_wrtstp, ll_colruns, ll_wrtruns CHARACTER(len=20) :: clname !!---------------------------------------------------------------------- ! + ll_wrtstp = ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) + ll_colruns = ll_wrtstp .AND. ( ln_ctl .OR. sn_cfctl%l_runstat ) + ll_wrtruns = ll_colruns .AND. lwm IF( kt == nit000 .AND. lwp ) THEN WRITE(numout,*) WRITE(numout,*) 'stp_ctl : time-stepping control' WRITE(numout,*) '~~~~~~~' ! ! open time.step file IF( lwm ) CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) - ! ! open run.stat file - IF( ln_ctl .AND. lwm ) THEN + ! ! open run.stat file(s) at start whatever + ! ! the value of sn_cfctl%ptimincr + IF( lwm .AND. ( ln_ctl .OR. sn_cfctl%l_runstat ) ) THEN CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) clname = 'run.stat.nc' IF( .NOT. Agrif_Root() ) clname = TRIM(Agrif_CFixed())//"_"//TRIM(clname) @@ -98,7 +103,7 @@ ENDIF IF( kt == nit000 ) lsomeoce = COUNT( ssmask(:,:) == 1._wp ) > 0 ! - IF(lwm) THEN !== current time step ==! ("time.step" file) + IF(lwm .AND. ll_wrtstp) THEN !== current time step ==! ("time.step" file) WRITE ( numstp, '(1x, i8)' ) kt REWIND( numstp ) ENDIF @@ -120,12 +125,12 @@ zmax(9) = MAXVAL( Cu_adv(:,:,:) , mask = tmask(:,:,:) == 1._wp ) ! cell Courant no. max ENDIF ! - IF( ln_ctl ) THEN + IF( ll_colruns ) THEN CALL mpp_max( "stpctl", zmax ) ! max over the global domain nstop = NINT( zmax(7) ) ! nstop indicator sheared among all local domains ENDIF ! !== run statistics ==! ("run.stat" files) - IF( ln_ctl .AND. lwm ) THEN + IF( ll_wrtruns ) THEN WRITE(numrun,9500) kt, zmax(1), zmax(2), -zmax(3), zmax(4) istatus = NF90_PUT_VAR( idrun, idssh, (/ zmax(1)/), (/kt/), (/1/) ) istatus = NF90_PUT_VAR( idrun, idu, (/ zmax(2)/), (/kt/), (/1/) ) }}} ''' 4. TOP/prtctl_trc.F90 TOP/trcini.F90 TOP/trcstp.F90 ''' Changes to control the production of tracer.stat follow similar lines with the introduction of a lltrcstat local logical. Note also changes to prtctl_trc.F90 to make mpp.top.output filenames compatible with other similar filenames (i.e. use I4.4 for area number). This one is a little off message because the control for this TOP output has been read in OCE/nemogcm.F90. I think this makes sense and moving it to the TOP name list just for the sake of keeping OCE and TOP fully independent seems unnecessary; TBD. {{{#!diff Index: TOP/prtctl_trc.F90 =================================================================== --- TOP/prtctl_trc.F90 (revision 10459) +++ TOP/prtctl_trc.F90 (working copy) @@ -209,7 +209,7 @@ IF( lk_mpp ) THEN sind = narea eind = narea - clb_name = "('mpp.top.output_',I3.3)" + clb_name = "('mpp.top.output_',I4.4)" cl_run = 'MULTI processor run' ! use indices for each area computed by mpp_init subroutine nlditl(1:jpnij) = nldit(:) @@ -228,7 +228,7 @@ ELSE sind = 1 eind = ijsplt - clb_name = "('mono.top.output_',I3.3)" + clb_name = "('mono.top.output_',I4.4)" cl_run = 'MONO processor run ' ! compute indices for each area as done in mpp_init subroutine CALL sub_dom Index: TOP/trcini.F90 =================================================================== --- TOP/trcini.F90 (revision 10459) +++ TOP/trcini.F90 (working copy) @@ -71,7 +71,9 @@ CALL trc_ini_trp ! passive tracers transport CALL trc_ice_ini ! Tracers in sea ice ! - IF(lwm) CALL ctl_opn( numstr, 'tracer.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp , narea ) + IF( lwm .AND. ( ln_ctl .OR. (sn_cfctl%l_config .AND. sn_cfctl%l_trcstat) ) ) THEN + CALL ctl_opn( numstr, 'tracer.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp , narea ) + ENDIF ! CALL trc_ini_state ! passive tracers initialisation : from a restart or from clim IF( nn_dttrc /= 1 ) & Index: TOP/trcstp.F90 =================================================================== --- TOP/trcstp.F90 (revision 10530) +++ TOP/trcstp.F90 (working copy) @@ -56,6 +56,7 @@ ! INTEGER :: jk, jn ! dummy loop indices REAL(wp):: ztrai ! local scalar + LOGICAL :: ll_trcstat ! local logical CHARACTER (len=25) :: charout ! !!------------------------------------------------------------------- ! @@ -67,6 +68,8 @@ r2dttrc = 2. * rdttrc ! = 2 rdttrc (leapfrog) ENDIF ! + ll_trcstat = ( ln_ctl .OR. sn_cfctl%l_trcstat ) .AND. & + & ( ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) ) IF( kt == nittrc000 .AND. lk_trdmxl_trc ) CALL trd_mxl_trc_init ! trends: Mixed-layer ! IF( .NOT.ln_linssh ) THEN ! update ocean volume due to ssh temporal evolution @@ -108,7 +111,7 @@ ! ENDIF ! - IF (ln_ctl ) THEN + IF (ll_trcstat) THEN ztrai = 0._wp ! content of all tracers DO jn = 1, jptra ztrai = ztrai + glob_sum( 'trcstp', trn(:,:,:,jn) * cvol(:,:,:) ) }}} ''' 5. OCE/LBC/mppini.F90 ''' Control over the creation of multiple layout.dat files is easy to implement and so has been done as an example of how output in this category will be handled in future. For this category, the area subsetting can be used to restrict which areas produce files. The standard layout.dat file, produced by narea = 1 is always produced. Also, OCE/SBC/sbcfwb.F90 has been fixed so that only one EMPave.dat file is ever read or produced. Ultimately, only one processor should read this file and MPI_BCAST the values to all others as a more scalable solution (for name lists too?). {{{#!diff Index: OCE/LBC/mppini.F90 =================================================================== --- OCE/LBC/mppini.F90 (revision 10459) +++ OCE/LBC/mppini.F90 (working copy) @@ -150,6 +150,7 @@ INTEGER :: ierr, ios ! INTEGER :: inbi, inbj, iimax, ijmax, icnt1, icnt2 LOGICAL :: llbest + LOGICAL :: llwrtlay INTEGER, ALLOCATABLE, DIMENSION(:) :: iin, ii_nono, ii_noea ! 1D workspace INTEGER, ALLOCATABLE, DIMENSION(:) :: ijn, ii_noso, ii_nowe ! - - INTEGER, ALLOCATABLE, DIMENSION(:,:) :: iimppt, ilci, ibondi, ipproc ! 2D workspace @@ -166,6 +167,7 @@ & ln_vol, nn_volctl, nn_rimwidth, nb_jpk_bdy !!---------------------------------------------------------------------- + llwrtlay = lwp .OR. ln_ctl .OR. ( sn_cfctl%l_config .AND. sn_cfctl%l_layout ) ! do we need to take into account bdy_msk? REWIND( numnam_ref ) ! Namelist nambdy in reference namelist : BDY READ ( numnam_ref, nambdy, IOSTAT = ios, ERR = 903) @@ -553,7 +555,7 @@ END DO ! Save processor layout in ascii file - IF (lwp) THEN + IF (llwrtlay) THEN CALL ctl_opn( inum, 'layout.dat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., narea ) WRITE(inum,'(a)') ' jpnij jpimax jpjmax jpk jpiglo jpjglo'//& & ' ( local: narea jpi jpj )' @@ -614,6 +616,8 @@ WRITE(numout,*) WRITE(numout,*) ' ==>>> North fold boundary prepared for jpni >1' ! additional prints in layout.dat + ENDIF + IF (llwrtlay) THEN WRITE(inum,*) WRITE(inum,*) WRITE(inum,*) 'number of subdomains located along the north fold : ', ndim_rank_north @@ -628,7 +632,7 @@ ! IF( ln_nnogather ) THEN CALL mpp_init_nfdcom ! northfold neighbour lists - IF (lwp) THEN + IF (llwrtlay) THEN WRITE(inum,*) WRITE(inum,*) WRITE(inum,*) 'north fold exchanges with explicit point-to-point messaging :' @@ -639,7 +643,7 @@ ENDIF ENDIF ! - IF (lwp) CLOSE(inum) + IF (llwrtlay) CLOSE(inum) ! DEALLOCATE(iin, ijn, ii_nono, ii_noea, ii_noso, ii_nowe, & & iimppt, ijmppt, ibondi, ibondj, ipproc, ipolj, & Index: OCE/SBC/sbcfwb.F90 =================================================================== --- OCE/SBC/sbcfwb.F90 (revision 10530) +++ OCE/SBC/sbcfwb.F90 (working copy) @@ -143,7 +143,7 @@ qns(:,:) = qns(:,:) - zcoef * sst_m(:,:) * tmask(:,:,1) ! account for change to the heat budget due to fw correction ENDIF ! - IF( kt == nitend .AND. lwp ) THEN ! save fwfold value in a file + IF( kt == nitend .AND. lwm ) THEN ! save fwfold value in a file (only one required) CALL ctl_opn( inum, 'EMPave.dat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., narea ) WRITE( inum, "(24X,I8,2ES24.16)" ) nyear, a_fwb_b, a_fwb CLOSE( inum ) }}} ''' 6. sette/sette.sh ''' Finally, once implemented, these changes allow SETTE tests to be run without creating the full set of multiple output files. It is simply a case of replacing all ln_ctl settings like so: {{{#!diff Index: sette.sh =================================================================== --- sette.sh (revision 10459) +++ sette.sh (working copy) @@ -287,7 +288,10 @@ set_namelist namelist_cfg nn_stock 495 set_namelist namelist_cfg jpni 4 set_namelist namelist_cfg jpnj 8 - set_namelist namelist_cfg ln_ctl .true. + set_namelist namelist_cfg ln_ctl .false. + set_namelist namelist_cfg sn_cfctl%l_config .true. + set_namelist namelist_cfg sn_cfctl%l_runstat .true. + set_namelist namelist_cfg sn_cfctl%l_trcstat .true. set_namelist namelist_cfg ln_use_calving .true. set_namelist namelist_cfg ln_wave .true. set_namelist namelist_cfg ln_cdgw .true. }}} == Sebastien's comments on the first draft, many of which have already been incorporated into version2 above: == Maybe you know this story, but it case you don’t know… :-) 1) A long time ago - in a galaxy far far away - ... ln_ctl was there (since ever?, at least in rev3) and was a control print of the trend over the first core. 2) At rev258 https://forge.ipsl.jussieu.fr/nemo/changeset/258 the concept was modified and extended to be able to debug mpi reproducibility. prtctl was added but, to my knowledge, never documented. The idea is to compare the mean value of every trend in the code over (1) the local mpi domain and (2) the same domain but in a 1 core simulation (or n core as soon as the domain you want to test is included in your mpi subdomain). You compare you mpp.output_xxxx and mono.output_xxxx files and the first difference tells you which core and which trend is the first to diverge. 3) Next, as prtctl was dealing with mpp.output_xxxx and mono.output_xxxx files, we again extended the use of ln_ctl to control the creation of any file trough the definition of lwp: https://forge.ipsl.jussieu.fr/nemo/changeset/1579 This was a bad idea as, with 1 variable (ln_ctl), we control 2 different concepts : (1) mpp debug which requires the production of mpp.output_xxxx and mono.output_xxxx files and (2) the control of all other outputs files (ocean.output, run.stat, layout.dat…) 4) For Performance issues, with Eric, we wanted to be able to remove the globsum in stpctl. At some point we thought that we should introduce a new namelist variable something like in_fast or ln_prod or ln_debug or nn_debug which would allow us to reduce the printed informations and use faster code (for example without globsum in stpctl). After some discussions, we thought that our idea was not clear enough to be introduced in the code before the release in December. We therefore decided to postpone this and simply use ln_ctl to switch on/off the globsum (because if ln_ctl = T, you don’t care of the performances so you can do globsum in stpctl). Once you switch off the globsum, the data in run.stat are useless, so we also switch off run.stat files. So Today, ln_ctl is mixing different functionalities coming from theses 4 layers of developments. I think we should take advantage of your development to clean-up this mess! One proposition (to be discussed) could be to split ln_ctl into 3 functionalities: - mpp debug associated to prtctl. That could be renamed, for example in prttrd or trdprt for "trend print". Or mppdbg for mpp debug? this part requires the creation of the mpp.output_xxxx and mono.output_xxxx files which, to me, should be controlled only by the activation or not of prtctl - something (a logical, an integer, a structure) related to the balance between verbosity-control-debug and performance. This would control/replace/be linked with the creation of run.stat files, nn_print, ln_timing maybe also layout.dat - use your sn_ctl to control other files Other minor points : - EMPave.dat : I had a quick look but it seems that this file is the same for each core (contains only the year and global mean). So we should not offer the possibility to create EMPave.dat_xxxx files. Either all cores read the same file (as we do for the nameliste) or only core 0 read it and use mpi_broadcast to send the informations to all other cores (as, I think, we should also do for the name lists). '''First part done, will consider use of mpi_bcast in 2019''' - We have files created by oce, si3 and top. Maybe, It is strange if a part of OCE, control the creation of top files like tracer.stat, no? '''To be discussed ''' - instead of having to test sn_cfctl%l_config everywhere as for example in "sn_cfctl%l_config .AND. sn_cfctl%l_trcstat”, I would, in nemo_set_cfctl, do sn_cfctl%l_trcstat = setto .AND. sn_cfctl%l_config ''' Actually the test of l_config isn't needed at the lower levels, removed ''' - there is also time.step file ''' Not sure we ever want to switch this off but it can now be updated less frequently according to ptimincr ''' - do we really need the sn_ctl structure? why no a simple list of logical and integer? ''' To be discussed ''' - I would like to “promote” the use of ln_timing, except in production mode, so people become used to look at this file to see the main bottlenecks in computational coast and communications… ''' Think this is a separate issue unless multiple files are produced? ''' == Tests {{{#!box help [[Include(wiki:Developers/DevProcess#tests)]] }}} == Review {{{#!box help [[Include(wiki:Developers/DevProcess#review)]] }}}