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 10745 – NEMO

Changeset 10745


Ignore:
Timestamp:
2019-03-12T17:14:33+01:00 (5 years ago)
Author:
andmirek
Message:

GMED 450 GO8 changes to namelist namctl

Location:
branches/UKMO/dev_r5518_GO6_package_text_diagnostics/NEMOGCM/NEMO
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_GO6_package_text_diagnostics/NEMOGCM/NEMO/OPA_SRC/IOM/in_out_manager.F90

    r6491 r10745  
    9999   !!---------------------------------------------------------------------- 
    100100   LOGICAL ::   ln_ctl       !: run control for debugging 
     101   TYPE :: sn_ctl                !: optional use structure for finer control over output selection 
     102      LOGICAL :: l_config  = .FALSE.  !: activate/deactivate finer control 
     103                                      !  Note if l_config is True then ln_ctl is ignored. 
     104                                      !  Otherwise setting ln_ctl True is equivalent to setting 
     105                                      !  all the following logicals in this structure True 
     106      LOGICAL :: l_runstat = .FALSE.  !: Produce/do not produce run.stat file (T/F) 
     107      LOGICAL :: l_trcstat = .FALSE.  !: Produce/do not produce tracer.stat file (T/F) 
     108      LOGICAL :: l_oceout  = .FALSE.  !: Produce all ocean.outputs    (T) or just one (F) 
     109      LOGICAL :: l_layout  = .FALSE.  !: Produce all layout.dat files (T) or just one (F) 
     110      LOGICAL :: l_mppout  = .FALSE.  !: Produce/do not produce mpp.output_XXXX files (T/F) 
     111      LOGICAL :: l_mpptop  = .FALSE.  !: Produce/do not produce mpp.top.output_XXXX files (T/F) 
     112                                      !  Optional subsetting of processor report files 
     113                                      !  Default settings of 0/1000000/1 should ensure all areas report. 
     114                                      !  Set to a more restrictive range to select specific areas 
     115      INTEGER :: procmin   = 0        !: Minimum narea to output 
     116      INTEGER :: procmax   = 1000000  !: Maximum narea to output 
     117      INTEGER :: procincr  = 1        !: narea increment to output 
     118      INTEGER :: ptimincr  = 1        !: timestep increment to output (time.step and run.stat) 
     119   END TYPE 
     120   TYPE(sn_ctl) :: sn_cfctl     !: run control structure for selective output 
    101121   INTEGER ::   nn_timing    !: run control for timing 
    102122   INTEGER ::   nn_print     !: level of print (0 no print) 
     
    109129   INTEGER ::   nn_bench     !: benchmark parameter (0/1) 
    110130   INTEGER ::   nn_bit_cmp   =    0    !: bit reproducibility  (0/1) 
    111  
    112131   !                                           
    113132   INTEGER ::   nprint, nictls, nictle, njctls, njctle, isplt, jsplt, nbench    !: OLD namelist names 
  • branches/UKMO/dev_r5518_GO6_package_text_diagnostics/NEMOGCM/NEMO/OPA_SRC/SOL/solver.F90

    r6498 r10745  
    5959      ! 
    6060 
    61       IF(lwp) THEN                  !* open elliptic solver statistics file (only on the printing processors) 
     61      IF(lwp .AND. ln_ctl .OR. sn_cfctl%l_runstat) THEN  !* open elliptic solver statistics file (only on the printing processors) 
    6262         CALL ctl_opn( numsol, 'solver.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    6363      ENDIF 
  • branches/UKMO/dev_r5518_GO6_package_text_diagnostics/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r10149 r10745  
    248248      CHARACTER(len=80), DIMENSION(16) ::   cltxt 
    249249      ! 
    250       NAMELIST/namctl/ ln_ctl  , nn_print, nn_ictls, nn_ictle,   & 
     250      NAMELIST/namctl/ ln_ctl  ,sn_cfctl, nn_print, nn_ictls, nn_ictle,   & 
    251251         &             nn_isplt, nn_jsplt, nn_jctls, nn_jctle,   & 
    252252         &             nn_bench, nn_timing 
     
    326326#endif 
    327327      narea = narea + 1                                     ! mynode return the rank of proc (0 --> jpnij -1 ) 
     328 
     329      IF( sn_cfctl%l_config ) THEN 
     330         ! Activate finer control of report outputs 
     331         ! optionally switch off output from selected areas (note this only 
     332         ! applies to output which does not involve global communications) 
     333         IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
     334           & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
     335           &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
     336      ELSE 
     337         ! Use ln_ctl to turn on or off all options. 
     338         CALL nemo_set_cfctl( sn_cfctl, ln_ctl, .TRUE. ) 
     339      ENDIF 
    328340 
    329341      lwm = (narea == 1)                                    ! control of output namelists 
     
    520532         WRITE(numout,*) '   Namelist namctl' 
    521533         WRITE(numout,*) '      run control (for debugging)     ln_ctl     = ', ln_ctl 
     534         WRITE(numout,*) '       finer control over o/p sn_cfctl%l_config  = ', sn_cfctl%l_config 
     535         WRITE(numout,*) '                              sn_cfctl%l_runstat = ', sn_cfctl%l_runstat 
     536         WRITE(numout,*) '                              sn_cfctl%l_trcstat = ', sn_cfctl%l_trcstat 
     537         WRITE(numout,*) '                              sn_cfctl%l_oceout  = ', sn_cfctl%l_oceout 
     538         WRITE(numout,*) '                              sn_cfctl%l_layout  = ', sn_cfctl%l_layout 
     539         WRITE(numout,*) '                              sn_cfctl%l_mppout  = ', sn_cfctl%l_mppout 
     540         WRITE(numout,*) '                              sn_cfctl%l_mpptop  = ', sn_cfctl%l_mpptop 
     541         WRITE(numout,*) '                              sn_cfctl%procmin   = ', sn_cfctl%procmin   
     542         WRITE(numout,*) '                              sn_cfctl%procmax   = ', sn_cfctl%procmax   
     543         WRITE(numout,*) '                              sn_cfctl%procincr  = ', sn_cfctl%procincr  
     544         WRITE(numout,*) '                              sn_cfctl%ptimincr  = ', sn_cfctl%ptimincr  
    522545         WRITE(numout,*) '      level of print                  nn_print   = ', nn_print 
    523546         WRITE(numout,*) '      Start i indice for SUM control  nn_ictls   = ', nn_ictls 
     
    691714   END SUBROUTINE nemo_alloc 
    692715 
     716   SUBROUTINE nemo_set_cfctl(sn_cfctl, setto, for_all ) 
     717      !!---------------------------------------------------------------------- 
     718      !!                     ***  ROUTINE nemo_set_cfctl  *** 
     719      !! 
     720      !! ** Purpose :   Set elements of the output control structure to setto. 
     721      !!                for_all should be .false. unless all areas are to be 
     722      !!                treated identically. 
     723      !! 
     724      !! ** Method  :   Note this routine can be used to switch on/off some 
     725      !!                types of output for selected areas but any output types 
     726      !!                that involve global communications (e.g. mpp_max, glob_sum) 
     727      !!                should be protected from selective switching by the 
     728      !!                for_all argument 
     729      !!---------------------------------------------------------------------- 
     730      LOGICAL :: setto, for_all 
     731      TYPE(sn_ctl) :: sn_cfctl 
     732      !!---------------------------------------------------------------------- 
     733      IF( for_all ) THEN 
     734         sn_cfctl%l_runstat = setto 
     735         sn_cfctl%l_trcstat = setto 
     736      ENDIF 
     737      sn_cfctl%l_oceout  = setto 
     738      sn_cfctl%l_layout  = setto 
     739      sn_cfctl%l_mppout  = setto 
     740      sn_cfctl%l_mpptop  = setto 
     741   END SUBROUTINE nemo_set_cfctl 
    693742 
    694743   SUBROUTINE nemo_partition( num_pes ) 
  • branches/UKMO/dev_r5518_GO6_package_text_diagnostics/NEMOGCM/NEMO/OPA_SRC/stpctl.F90

    r9276 r10745  
    6161                                            ! values and warn if they're out of Range 
    6262      INTEGER, DIMENSION(3) ::   ilocu      !  
    63       INTEGER, DIMENSION(2) ::   ilocs      !  
     63      INTEGER, DIMENSION(2) ::   ilocs      ! 
     64      LOGICAL                ::   ll_wrtstp, ll_colruns, ll_wrtruns 
    6465      !!---------------------------------------------------------------------- 
    65  
     66      ll_wrtstp  = ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 
     67      ll_colruns = ll_wrtstp .AND. ( ln_ctl .OR. sn_cfctl%l_runstat ) 
     68      ll_wrtruns = ll_colruns .AND. lwm 
    6669      IF( kt == nit000 .AND. lwp ) THEN 
    6770         WRITE(numout,*) 
     
    7477            clfname = 'time.step' 
    7578         ENDIF 
    76          CALL ctl_opn( numstp, TRIM(clfname), 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    77       ENDIF 
    78  
    79       IF(lwp) WRITE ( numstp, '(1x, i8)' )   kt      !* save the current time step in numstp 
    80       IF(lwp) REWIND( numstp )                       !  -------------------------- 
     79         IF( lwm ) & 
     80     &    CALL ctl_opn( numstp, TRIM(clfname), 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
     81      ENDIF 
     82 
     83      IF(lwp .AND. ll_wrtstp) THEN 
     84         WRITE ( numstp, '(1x, i8)' )   kt      !* save the current time step in numstp 
     85         REWIND( numstp )                       !  -------------------------- 
     86      ENDIF 
    8187 
    8288      !                                              !* Test maximum of velocity (zonal only) 
     
    9399      IF( lk_mpp )   CALL mpp_max( zumax )                 ! max over the global domain 
    94100      ! 
    95       IF( MOD( kt, nwrite ) == 1 .AND. lwp )   WRITE(numout,*) ' ==>> time-step= ',kt,' abs(U) max: ', zumax 
     101      IF( ll_colruns )   WRITE(numout,*) ' ==>> time-step= ',kt,' abs(U) max: ', zumax 
    96102      ! 
    97103      IF( zumax > 20.e0 ) THEN 
     
    212218      IF( lk_dynspg_flt ) THEN      ! elliptic solver statistics (if required) 
    213219         ! 
    214          IF(lwp) WRITE(numsol,9200) kt, niter, res, SQRT(epsr)/eps       ! Solver 
     220         IF(ll_wrtruns) WRITE(numsol,9200) kt, niter, res, SQRT(epsr)/eps       ! Solver 
    215221         ! 
    216222         IF( kindic < 0 .AND. zsmin > 0.e0 .AND. zumax <= 20.e0 ) THEN   ! create a abort file if problem found  
     
    226232         ! 
    227233      ELSE                                   !* ssh statistics (and others...) 
    228          IF( kt == nit000 .AND. lwp ) THEN   ! open ssh statistics file (put in solver.stat file) 
     234         IF( kt == nit000 .AND. lwp .AND. ln_ctl .OR. sn_cfctl%l_runstat) THEN   ! open ssh statistics file (put in solver.stat file) 
    229235            CALL ctl_opn( numsol, 'solver.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    230236         ENDIF 
    231237         ! 
    232          zssh2 = SUM( sshn(:,:) * sshn(:,:) * tmask_i(:,:) ) 
    233          IF( lk_mpp )   CALL mpp_sum( zssh2 )      ! sum over the global domain 
    234          ! 
    235          IF(lwp) WRITE(numsol,9300) kt, zssh2, zumax, zsmin      ! ssh statistics 
     238         IF( ll_wrtruns ) THEN 
     239            zssh2 = SUM( sshn(:,:) * sshn(:,:) * tmask_i(:,:) ) 
     240            IF( lk_mpp )   CALL mpp_sum( zssh2 )      ! sum over the global domain 
     241         ! 
     242            WRITE(numsol,9300) kt, zssh2, zumax, zsmin      ! ssh statistics 
     243         ENDIF 
    236244         ! 
    237245      ENDIF 
  • branches/UKMO/dev_r5518_GO6_package_text_diagnostics/NEMOGCM/NEMO/OPA_SRC/trc_oce.F90

    r6486 r10745  
    188188         zchl = zrgb(1,jc) 
    189189         irgb = NINT( 41 + 20.* LOG10( zchl ) + 1.e-15 ) 
    190          IF(lwp) WRITE(numout,*) '    jc =', jc, '  Chl = ', zchl, '  irgb = ', irgb 
     190         IF(lwp .AND. nprint >= 1 ) WRITE(numout,*) '    jc =', jc, '  Chl = ', zchl, '  irgb = ', irgb 
    191191         IF( irgb /= jc ) THEN 
    192192            IF(lwp) WRITE(numout,*) '    jc =', jc, '  Chl = ', zchl, '  Chl class = ', irgb 
  • branches/UKMO/dev_r5518_GO6_package_text_diagnostics/NEMOGCM/NEMO/TOP_SRC/trcini.F90

    r10149 r10745  
    123123      CALL trc_ice_ini                                 ! Tracers in sea ice 
    124124 
    125       IF( ln_ctl ) THEN 
    126          ! 
    127          IF (narea == 1) THEN   
    128             ! The tracer.stat file only contains global tracer sum values, if  
    129             ! it contains anything at all. Hence it only needs to be opened  
    130             ! and written to on the master PE, not on all PEs.   
    131             CALL ctl_opn( numstr, 'tracer.stat', 'REPLACE','FORMATTED',  &  
    132                           'SEQUENTIAL', -1, numout, lwp , narea )  
    133          ENDIF   
    134          ! 
    135       ENDIF 
     125      ! 
     126      IF (lwm .AND. sn_cfctl%l_trcstat) THEN   
     127         ! The tracer.stat file only contains global tracer sum values, if  
     128         ! it contains anything at all. Hence it only needs to be opened  
     129         ! and written to on the master PE, not on all PEs.   
     130         CALL ctl_opn( numstr, 'tracer.stat', 'REPLACE','FORMATTED',  &  
     131                       'SEQUENTIAL', -1, numout, lwp , narea )  
     132      ENDIF   
     133      ! 
    136134 
    137135      IF( ln_trcdta ) THEN 
  • branches/UKMO/dev_r5518_GO6_package_text_diagnostics/NEMOGCM/NEMO/TOP_SRC/trcstp.F90

    r9237 r10745  
    6262      INTEGER               ::  jk, jn  ! dummy loop indices 
    6363      REAL(wp)              ::  ztrai 
     64      LOGICAL ::   ll_trcstat ! local logical 
    6465      CHARACTER (len=25)    ::  charout  
    6566      !!------------------------------------------------------------------- 
     
    6768      IF( nn_timing == 1 )   CALL timing_start('trc_stp') 
    6869      ! 
     70      ll_trcstat  = ( ln_ctl .OR. sn_cfctl%l_trcstat ) .AND. & 
     71     &              ( ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) ) 
    6972      IF( kt == nittrc000 .AND. lk_trdmxl_trc )  CALL trd_mxl_trc_init    ! trends: Mixed-layer 
    7073      ! 
     
    120123      ENDIF 
    121124      ! 
    122       IF (ln_ctl) THEN  
     125      IF (ll_trcstat) THEN  
    123126         ! The following code is very expensive since it involves multiple  
    124127         ! reproducible global sums over all tracer fields and is potentially   
Note: See TracChangeset for help on using the changeset viewer.