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

Changeset 10570


Ignore:
Timestamp:
2019-01-24T16:14:49+01:00 (5 years ago)
Author:
acc
Message:

Trunk update to implement finer control over the choice of text report files generated. See ticket: #2167

Location:
NEMO/trunk
Files:
18 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/cfgs/SHARED/namelist_ref

    r10499 r10570  
    501501   !                          ! diagnostics: 
    502502   ln_bergdia        = .true.       ! Calculate budgets 
    503    nn_verbose_level  = 1            ! Turn on more verbose output if level > 0 
     503   nn_verbose_level  = 0            ! Turn on more verbose output if level > 0 
    504504   nn_verbose_write  = 15           ! Timesteps between verbose messages 
    505505   nn_sample_rate    = 1            ! Timesteps between sampling for trajectory storage 
     
    13041304&namctl        !   Control prints                                       (default: OFF) 
    13051305!----------------------------------------------------------------------- 
    1306    ln_ctl      = .false.   !  trends control print (expensive!) 
     1306   ln_ctl = .FALSE.                 ! Toggle all report printing on/off (T/F); Ignored if sn_cfctl%l_config is T 
     1307     sn_cfctl%l_config = .TRUE.     ! IF .true. then control which reports are written with the following 
     1308       sn_cfctl%l_runstat = .FALSE. ! switches and which areas produce reports with the proc integer settings. 
     1309       sn_cfctl%l_trcstat = .FALSE. ! The default settings for the proc integers should ensure 
     1310       sn_cfctl%l_oceout  = .FALSE. ! that  all areas report. 
     1311       sn_cfctl%l_layout  = .FALSE. ! 
     1312       sn_cfctl%l_mppout  = .FALSE. ! 
     1313       sn_cfctl%l_mpptop  = .FALSE. ! 
     1314       sn_cfctl%procmin   = 0       ! Minimum area number for reporting [default:0] 
     1315       sn_cfctl%procmax   = 1000000 ! Maximum area number for reporting [default:1000000] 
     1316       sn_cfctl%procincr  = 1       ! Increment for optional subsetting of areas [default:1] 
     1317       sn_cfctl%ptimincr  = 1       ! Timestep increment for writing time step progress info 
    13071318   nn_print    =    0      !  level of print (0 no extra print) 
    13081319   nn_ictls    =    0      !  start i indice of control sum (use to compare mono versus 
  • NEMO/trunk/src/OCE/ICB/icbdia.F90

    r10425 r10570  
    327327               &                    'returned',calving_ret_net) 
    328328         ENDIF 
    329          WRITE( numicb, '("calved by class = ",i6,20(",",i6))') (nbergs_calved_by_class(ik),ik=1,nclasses) 
    330          IF( nspeeding_tickets > 0 )   WRITE( numicb, '("speeding tickets issued = ",i6)') nspeeding_tickets 
     329         IF (nn_verbose_level > 0) THEN 
     330            WRITE( numicb, '("calved by class = ",i6,20(",",i6))') (nbergs_calved_by_class(ik),ik=1,nclasses) 
     331            IF( nspeeding_tickets > 0 )   WRITE( numicb, '("speeding tickets issued = ",i6)') nspeeding_tickets 
     332         ENDIF 
    331333         ! 
    332334         nbergs_start              = nbergs_end 
     
    437439         stored_start = SUM( berg_grid%stored_ice(:,:,:) ) 
    438440         CALL mpp_sum( 'icbdia', stored_start ) 
    439          WRITE(numicb,'(a,es13.6,a)')   'icb_dia_income: initial stored mass=',stored_start,' kg' 
    440441         ! 
    441442         stored_heat_start = SUM( berg_grid%stored_heat(:,:) ) 
    442443         CALL mpp_sum( 'icbdia', stored_heat_start ) 
    443          WRITE(numicb,'(a,es13.6,a)')    'icb_dia_income: initial stored heat=',stored_heat_start,' J' 
     444         IF (nn_verbose_level > 0) THEN 
     445            WRITE(numicb,'(a,es13.6,a)')   'icb_dia_income: initial stored mass=',stored_start,' kg' 
     446            WRITE(numicb,'(a,es13.6,a)')   'icb_dia_income: initial stored heat=',stored_heat_start,' J' 
     447         ENDIF 
    444448      ENDIF 
    445449      ! 
     
    515519      !!---------------------------------------------------------------------- 
    516520      ! 
     521      IF (nn_verbose_level == 0) RETURN 
    517522      IF( PRESENT(kbergs) ) THEN 
    518523         WRITE(numicb,100) cd_budgetstr // ' state:',                                    & 
     
    539544      !!---------------------------------------------------------------------- 
    540545      ! 
     546      IF (nn_verbose_level == 0) RETURN 
    541547      WRITE(numicb,200) cd_budgetstr // ' check:',                 & 
    542548         &              cd_startstr,    pstartval, cd_budgetunits, & 
     
    558564      !!---------------------------------------------------------------------- 
    559565      ! 
     566      IF (nn_verbose_level == 0) RETURN 
    560567      zval = ( ( pendval - pstartval ) - ( pinval - poutval ) ) /   & 
    561568         &   MAX( 1.e-30, MAX( ABS( pendval - pstartval ) , ABS( pinval - poutval ) ) ) 
     
    578585      !!---------------------------------------------------------------------- 
    579586      ! 
     587      IF (nn_verbose_level == 0) RETURN 
    580588      WRITE(numicb,100) cd_budgetstr // ' state:',           & 
    581589         &              cd_startstr  // ' start', pstartval, & 
     
    595603      !!---------------------------------------------------------------------- 
    596604      ! 
     605      IF (nn_verbose_level == 0) RETURN 
    597606      WRITE(numicb,200) cd_budgetstr // ' budget:', & 
    598607         &              cd_instr     // ' in',      pinval, & 
  • NEMO/trunk/src/OCE/ICB/icbdyn.F90

    r10068 r10570  
    371371      ENDIF 
    372372      !                                      ! check the speed and acceleration limits 
    373       IF( ABS( zuveln ) > pp_vel_lim   .OR. ABS( zvveln ) > pp_vel_lim   )   & 
    374          WRITE(numicb,'("pe=",i3,x,a)') narea,'Dump triggered by excessive velocity' 
    375       IF( ABS( pax    ) > pp_accel_lim .OR. ABS( pay    ) > pp_accel_lim )   & 
    376          WRITE(numicb,'("pe=",i3,x,a)') narea,'Dump triggered by excessive acceleration' 
     373      IF (nn_verbose_level > 0) THEN 
     374         IF( ABS( zuveln ) > pp_vel_lim   .OR. ABS( zvveln ) > pp_vel_lim   )   & 
     375            WRITE(numicb,'("pe=",i3,x,a)') narea,'Dump triggered by excessive velocity' 
     376         IF( ABS( pax    ) > pp_accel_lim .OR. ABS( pay    ) > pp_accel_lim )   & 
     377            WRITE(numicb,'("pe=",i3,x,a)') narea,'Dump triggered by excessive acceleration' 
     378      ENDIF 
    377379      ! 
    378380   END SUBROUTINE icb_accel 
  • NEMO/trunk/src/OCE/ICB/icbini.F90

    r10425 r10570  
    7878      !                          ! note that we choose to do this on all processors since we cannot 
    7979      !                          ! predict where icebergs will be ahead of time 
    80       CALL ctl_opn( numicb, 'icebergs.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
     80      IF( nn_verbose_level > 0) THEN 
     81         CALL ctl_opn( numicb, 'icebergs.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
     82      ENDIF 
    8183 
    8284      ! set parameters (mostly from namelist) 
     
    241243         CALL iom_close( inum )                                     ! close file 
    242244         ! 
    243          WRITE(numicb,*) 
    244          WRITE(numicb,*) '          calving read in a file' 
     245         IF( nn_verbose_level > 0) THEN 
     246            WRITE(numicb,*) 
     247            WRITE(numicb,*) '          calving read in a file' 
     248         ENDIF 
    245249         ALLOCATE( sf_icb(1), STAT=istat1 )         ! Create sf_icb structure (calving) 
    246250         ALLOCATE( sf_icb(1)%fnow(jpi,jpj,1), STAT=istat2 ) 
     
    336340      ibergs = icb_utl_count() 
    337341      CALL mpp_sum('icbini', ibergs) 
    338       WRITE(numicb,'(a,i6,a)') 'diamonds, icb_ini_gen: ',ibergs,' were generated' 
     342      IF( nn_verbose_level > 0) THEN 
     343         WRITE(numicb,'(a,i6,a)') 'diamonds, icb_ini_gen: ',ibergs,' were generated' 
     344      ENDIF 
    339345      ! 
    340346   END SUBROUTINE icb_ini_gen 
  • NEMO/trunk/src/OCE/ICB/icblbc.F90

    r10425 r10570  
    640640            zsbergs(0) = narea 
    641641            zsbergs(1) = nicbfldnsend(jn) 
    642             !IF ( nicbfldnsend(jn) .GT. 0) write(numicb,*) 'ICB sending ',nicbfldnsend(jn),' to ', ifldproc 
     642            !IF ( nicbfldnsend(jn) .GT. 0 .AND. nn_verbose_level > 0 ) write(numicb,*) 'ICB sending ',nicbfldnsend(jn),' to ', ifldproc 
    643643            CALL mppsend( 21, zsbergs(0:1), 2, ifldproc-1, nicbfldreq(jn)) 
    644644         ENDIF 
     
    656656             IF( nicbfldproc(jjn) .eq. INT(znbergs(1)) ) EXIT 
    657657            END DO 
    658             IF( jjn .GT. jpni ) write(numicb,*) 'ICB ERROR' 
     658            IF( jjn .GT. jpni .AND. nn_verbose_level > 0 ) write(numicb,*) 'ICB ERROR' 
    659659            nicbfldexpect(jjn) = INT( znbergs(2) ) 
    660             !IF ( nicbfldexpect(jjn) .GT. 0) write(numicb,*) 'ICB expecting ',nicbfldexpect(jjn),' from ', nicbfldproc(jjn) 
    661             !CALL FLUSH(numicb) 
     660            !IF ( nicbfldexpect(jjn) .GT. 0 .AND. nn_verbose_level > 0 ) write(numicb,*) 'ICB expecting ',nicbfldexpect(jjn),' from ', nicbfldproc(jjn) 
     661            !IF (nn_verbose_level > 0) CALL FLUSH(numicb) 
    662662         ENDIF 
    663663         ! 
     
    911911         ENDIF 
    912912         old => new 
    913         !WRITE( numicb,*) 'icb_increase_ibuffer',narea,' increased to',inew_size 
     913         !IF (nn_verbose_level > 0) WRITE( numicb,*) 'icb_increase_ibuffer',narea,' increased to',inew_size 
    914914      ENDIF 
    915915      ! 
  • NEMO/trunk/src/OCE/ICB/icbstp.F90

    r10068 r10570  
    163163      IF(lwp) WRITE(numout,'(a,i6)') 'icebergs: icb_end complete', narea 
    164164      ! 
    165       CALL flush( numicb ) 
    166       CLOSE( numicb ) 
     165      IF( nn_verbose_level > 0 ) THEN 
     166         CALL flush( numicb ) 
     167         CLOSE( numicb ) 
     168      ENDIF 
    167169      ! 
    168170   END SUBROUTINE icb_end 
  • NEMO/trunk/src/OCE/ICB/icbutl.F90

    r10425 r10570  
    625625      !!---------------------------------------------------------------------- 
    626626      ! 
     627      IF (nn_verbose_level == 0) RETURN 
    627628      pt => berg%current_point 
    628629      WRITE(numicb, 9200) kt, berg%number(1), & 
     
    649650      !!---------------------------------------------------------------------- 
    650651      ! 
     652      IF (nn_verbose_level == 0) RETURN 
    651653      this => first_berg 
    652654      IF( ASSOCIATED(this) ) THEN 
  • NEMO/trunk/src/OCE/IOM/in_out_manager.F90

    r10425 r10570  
    100100   !!---------------------------------------------------------------------- 
    101101   LOGICAL ::   ln_ctl           !: run control for debugging 
     102   TYPE :: sn_ctl                !: optional use structure for finer control over output selection 
     103      LOGICAL :: l_config  = .FALSE.  !: activate/deactivate finer control 
     104                                      !  Note if l_config is True then ln_ctl is ignored. 
     105                                      !  Otherwise setting ln_ctl True is equivalent to setting 
     106                                      !  all the following logicals in this structure True 
     107      LOGICAL :: l_runstat = .FALSE.  !: Produce/do not produce run.stat file (T/F) 
     108      LOGICAL :: l_trcstat = .FALSE.  !: Produce/do not produce tracer.stat file (T/F) 
     109      LOGICAL :: l_oceout  = .FALSE.  !: Produce all ocean.outputs    (T) or just one (F) 
     110      LOGICAL :: l_layout  = .FALSE.  !: Produce all layout.dat files (T) or just one (F) 
     111      LOGICAL :: l_mppout  = .FALSE.  !: Produce/do not produce mpp.output_XXXX files (T/F) 
     112      LOGICAL :: l_mpptop  = .FALSE.  !: Produce/do not produce mpp.top.output_XXXX files (T/F) 
     113                                      !  Optional subsetting of processor report files 
     114                                      !  Default settings of 0/1000000/1 should ensure all areas report. 
     115                                      !  Set to a more restrictive range to select specific areas 
     116      INTEGER :: procmin   = 0        !: Minimum narea to output 
     117      INTEGER :: procmax   = 1000000  !: Maximum narea to output 
     118      INTEGER :: procincr  = 1        !: narea increment to output 
     119      INTEGER :: ptimincr  = 1        !: timestep increment to output (time.step and run.stat) 
     120   END TYPE 
     121   TYPE (sn_ctl) :: sn_cfctl     !: run control structure for selective output 
    102122   LOGICAL ::   ln_timing        !: run control for timing 
    103123   LOGICAL ::   ln_diacfl        !: flag whether to create CFL diagnostics 
  • NEMO/trunk/src/OCE/LBC/mppini.F90

    r10560 r10570  
    151151      INTEGER ::   inbi, inbj, iimax,  ijmax, icnt1, icnt2 
    152152      LOGICAL ::   llbest 
     153      LOGICAL ::   llwrtlay 
    153154      INTEGER, ALLOCATABLE, DIMENSION(:)     ::   iin, ii_nono, ii_noea          ! 1D workspace 
    154155      INTEGER, ALLOCATABLE, DIMENSION(:)     ::   ijn, ii_noso, ii_nowe          !  -     - 
     
    167168      !!---------------------------------------------------------------------- 
    168169 
     170      llwrtlay = lwp .OR. ln_ctl .OR. sn_cfctl%l_layout 
    169171      ! do we need to take into account bdy_msk? 
    170172      REWIND( numnam_ref )              ! Namelist nambdy in reference namelist : BDY 
     
    554556 
    555557      ! Save processor layout in ascii file 
    556       IF (lwp) THEN 
     558      IF (llwrtlay) THEN 
    557559         CALL ctl_opn( inum, 'layout.dat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., narea ) 
    558560         WRITE(inum,'(a)') '   jpnij   jpimax  jpjmax    jpk  jpiglo  jpjglo'//& 
     
    615617            WRITE(numout,*) '   ==>>>   North fold boundary prepared for jpni >1' 
    616618            ! additional prints in layout.dat 
     619         ENDIF 
     620         IF (llwrtlay) THEN 
    617621            WRITE(inum,*) 
    618622            WRITE(inum,*) 
     
    629633      IF( ln_nnogather ) THEN 
    630634         CALL mpp_init_nfdcom     ! northfold neighbour lists 
    631          IF (lwp) THEN 
     635         IF (llwrtlay) THEN 
    632636            WRITE(inum,*) 
    633637            WRITE(inum,*) 
     
    640644      ENDIF 
    641645      ! 
    642       IF (lwp) CLOSE(inum)    
     646      IF (llwrtlay) CLOSE(inum)    
    643647      ! 
    644648      DEALLOCATE(iin, ijn, ii_nono, ii_noea, ii_noso, ii_nowe,    & 
  • NEMO/trunk/src/OCE/SBC/sbcfwb.F90

    r10425 r10570  
    144144         ENDIF 
    145145         ! 
    146          IF( kt == nitend .AND. lwp ) THEN            ! save fwfold value in a file 
     146         IF( kt == nitend .AND. lwm ) THEN            ! save fwfold value in a file (only one required) 
    147147            CALL ctl_opn( inum, 'EMPave.dat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., narea ) 
    148148            WRITE( inum, "(24X,I8,2ES24.16)" ) nyear, a_fwb_b, a_fwb 
  • NEMO/trunk/src/OCE/nemogcm.F90

    r10510 r10570  
    257257      CHARACTER(len=120), DIMENSION(60) ::   cltxt, cltxt2, clnam 
    258258      !! 
    259       NAMELIST/namctl/ ln_ctl   , nn_print, nn_ictls, nn_ictle,   & 
    260          &             nn_isplt , nn_jsplt, nn_jctls, nn_jctle,   & 
     259      NAMELIST/namctl/ ln_ctl   , sn_cfctl, nn_print, nn_ictls, nn_ictle,   & 
     260         &             nn_isplt , nn_jsplt, nn_jctls, nn_jctle,             & 
    261261         &             ln_timing, ln_diacfl 
    262262      NAMELIST/namcfg/ ln_read_cfg, cn_domcfg, ln_closea, ln_write_cfg, cn_domcfg_out, ln_use_jattr 
     
    327327 
    328328      narea = narea + 1                                     ! mynode return the rank of proc (0 --> jpnij -1 ) 
     329 
     330      IF( sn_cfctl%l_config ) THEN 
     331         ! Activate finer control of report outputs 
     332         ! optionally switch off output from selected areas (note this only 
     333         ! applies to output which does not involve global communications) 
     334         IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
     335           & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
     336           &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
     337      ELSE 
     338         ! Use ln_ctl to turn on or off all options. 
     339         CALL nemo_set_cfctl( sn_cfctl, ln_ctl, .TRUE. ) 
     340      ENDIF 
    329341 
    330342      lwm = (narea == 1)                                    ! control of output namelists 
     
    504516         WRITE(numout,*) '   Namelist namctl' 
    505517         WRITE(numout,*) '      run control (for debugging)     ln_ctl     = ', ln_ctl 
     518         WRITE(numout,*) '       finer control over o/p sn_cfctl%l_config  = ', sn_cfctl%l_config 
     519         WRITE(numout,*) '                              sn_cfctl%l_runstat = ', sn_cfctl%l_runstat 
     520         WRITE(numout,*) '                              sn_cfctl%l_trcstat = ', sn_cfctl%l_trcstat 
     521         WRITE(numout,*) '                              sn_cfctl%l_oceout  = ', sn_cfctl%l_oceout 
     522         WRITE(numout,*) '                              sn_cfctl%l_layout  = ', sn_cfctl%l_layout 
     523         WRITE(numout,*) '                              sn_cfctl%l_mppout  = ', sn_cfctl%l_mppout 
     524         WRITE(numout,*) '                              sn_cfctl%l_mpptop  = ', sn_cfctl%l_mpptop 
     525         WRITE(numout,*) '                              sn_cfctl%procmin   = ', sn_cfctl%procmin   
     526         WRITE(numout,*) '                              sn_cfctl%procmax   = ', sn_cfctl%procmax   
     527         WRITE(numout,*) '                              sn_cfctl%procincr  = ', sn_cfctl%procincr  
     528         WRITE(numout,*) '                              sn_cfctl%ptimincr  = ', sn_cfctl%ptimincr  
    506529         WRITE(numout,*) '      level of print                  nn_print   = ', nn_print 
    507530         WRITE(numout,*) '      Start i indice for SUM control  nn_ictls   = ', nn_ictls 
     
    650673   END SUBROUTINE nemo_alloc 
    651674 
     675   SUBROUTINE nemo_set_cfctl(sn_cfctl, setto, for_all ) 
     676      !!---------------------------------------------------------------------- 
     677      !!                     ***  ROUTINE nemo_set_cfctl  *** 
     678      !! 
     679      !! ** Purpose :   Set elements of the output control structure to setto. 
     680      !!                for_all should be .false. unless all areas are to be 
     681      !!                treated identically. 
     682      !! 
     683      !! ** Method  :   Note this routine can be used to switch on/off some 
     684      !!                types of output for selected areas but any output types 
     685      !!                that involve global communications (e.g. mpp_max, glob_sum) 
     686      !!                should be protected from selective switching by the 
     687      !!                for_all argument 
     688      !!---------------------------------------------------------------------- 
     689      LOGICAL :: setto, for_all 
     690      TYPE (sn_ctl) :: sn_cfctl 
     691      !!---------------------------------------------------------------------- 
     692      IF( for_all ) THEN 
     693         sn_cfctl%l_runstat = setto 
     694         sn_cfctl%l_trcstat = setto 
     695      ENDIF 
     696      sn_cfctl%l_oceout  = setto 
     697      sn_cfctl%l_layout  = setto 
     698      sn_cfctl%l_mppout  = setto 
     699      sn_cfctl%l_mpptop  = setto 
     700   END SUBROUTINE nemo_set_cfctl 
     701 
    652702   !!====================================================================== 
    653703END MODULE nemogcm 
  • NEMO/trunk/src/OCE/stpctl.F90

    r10425 r10570  
    6767      REAL(wp)               ::   zzz                 ! local real  
    6868      REAL(wp), DIMENSION(9) ::   zmax 
     69      LOGICAL                ::   ll_wrtstp, ll_colruns, ll_wrtruns 
    6970      CHARACTER(len=20) :: clname 
    7071      !!---------------------------------------------------------------------- 
    7172      ! 
     73      ll_wrtstp  = ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 
     74      ll_colruns = ll_wrtstp .AND. ( ln_ctl .OR. sn_cfctl%l_runstat ) 
     75      ll_wrtruns = ll_colruns .AND. lwm 
    7276      IF( kt == nit000 .AND. lwp ) THEN 
    7377         WRITE(numout,*) 
     
    7680         !                                ! open time.step file 
    7781         IF( lwm ) CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    78          !                                ! open run.stat file 
    79          IF( ln_ctl .AND. lwm ) THEN 
     82         !                                ! open run.stat file(s) at start whatever 
     83         !                                ! the value of sn_cfctl%ptimincr 
     84         IF( lwm .AND. ( ln_ctl .OR. sn_cfctl%l_runstat ) ) THEN 
    8085            CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    8186            clname = 'run.stat.nc' 
     
    99104      IF( kt == nit000 )   lsomeoce = COUNT( ssmask(:,:) == 1._wp ) > 0 
    100105      ! 
    101       IF(lwm) THEN                        !==  current time step  ==!   ("time.step" file) 
     106      IF(lwm .AND. ll_wrtstp) THEN        !==  current time step  ==!   ("time.step" file) 
    102107         WRITE ( numstp, '(1x, i8)' )   kt 
    103108         REWIND( numstp ) 
     
    121126      ENDIF 
    122127      ! 
    123       IF( ln_ctl ) THEN 
     128      IF( ll_colruns ) THEN 
    124129         CALL mpp_max( "stpctl", zmax )          ! max over the global domain 
    125130         nstop = NINT( zmax(7) )                 ! nstop indicator sheared among all local domains 
    126131      ENDIF 
    127132      !                                   !==  run statistics  ==!   ("run.stat" files) 
    128       IF( ln_ctl .AND. lwm ) THEN 
     133      IF( ll_wrtruns ) THEN 
    129134         WRITE(numrun,9500) kt, zmax(1), zmax(2), -zmax(3), zmax(4) 
    130135         istatus = NF90_PUT_VAR( idrun, idssh, (/ zmax(1)/), (/kt/), (/1/) ) 
  • NEMO/trunk/src/OFF/nemogcm.F90

    r10457 r10570  
    159159      CHARACTER(len=120), DIMENSION(30) ::   cltxt, cltxt2, clnam 
    160160      !! 
    161       NAMELIST/namctl/ ln_ctl   , nn_print, nn_ictls, nn_ictle,   & 
    162          &             nn_isplt , nn_jsplt, nn_jctls, nn_jctle,   & 
     161      NAMELIST/namctl/ ln_ctl   , sn_cfctl, nn_print, nn_ictls, nn_ictle,   & 
     162         &             nn_isplt , nn_jsplt, nn_jctls, nn_jctle,             & 
    163163         &             ln_timing, ln_diacfl 
    164164      NAMELIST/namcfg/ ln_read_cfg, cn_domcfg, ln_closea, ln_write_cfg, cn_domcfg_out, ln_use_jattr 
     
    215215      narea = narea + 1                       ! mynode return the rank of proc (0 --> jpnij -1 ) 
    216216 
     217      IF( sn_cfctl%l_config ) THEN 
     218         ! Activate finer control of report outputs 
     219         ! optionally switch off output from selected areas (note this only 
     220         ! applies to output which does not involve global communications) 
     221         IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
     222           & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
     223           &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
     224      ELSE 
     225         ! Use ln_ctl to turn on or off all options. 
     226         CALL nemo_set_cfctl( sn_cfctl, ln_ctl, .TRUE. ) 
     227      ENDIF 
     228 
    217229      lwm = (narea == 1)                      ! control of output namelists 
    218230      lwp = (narea == 1) .OR. ln_ctl          ! control of all listing output print 
     
    238250         WRITE(numout,*) '                       NEMO team' 
    239251         WRITE(numout,*) '                   Off-line TOP Model' 
    240          WRITE(numout,*) '                NEMO version 4.0  (2017) ' 
    241          WRITE(numout,*) 
     252         WRITE(numout,*) '                NEMO version 4.0  (2019) ' 
     253         WRITE(numout,*) 
     254         WRITE(numout,*) "           ._      ._      ._      ._      ._    " 
     255         WRITE(numout,*) "       _.-._)`\_.-._)`\_.-._)`\_.-._)`\_.-._)`\_ " 
     256         WRITE(numout,*) 
     257         WRITE(numout,*) "           o         _,           _,             " 
     258         WRITE(numout,*) "            o      .' (        .-' /             " 
     259         WRITE(numout,*) "           o     _/..._'.    .'   /              " 
     260         WRITE(numout,*) "      (    o .-'`      ` '-./  _.'               " 
     261         WRITE(numout,*) "       )    ( o)           ;= <_         (       " 
     262         WRITE(numout,*) "      (      '-.,\\__ __.-;`\   '.        )      " 
     263         WRITE(numout,*) "       )  )       \) |`\ \)  '.   \      (   (   " 
     264         WRITE(numout,*) "      (  (           \_/       '-._\      )   )  " 
     265         WRITE(numout,*) "       )  )                        `     (   (   " 
     266         WRITE(numout,*) "     ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ " 
    242267         WRITE(numout,*) 
    243268         DO ji = 1, SIZE(cltxt) 
    244             IF( TRIM(cltxt (ji)) /= '' )   WRITE(numout,*) cltxt(ji)    ! control print of mynode 
     269            IF( TRIM(cltxt (ji)) /= '' )   WRITE(numout,*) TRIM(cltxt(ji))    ! control print of mynode 
    245270         END DO 
    246271         WRITE(numout,*) 
    247272         WRITE(numout,*) 
    248273         DO ji = 1, SIZE(cltxt2) 
    249             IF( TRIM(cltxt2(ji)) /= '' )   WRITE(numout,*) cltxt2(ji)   ! control print of domain size 
     274            IF( TRIM(cltxt2(ji)) /= '' )   WRITE(numout,*) TRIM(cltxt2(ji))   ! control print of domain size 
    250275         END DO 
    251276         ! 
     
    324349         WRITE(numout,*) '   Namelist namctl' 
    325350         WRITE(numout,*) '      run control (for debugging)     ln_ctl     = ', ln_ctl 
     351         WRITE(numout,*) '       finer control over o/p sn_cfctl%l_config  = ', sn_cfctl%l_config 
     352         WRITE(numout,*) '                              sn_cfctl%l_runstat = ', sn_cfctl%l_runstat 
     353         WRITE(numout,*) '                              sn_cfctl%l_trcstat = ', sn_cfctl%l_trcstat 
     354         WRITE(numout,*) '                              sn_cfctl%l_oceout  = ', sn_cfctl%l_oceout 
     355         WRITE(numout,*) '                              sn_cfctl%l_layout  = ', sn_cfctl%l_layout 
     356         WRITE(numout,*) '                              sn_cfctl%l_mppout  = ', sn_cfctl%l_mppout 
     357         WRITE(numout,*) '                              sn_cfctl%l_mpptop  = ', sn_cfctl%l_mpptop 
     358         WRITE(numout,*) '                              sn_cfctl%procmin   = ', sn_cfctl%procmin   
     359         WRITE(numout,*) '                              sn_cfctl%procmax   = ', sn_cfctl%procmax   
     360         WRITE(numout,*) '                              sn_cfctl%procincr  = ', sn_cfctl%procincr  
     361         WRITE(numout,*) '                              sn_cfctl%ptimincr  = ', sn_cfctl%ptimincr  
    326362         WRITE(numout,*) '      level of print                  nn_print   = ', nn_print 
    327363         WRITE(numout,*) '      Start i indice for SUM control  nn_ictls   = ', nn_ictls 
     
    449485   END SUBROUTINE nemo_alloc 
    450486 
     487   SUBROUTINE nemo_set_cfctl(sn_cfctl, setto, for_all ) 
     488      !!---------------------------------------------------------------------- 
     489      !!                     ***  ROUTINE nemo_set_cfctl  *** 
     490      !! 
     491      !! ** Purpose :   Set elements of the output control structure to setto. 
     492      !!                for_all should be .false. unless all areas are to be 
     493      !!                treated identically. 
     494      !! 
     495      !! ** Method  :   Note this routine can be used to switch on/off some 
     496      !!                types of output for selected areas but any output types 
     497      !!                that involve global communications (e.g. mpp_max, glob_sum) 
     498      !!                should be protected from selective switching by the 
     499      !!                for_all argument 
     500      !!---------------------------------------------------------------------- 
     501      LOGICAL :: setto, for_all 
     502      TYPE (sn_ctl) :: sn_cfctl 
     503      !!---------------------------------------------------------------------- 
     504      IF( for_all ) THEN 
     505         sn_cfctl%l_runstat = setto 
     506         sn_cfctl%l_trcstat = setto 
     507      ENDIF 
     508      sn_cfctl%l_oceout  = setto 
     509      sn_cfctl%l_layout  = setto 
     510      sn_cfctl%l_mppout  = setto 
     511      sn_cfctl%l_mpptop  = setto 
     512   END SUBROUTINE nemo_set_cfctl 
     513 
    451514   SUBROUTINE istate_init 
    452515      !!---------------------------------------------------------------------- 
  • NEMO/trunk/src/SAO/nemogcm.F90

    r10425 r10570  
    9393      CHARACTER(len=120), DIMENSION(30) ::   cltxt, cltxt2, clnam 
    9494      ! 
    95       NAMELIST/namctl/ ln_ctl   , nn_print, nn_ictls, nn_ictle,   & 
    96          &             nn_isplt , nn_jsplt, nn_jctls, nn_jctle,   & 
     95      NAMELIST/namctl/ ln_ctl   , sn_cfctl, nn_print, nn_ictls, nn_ictle,   & 
     96         &             nn_isplt , nn_jsplt, nn_jctls, nn_jctle,             & 
    9797         &             ln_timing, ln_diacfl 
    9898      NAMELIST/namcfg/ ln_read_cfg, cn_domcfg, ln_closea, ln_write_cfg, cn_domcfg_out, ln_use_jattr 
     
    164164      narea = narea + 1                                     ! mynode return the rank of proc (0 --> jpnij -1 ) 
    165165 
     166      IF( sn_cfctl%l_config ) THEN 
     167         ! Activate finer control of report outputs 
     168         ! optionally switch off output from selected areas (note this only 
     169         ! applies to output which does not involve global communications 
     170         IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
     171           & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
     172           &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
     173      ELSE 
     174         ! Use ln_ctl to turn on or off all options. 
     175         CALL nemo_set_cfctl( sn_cfctl, ln_ctl, .TRUE. ) 
     176      ENDIF 
     177 
    166178      lwm = (narea == 1)                                    ! control of output namelists 
    167179      lwp = (narea == 1) .OR. ln_ctl                        ! control of all listing output print 
     
    188200         WRITE(numout,*) '                       NEMO team' 
    189201         WRITE(numout,*) '            Stand Alone Observation operator' 
    190          WRITE(numout,*) '                NEMO version 4.0  (2017) ' 
    191          WRITE(numout,*) 
     202         WRITE(numout,*) '                NEMO version 4.0  (2019) ' 
     203         WRITE(numout,*) 
     204         WRITE(numout,*) "           ._      ._      ._      ._      ._    " 
     205         WRITE(numout,*) "       _.-._)`\_.-._)`\_.-._)`\_.-._)`\_.-._)`\_ " 
     206         WRITE(numout,*) 
     207         WRITE(numout,*) "           o         _,           _,             " 
     208         WRITE(numout,*) "            o      .' (        .-' /             " 
     209         WRITE(numout,*) "           o     _/..._'.    .'   /              " 
     210         WRITE(numout,*) "      (    o .-'`      ` '-./  _.'               " 
     211         WRITE(numout,*) "       )    ( o)           ;= <_         (       " 
     212         WRITE(numout,*) "      (      '-.,\\__ __.-;`\   '.        )      " 
     213         WRITE(numout,*) "       )  )       \) |`\ \)  '.   \      (   (   " 
     214         WRITE(numout,*) "      (  (           \_/       '-._\      )   )  " 
     215         WRITE(numout,*) "       )  )                        `     (   (   " 
     216         WRITE(numout,*) "     ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ " 
    192217         WRITE(numout,*) 
    193218         DO ji = 1, SIZE(cltxt) 
    194             IF( TRIM(cltxt (ji)) /= '' )   WRITE(numout,*) cltxt(ji)    ! control print of mynode 
     219            IF( TRIM(cltxt (ji)) /= '' )   WRITE(numout,*) TRIM(cltxt(ji))    ! control print of mynode 
    195220         END DO 
    196221         WRITE(numout,*) 
    197222         WRITE(numout,*) 
    198223         DO ji = 1, SIZE(cltxt2) 
    199             IF( TRIM(cltxt2(ji)) /= '' )   WRITE(numout,*) cltxt2(ji)   ! control print of domain size 
     224            IF( TRIM(cltxt2(ji)) /= '' )   WRITE(numout,*) TRIM(cltxt2(ji))   ! control print of domain size 
    200225         END DO 
    201226         ! 
     
    245270         WRITE(numout,*) '   Namelist namctl' 
    246271         WRITE(numout,*) '      run control (for debugging)     ln_ctl     = ', ln_ctl 
     272         WRITE(numout,*) '       finer control over o/p sn_cfctl%l_config  = ', sn_cfctl%l_config 
     273         WRITE(numout,*) '                              sn_cfctl%l_runstat = ', sn_cfctl%l_runstat 
     274         WRITE(numout,*) '                              sn_cfctl%l_trcstat = ', sn_cfctl%l_trcstat 
     275         WRITE(numout,*) '                              sn_cfctl%l_oceout  = ', sn_cfctl%l_oceout 
     276         WRITE(numout,*) '                              sn_cfctl%l_layout  = ', sn_cfctl%l_layout 
     277         WRITE(numout,*) '                              sn_cfctl%l_mppout  = ', sn_cfctl%l_mppout 
     278         WRITE(numout,*) '                              sn_cfctl%l_mpptop  = ', sn_cfctl%l_mpptop 
     279         WRITE(numout,*) '                              sn_cfctl%procmin   = ', sn_cfctl%procmin   
     280         WRITE(numout,*) '                              sn_cfctl%procmax   = ', sn_cfctl%procmax   
     281         WRITE(numout,*) '                              sn_cfctl%procincr  = ', sn_cfctl%procincr  
     282         WRITE(numout,*) '                              sn_cfctl%ptimincr  = ', sn_cfctl%ptimincr  
    247283         WRITE(numout,*) '      level of print                  nn_print   = ', nn_print 
    248284         WRITE(numout,*) '      Start i indice for SUM control  nn_ictls   = ', nn_ictls 
     
    266302      IF(lwp) THEN                  ! control print 
    267303         WRITE(numout,*) 
    268          WRITE(numout,*) 'namcfg  : configuration initialization through namelist read' 
    269          WRITE(numout,*) '~~~~~~~ ' 
    270304         WRITE(numout,*) '   Namelist namcfg' 
    271305         WRITE(numout,*) '      read domain configuration file                ln_read_cfg      = ', ln_read_cfg 
    272306         WRITE(numout,*) '         filename to be read                           cn_domcfg     = ', TRIM(cn_domcfg) 
    273307         WRITE(numout,*) '         keep closed seas in the domain (if exist)     ln_closea     = ', ln_closea 
    274          WRITE(numout,*) '      write configuration definition file           ln_write_cfg     = ', ln_write_cfg 
     308         WRITE(numout,*) '      create a configuration definition file        ln_write_cfg     = ', ln_write_cfg 
    275309         WRITE(numout,*) '         filename to be written                        cn_domcfg_out = ', TRIM(cn_domcfg_out) 
    276310         WRITE(numout,*) '      use file attribute if exists as i/p j-start   ln_use_jattr     = ', ln_use_jattr 
     
    317351      ENDIF 
    318352      ! 
    319       IF( 1_wp /= SIGN(1._wp,-0._wp)  )   CALL ctl_stop( 'nemo_ctl: The intrinsec SIGN function follows ',  & 
    320          &                                               'f2003 standard. '                              ,  & 
    321          &                                               'Compile with key_nosignedzero enabled' ) 
     353      IF( 1._wp /= SIGN(1._wp,-0._wp)  )   CALL ctl_stop( 'nemo_ctl: The intrinsec SIGN function follows f2003 standard.',  & 
     354         &                                                'Compile with key_nosignedzero enabled:',   & 
     355         &                                                '--> add -Dkey_nosignedzero to the definition of %CPP in your arch file' ) 
    322356      ! 
    323357   END SUBROUTINE nemo_ctl 
     
    377411   END SUBROUTINE nemo_alloc 
    378412 
     413   SUBROUTINE nemo_set_cfctl(sn_cfctl, setto, for_all ) 
     414      !!---------------------------------------------------------------------- 
     415      !!                     ***  ROUTINE nemo_set_cfctl  *** 
     416      !! 
     417      !! ** Purpose :   Set elements of the output control structure to setto. 
     418      !!                for_all should be .false. unless all areas are to be 
     419      !!                treated identically. 
     420      !! 
     421      !! ** Method  :   Note this routine can be used to switch on/off some 
     422      !!                types of output for selected areas but any output types 
     423      !!                that involve global communications (e.g. mpp_max, glob_sum) 
     424      !!                should be protected from selective switching by the 
     425      !!                for_all argument 
     426      !!---------------------------------------------------------------------- 
     427      LOGICAL :: setto, for_all 
     428      TYPE (sn_ctl) :: sn_cfctl 
     429      !!---------------------------------------------------------------------- 
     430      IF( for_all ) THEN 
     431         sn_cfctl%l_runstat = setto 
     432         sn_cfctl%l_trcstat = setto 
     433      ENDIF 
     434      sn_cfctl%l_oceout  = setto 
     435      sn_cfctl%l_layout  = setto 
     436      sn_cfctl%l_mppout  = setto 
     437      sn_cfctl%l_mpptop  = setto 
     438   END SUBROUTINE nemo_set_cfctl 
     439 
    379440   !!====================================================================== 
    380441END MODULE nemogcm 
  • NEMO/trunk/src/SAS/nemogcm.F90

    r10459 r10570  
    183183      CHARACTER(len=80)                 ::   clname 
    184184      !! 
    185       NAMELIST/namctl/ ln_ctl   , nn_print, nn_ictls, nn_ictle,   & 
    186          &             nn_isplt , nn_jsplt, nn_jctls, nn_jctle,   & 
     185      NAMELIST/namctl/ ln_ctl   , sn_cfctl, nn_print, nn_ictls, nn_ictle,   & 
     186         &             nn_isplt , nn_jsplt, nn_jctls, nn_jctle,             & 
    187187         &             ln_timing, ln_diacfl 
    188188      NAMELIST/namcfg/ ln_read_cfg, cn_domcfg, ln_closea, ln_write_cfg, cn_domcfg_out, ln_use_jattr 
     
    261261      narea = narea + 1                                     ! mynode return the rank of proc (0 --> jpnij -1 ) 
    262262 
     263      IF( sn_cfctl%l_config ) THEN 
     264         ! Activate finer control of report outputs 
     265         ! optionally switch off output from selected areas (note this only 
     266         ! applies to output which does not involve global communications) 
     267         IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
     268           & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
     269           &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
     270      ELSE 
     271         ! Use ln_ctl to turn on or off all options. 
     272         CALL nemo_set_cfctl( sn_cfctl, ln_ctl, .TRUE. ) 
     273      ENDIF 
     274 
    263275      lwm = (narea == 1)                                    ! control of output namelists 
    264276      lwp = (narea == 1) .OR. ln_ctl                        ! control of all listing output print 
     
    286298         WRITE(numout,*) '                       NEMO team' 
    287299         WRITE(numout,*) '            Ocean General Circulation Model' 
    288          WRITE(numout,*) '                NEMO version 4.0  (2017) ' 
     300         WRITE(numout,*) '                NEMO version 4.0  (2019) ' 
    289301         WRITE(numout,*) '             StandAlone Surface version (SAS) ' 
    290          WRITE(numout,*) 
     302         WRITE(numout,*) "           ._      ._      ._      ._      ._    " 
     303         WRITE(numout,*) "       _.-._)`\_.-._)`\_.-._)`\_.-._)`\_.-._)`\_ " 
     304         WRITE(numout,*) 
     305         WRITE(numout,*) "           o         _,           _,             " 
     306         WRITE(numout,*) "            o      .' (        .-' /             " 
     307         WRITE(numout,*) "           o     _/..._'.    .'   /              " 
     308         WRITE(numout,*) "      (    o .-'`      ` '-./  _.'               " 
     309         WRITE(numout,*) "       )    ( o)           ;= <_         (       " 
     310         WRITE(numout,*) "      (      '-.,\\__ __.-;`\   '.        )      " 
     311         WRITE(numout,*) "       )  )       \) |`\ \)  '.   \      (   (   " 
     312         WRITE(numout,*) "      (  (           \_/       '-._\      )   )  " 
     313         WRITE(numout,*) "       )  )                        `     (   (   " 
     314         WRITE(numout,*) "     ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ " 
    291315         WRITE(numout,*) 
    292316         DO ji = 1, SIZE(cltxt) 
     
    361385         WRITE(numout,*) '   Namelist namctl' 
    362386         WRITE(numout,*) '      run control (for debugging)     ln_ctl     = ', ln_ctl 
     387         WRITE(numout,*) '       finer control over o/p sn_cfctl%l_config  = ', sn_cfctl%l_config 
     388         WRITE(numout,*) '                              sn_cfctl%l_runstat = ', sn_cfctl%l_runstat 
     389         WRITE(numout,*) '                              sn_cfctl%l_trcstat = ', sn_cfctl%l_trcstat 
     390         WRITE(numout,*) '                              sn_cfctl%l_oceout  = ', sn_cfctl%l_oceout 
     391         WRITE(numout,*) '                              sn_cfctl%l_layout  = ', sn_cfctl%l_layout 
     392         WRITE(numout,*) '                              sn_cfctl%l_mppout  = ', sn_cfctl%l_mppout 
     393         WRITE(numout,*) '                              sn_cfctl%l_mpptop  = ', sn_cfctl%l_mpptop 
     394         WRITE(numout,*) '                              sn_cfctl%procmin   = ', sn_cfctl%procmin   
     395         WRITE(numout,*) '                              sn_cfctl%procmax   = ', sn_cfctl%procmax   
     396         WRITE(numout,*) '                              sn_cfctl%procincr  = ', sn_cfctl%procincr  
     397         WRITE(numout,*) '                              sn_cfctl%ptimincr  = ', sn_cfctl%ptimincr  
    363398         WRITE(numout,*) '      level of print                  nn_print   = ', nn_print 
    364399         WRITE(numout,*) '      Start i indice for SUM control  nn_ictls   = ', nn_ictls 
     
    494529   END SUBROUTINE nemo_alloc 
    495530 
     531   SUBROUTINE nemo_set_cfctl(sn_cfctl, setto, for_all ) 
     532      !!---------------------------------------------------------------------- 
     533      !!                     ***  ROUTINE nemo_set_cfctl  *** 
     534      !! 
     535      !! ** Purpose :   Set elements of the output control structure to setto. 
     536      !!                for_all should be .false. unless all areas are to be 
     537      !!                treated identically. 
     538      !! 
     539      !! ** Method  :   Note this routine can be used to switch on/off some 
     540      !!                types of output for selected areas but any output types 
     541      !!                that involve global communications (e.g. mpp_max, glob_sum) 
     542      !!                should be protected from selective switching by the 
     543      !!                for_all argument 
     544      !!---------------------------------------------------------------------- 
     545      LOGICAL :: setto, for_all 
     546      TYPE (sn_ctl) :: sn_cfctl 
     547      !!---------------------------------------------------------------------- 
     548      IF( for_all ) THEN 
     549         sn_cfctl%l_runstat = setto 
     550         sn_cfctl%l_trcstat = setto 
     551      ENDIF 
     552      sn_cfctl%l_oceout  = setto 
     553      sn_cfctl%l_layout  = setto 
     554      sn_cfctl%l_mppout  = setto 
     555      sn_cfctl%l_mpptop  = setto 
     556   END SUBROUTINE nemo_set_cfctl 
     557 
    496558   !!====================================================================== 
    497559END MODULE nemogcm 
  • NEMO/trunk/src/TOP/prtctl_trc.F90

    r9125 r10570  
    210210         sind = narea 
    211211         eind = narea 
    212          clb_name = "('mpp.top.output_',I3.3)" 
     212         clb_name = "('mpp.top.output_',I4.4)" 
    213213         cl_run = 'MULTI processor run' 
    214214         ! use indices for each area computed by mpp_init subroutine 
     
    229229         sind = 1 
    230230         eind = ijsplt 
    231          clb_name = "('mono.top.output_',I3.3)" 
     231         clb_name = "('mono.top.output_',I4.4)" 
    232232         cl_run   = 'MONO processor run ' 
    233233         ! compute indices for each area as done in mpp_init subroutine 
  • NEMO/trunk/src/TOP/trcini.F90

    r10425 r10570  
    7272      CALL trc_ice_ini   ! Tracers in sea ice 
    7373      ! 
    74       IF(lwm) CALL ctl_opn( numstr, 'tracer.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp , narea ) 
     74      IF( lwm .AND. sn_cfctl%l_trcstat ) THEN 
     75         CALL ctl_opn( numstr, 'tracer.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp , narea ) 
     76      ENDIF 
    7577      ! 
    7678      CALL trc_ini_state  !  passive tracers initialisation : from a restart or from clim 
  • NEMO/trunk/src/TOP/trcstp.F90

    r10425 r10570  
    5757      INTEGER ::   jk, jn   ! dummy loop indices 
    5858      REAL(wp)::   ztrai    ! local scalar 
     59      LOGICAL ::   ll_trcstat ! local logical 
    5960      CHARACTER (len=25) ::   charout   ! 
    6061      !!------------------------------------------------------------------- 
     
    6869      ENDIF 
    6970      ! 
     71      ll_trcstat  = ( ln_ctl .OR. sn_cfctl%l_trcstat ) .AND. & 
     72     &              ( ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) ) 
    7073      IF( kt == nittrc000 .AND. lk_trdmxl_trc )  CALL trd_mxl_trc_init    ! trends: Mixed-layer 
    7174      ! 
     
    109112      ENDIF 
    110113      ! 
    111       IF (ln_ctl ) THEN 
     114      IF (ll_trcstat) THEN 
    112115         ztrai = 0._wp                                                   !  content of all tracers 
    113116         DO jn = 1, jptra 
Note: See TracChangeset for help on using the changeset viewer.