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 12236 for NEMO/branches/2019/dev_r11943_MERGE_2019/src – NEMO

Ignore:
Timestamp:
2019-12-13T10:19:48+01:00 (4 years ago)
Author:
acc
Message:

Branch 2019/dev_r11943_MERGE_2019. Merge in changes from 2019/fix_sn_cfctl_ticket2328. Fully SETTE tested

Location:
NEMO/branches/2019/dev_r11943_MERGE_2019/src
Files:
92 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/ABL/ablmod.F90

    r12015 r12236  
    579579      CALL iom_put( "taum_oce", ptaum ) 
    580580 
    581       IF(ln_ctl) THEN 
     581      IF(sn_cfctl%l_prtctl) THEN 
    582582         CALL prt_ctl( tab2d_1=pwndm  , clinfo1=' abl_stp: wndm   : ' ) 
    583583         CALL prt_ctl( tab2d_1=ptaui  , clinfo1=' abl_stp: utau   : ' ) 
     
    605605         CALL lbc_lnk_multi( 'ablmod', ptaui_ice, 'U', -1., ptauj_ice, 'V', -1. ) 
    606606         ! 
    607          IF(ln_ctl)   CALL prt_ctl( tab2d_1=ptaui_ice  , clinfo1=' abl_stp: putaui : '   & 
    608             &                     , tab2d_2=ptauj_ice  , clinfo2='          pvtaui : ' ) 
     607         IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab2d_1=ptaui_ice  , clinfo1=' abl_stp: putaui : '   & 
     608            &                                , tab2d_2=ptauj_ice  , clinfo2='          pvtaui : ' ) 
    609609#endif 
    610610      !                            !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/ICE/icecor.F90

    r11536 r12236  
    165165      ! 
    166166      ! controls 
    167       IF( ln_ctl       )   CALL ice_prt3D   ('icecor')                                                             ! prints 
     167      IF( sn_cfctl%l_prtctl ) & 
     168         &                 CALL ice_prt3D   ('icecor')                                                             ! prints 
    168169      IF( ln_icectl .AND. kn == 2 ) & 
    169170         &                 CALL ice_prt     ( kt, iiceprt, jiceprt, 2, ' - Final state - ' )                       ! prints 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/ICE/icectl.F90

    r11612 r12236  
    695695      !!                  ***  ROUTINE ice_prt3D *** 
    696696      !! 
    697       !! ** Purpose : CTL prints of ice arrays in case ln_ctl is activated  
     697      !! ** Purpose : CTL prints of ice arrays in case sn_cfctl%prtctl is activated  
    698698      !! 
    699699      !!------------------------------------------------------------------- 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/ICE/icedyn_rdgrft.F90

    r11960 r12236  
    268268 
    269269      ! controls 
    270       IF( ln_ctl       )   CALL ice_prt3D   ('icedyn_rdgrft')                                                             ! prints 
     270      IF( sn_cfctl%l_prtctl )   CALL ice_prt3D   ('icedyn_rdgrft')                                                        ! prints 
    271271      IF( ln_icectl    )   CALL ice_prt     (kt, iiceprt, jiceprt,-1, ' - ice dyn rdgrft - ')                             ! prints 
    272272      IF( ln_icediachk )   CALL ice_cons_hsm(1, 'icedyn_rdgrft', rdiag_v, rdiag_s, rdiag_t, rdiag_fv, rdiag_fs, rdiag_ft) ! conservation 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/ICE/icedyn_rhg.F90

    r11960 r12236  
    8787      ! 
    8888      ! controls 
    89       IF( ln_ctl       )   CALL ice_prt3D   ('icedyn_rhg')                                                             ! prints 
     89      IF( sn_cfctl%l_prtctl ) & 
     90         &                 CALL ice_prt3D   ('icedyn_rhg')                                                             ! prints 
    9091      IF( ln_icediachk )   CALL ice_cons_hsm(1, 'icedyn_rhg', rdiag_v, rdiag_s, rdiag_t, rdiag_fv, rdiag_fs, rdiag_ft) ! conservation 
    9192      IF( ln_icediachk )   CALL ice_cons2D  (1, 'icedyn_rhg',  diag_v,  diag_s,  diag_t,  diag_fv,  diag_fs,  diag_ft) ! conservation 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/ICE/icedyn_rhg_evp.F90

    r11949 r12236  
    346346         l_full_nf_update = jter == nn_nevp   ! false: disable full North fold update (performances) for iter = 1 to nn_nevp-1 
    347347         ! 
    348 !!$         IF(ln_ctl) THEN   ! Convergence test 
     348!!$         IF(sn_cfctl%l_prtctl) THEN   ! Convergence test 
    349349!!$            DO jj = 1, jpjm1 
    350350!!$               zu_ice(:,jj) = u_ice(:,jj) ! velocity at previous time step 
     
    668668         ENDIF 
    669669 
    670 !!$         IF(ln_ctl) THEN   ! Convergence test 
     670!!$         IF(sn_cfctl%l_prtctl) THEN   ! Convergence test 
    671671!!$            DO jj = 2 , jpjm1 
    672672!!$               zresr(:,jj) = MAX( ABS( u_ice(:,jj) - zu_ice(:,jj) ), ABS( v_ice(:,jj) - zv_ice(:,jj) ) ) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/ICE/icethd.F90

    r11960 r12236  
    252252      ! controls 
    253253      IF( ln_icectl )   CALL ice_prt    (kt, iiceprt, jiceprt, 1, ' - ice thermodyn. - ') ! prints 
    254       IF( ln_ctl    )   CALL ice_prt3D  ('icethd')                                        ! prints 
     254      IF( sn_cfctl%l_prtctl )   & 
     255        &               CALL ice_prt3D  ('icethd')                                        ! prints 
    255256      IF( ln_timing )   CALL timing_stop('icethd')                                        ! timing 
    256257      ! 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/ICE/iceupdate.F90

    r11949 r12236  
    285285#endif 
    286286      IF( ln_icectl                      )   CALL ice_prt       (kt, iiceprt, jiceprt, 3, 'Final state ice_update') ! prints 
    287       IF( ln_ctl                         )   CALL ice_prt3D     ('iceupdate')                                       ! prints 
     287      IF( sn_cfctl%l_prtctl              )   CALL ice_prt3D     ('iceupdate')                                       ! prints 
    288288      IF( ln_timing                      )   CALL timing_stop   ('ice_update')                                      ! timing 
    289289      ! 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/C1D/dyncor_c1d.F90

    r11949 r12236  
    9797       
    9898      ! 
    99       IF(ln_ctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' cor  - Ua: ', mask1=umask,  & 
    100          &                       tab3d_2=pvv(:,:,:,Krhs), clinfo2=' Va: '       , mask2=vmask ) 
     99      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' cor  - Ua: ', mask1=umask,  & 
     100         &                                  tab3d_2=pvv(:,:,:,Krhs), clinfo2=' Va: '       , mask2=vmask ) 
    101101      ! 
    102102   END SUBROUTINE dyn_cor_c1d 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/C1D/dyndmp.F90

    r11960 r12236  
    219219      ! 
    220220      !                           ! Control print 
    221       IF( ln_ctl   )   CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' dmp  - Ua: ', mask1=umask,   & 
    222          &                           tab3d_2=pvv(:,:,:,Krhs), clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
     221      IF( sn_cfctl%l_prtctl   )   CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' dmp  - Ua: ', mask1=umask,   & 
     222         &                                      tab3d_2=pvv(:,:,:,Krhs), clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
    223223      ! 
    224224      ! 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/DOM/daymod.F90

    r10068 r12236  
    277277      IF( nsec_week > 7*nsecd )   nsec_week = ndt05     ! New week 
    278278 
    279       IF(ln_ctl) THEN 
     279      IF(sn_cfctl%l_prtctl) THEN 
    280280         WRITE(charout,FMT="('kt =', I4,'  d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear 
    281281         CALL prt_ctl_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/DYN/dynadv_cen2.F90

    r11949 r12236  
    141141      ENDIF 
    142142      !                                   ! Control print 
    143       IF(ln_ctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' cen2 adv - Ua: ', mask1=umask,   & 
    144          &                       tab3d_2=pvv(:,:,:,Krhs), clinfo2=           ' Va: ', mask2=vmask, clinfo3='dyn' ) 
     143      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' cen2 adv - Ua: ', mask1=umask,   & 
     144         &                                  tab3d_2=pvv(:,:,:,Krhs), clinfo2=           ' Va: ', mask2=vmask, clinfo3='dyn' ) 
    145145      ! 
    146146   END SUBROUTINE dyn_adv_cen2 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/DYN/dynadv_ubs.F90

    r11949 r12236  
    234234      ENDIF 
    235235      !                                         ! Control print 
    236       IF(ln_ctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' ubs2 adv - Ua: ', mask1=umask,   & 
    237          &                       tab3d_2=pvv(:,:,:,Krhs), clinfo2=           ' Va: ', mask2=vmask, clinfo3='dyn' ) 
     236      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' ubs2 adv - Ua: ', mask1=umask,   & 
     237         &                                  tab3d_2=pvv(:,:,:,Krhs), clinfo2=           ' Va: ', mask2=vmask, clinfo3='dyn' ) 
    238238      ! 
    239239   END SUBROUTINE dyn_adv_ubs 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/DYN/dynatf.F90

    r12150 r12236  
    328328      ENDIF 
    329329      ! 
    330       IF(ln_ctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Kaa), clinfo1=' nxt  - puu(:,:,:,Kaa): ', mask1=umask,   & 
    331          &                       tab3d_2=pvv(:,:,:,Kaa), clinfo2=' pvv(:,:,:,Kaa): '       , mask2=vmask ) 
     330      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Kaa), clinfo1=' nxt  - puu(:,:,:,Kaa): ', mask1=umask,   & 
     331         &                                  tab3d_2=pvv(:,:,:,Kaa), clinfo2=' pvv(:,:,:,Kaa): '       , mask2=vmask ) 
    332332      !  
    333333      IF( ln_dynspg_ts )   DEALLOCATE( zue, zve ) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/DYN/dynhpg.F90

    r12150 r12236  
    124124      ENDIF 
    125125      ! 
    126       IF(ln_ctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' hpg  - Ua: ', mask1=umask,   & 
    127          &                       tab3d_2=pvv(:,:,:,Krhs), clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
     126      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' hpg  - Ua: ', mask1=umask,   & 
     127         &                                  tab3d_2=pvv(:,:,:,Krhs), clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
    128128      ! 
    129129      IF( ln_timing )   CALL timing_stop('dyn_hpg') 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/DYN/dynkeg.F90

    r11949 r12236  
    149149      ENDIF 
    150150      ! 
    151       IF(ln_ctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' keg  - Ua: ', mask1=umask,   & 
    152          &                       tab3d_2=pvv(:,:,:,Krhs), clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
     151      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' keg  - Ua: ', mask1=umask,   & 
     152         &                                  tab3d_2=pvv(:,:,:,Krhs), clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
    153153      ! 
    154154      IF( ln_timing )   CALL timing_stop('dyn_keg') 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/DYN/dynldf.F90

    r11949 r12236  
    8282      ENDIF 
    8383      !                                          ! print sum trends (used for debugging) 
    84       IF(ln_ctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' ldf  - Ua: ', mask1=umask,   & 
    85          &                       tab3d_2=pvv(:,:,:,Krhs), clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
     84      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' ldf  - Ua: ', mask1=umask,   & 
     85         &                                  tab3d_2=pvv(:,:,:,Krhs), clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
    8686      ! 
    8787      IF( ln_timing )   CALL timing_stop('dyn_ldf') 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/DYN/dynldf_iso.F90

    r11949 r12236  
    288288 
    289289      ! print sum trends (used for debugging) 
    290       IF(ln_ctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' ldfh - Ua: ', mask1=umask, & 
    291          &                       tab3d_2=pvv(:,:,:,Krhs), clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
     290      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' ldfh - Ua: ', mask1=umask, & 
     291         &                                  tab3d_2=pvv(:,:,:,Krhs), clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
    292292 
    293293 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/DYN/dynspg.F90

    r12205 r12236  
    178178      ENDIF 
    179179      !                                      ! print mean trends (used for debugging) 
    180       IF(ln_ctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' spg  - Ua: ', mask1=umask, & 
    181          &                       tab3d_2=pvv(:,:,:,Krhs), clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
     180      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' spg  - Ua: ', mask1=umask, & 
     181         &                                  tab3d_2=pvv(:,:,:,Krhs), clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
    182182      ! 
    183183      IF( ln_timing )   CALL timing_stop('dyn_spg') 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/DYN/dynvor.F90

    r11960 r12236  
    181181      ! 
    182182      !                       ! print sum trends (used for debugging) 
    183       IF(ln_ctl) CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' vor  - Ua: ', mask1=umask,               & 
    184          &                     tab3d_2=pvv(:,:,:,Krhs), clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
     183      IF(sn_cfctl%l_prtctl) CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' vor  - Ua: ', mask1=umask,               & 
     184         &                                tab3d_2=pvv(:,:,:,Krhs), clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
    185185      ! 
    186186      IF( ln_timing )   CALL timing_stop('dyn_vor') 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/DYN/dynzad.F90

    r11949 r12236  
    116116      ENDIF 
    117117      !                             ! Control print 
    118       IF(ln_ctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' zad  - Ua: ', mask1=umask,   & 
    119          &                       tab3d_2=pvv(:,:,:,Krhs), clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
     118      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Krhs), clinfo1=' zad  - Ua: ', mask1=umask,   & 
     119         &                                  tab3d_2=pvv(:,:,:,Krhs), clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
    120120      ! 
    121121      IF( ln_timing )   CALL timing_stop('dyn_zad') 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/DYN/dynzdf.F90

    r12150 r12236  
    494494      ENDIF 
    495495      !                                          ! print mean trends (used for debugging) 
    496       IF(ln_ctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Kaa), clinfo1=' zdf  - Ua: ', mask1=umask,               & 
    497          &                       tab3d_2=pvv(:,:,:,Kaa), clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
     496      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=puu(:,:,:,Kaa), clinfo1=' zdf  - Ua: ', mask1=umask,               & 
     497         &                                  tab3d_2=pvv(:,:,:,Kaa), clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
    498498         ! 
    499499      IF( ln_timing )   CALL timing_stop('dyn_zdf') 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/DYN/sshwzv.F90

    r12150 r12236  
    125125      !                                           !------------------------------! 
    126126      ! 
    127       IF(ln_ctl)   CALL prt_ctl( tab2d_1=pssh(:,:,Kaa), clinfo1=' pssh(:,:,Kaa)  - : ', mask1=tmask ) 
     127      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab2d_1=pssh(:,:,Kaa), clinfo1=' pssh(:,:,Kaa)  - : ', mask1=tmask ) 
    128128      ! 
    129129      IF( ln_timing )   CALL timing_stop('ssh_nxt') 
     
    267267      ENDIF 
    268268      ! 
    269       IF(ln_ctl)   CALL prt_ctl( tab2d_1=pssh(:,:,Kmm), clinfo1=' pssh(:,:,Kmm)  - : ', mask1=tmask ) 
     269      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab2d_1=pssh(:,:,Kmm), clinfo1=' pssh(:,:,Kmm)  - : ', mask1=tmask ) 
    270270      ! 
    271271      IF( ln_timing )   CALL timing_stop('ssh_atf') 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/IOM/in_out_manager.F90

    r12182 r12236  
    9999   !!                    output monitoring 
    100100   !!---------------------------------------------------------------------- 
    101    LOGICAL ::   ln_ctl           !: run control for debugging 
    102    TYPE :: sn_ctl                !: optional use structure for finer control over output selection 
     101   TYPE :: sn_ctl                !: structure for control over output selection 
     102      LOGICAL :: l_glochk  = .FALSE.  !: range sanity checks are local (F) or global (T) 
     103                                      !  Use global setting for debugging only; 
     104                                      !  local breaches will still be reported 
     105                                      !  and stop the code in most cases. 
     106      LOGICAL :: l_allon   = .FALSE.  !: overall control; activate all following output options 
    103107      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 
     108                                      !  Note if l_config is True then sn_cfctl%l_allon is ignored. 
     109                                      !  Otherwise setting sn_cfctl%l_allon T/F is equivalent to  
     110                                      !  setting all the following logicals in this structure T/F 
     111                                      !  and disabling subsetting of processors 
    107112      LOGICAL :: l_runstat = .FALSE.  !: Produce/do not produce run.stat file (T/F) 
    108113      LOGICAL :: l_trcstat = .FALSE.  !: Produce/do not produce tracer.stat file (T/F) 
    109114      LOGICAL :: l_oceout  = .FALSE.  !: Produce all ocean.outputs    (T) or just one (F) 
    110115      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) 
     116      LOGICAL :: l_prtctl  = .FALSE.  !: Produce/do not produce mpp.output_XXXX files (T/F) 
     117      LOGICAL :: l_prttrc  = .FALSE.  !: Produce/do not produce mpp.top.output_XXXX files (T/F) 
     118      LOGICAL :: l_oasout  = .FALSE.  !: Produce/do not write oasis setup info to ocean.output (T/F) 
    113119                                      !  Optional subsetting of processor report files 
    114120                                      !  Default settings of 0/1000000/1 should ensure all areas report. 
     
    169175   CHARACTER(lc) ::   ctmp10                !: temporary character 10 
    170176   LOGICAL       ::   lwm      = .FALSE.    !: boolean : true on the 1st processor only (always) 
    171    LOGICAL       ::   lwp      = .FALSE.    !: boolean : true on the 1st processor only .OR. ln_ctl 
     177   LOGICAL       ::   lwp      = .FALSE.    !: boolean : true on the 1st processor only .OR. sn_cfctl%l_oceout=T 
    172178   LOGICAL       ::   lsp_area = .TRUE.     !: to make a control print over a specific area 
    173179   CHARACTER(lc) ::   cxios_context         !: context name used in xios 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/IOM/prtctl.F90

    r10068 r12236  
    5050      !!                debugging a new parametrization in mono or mpp.  
    5151      !! 
    52       !! ** Method  : 2 possibilities exist when setting the ln_ctl parameter to 
     52      !! ** Method  : 2 possibilities exist when setting the sn_cfctl%prtctl parameter to 
    5353      !!                .true. in the ocean namelist: 
    5454      !!              - to debug a MPI run .vs. a mono-processor one;  
     
    6464      !!                name must be explicitly typed if used. For instance if the 3D 
    6565      !!                array tn(:,:,:) must be passed through the prt_ctl subroutine,  
    66       !!                it must looks like: CALL prt_ctl(tab3d_1=tn). 
     66      !!                it must look like: CALL prt_ctl(tab3d_1=tn). 
    6767      !! 
    6868      !!                    tab2d_1 : first 2D array 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/LBC/mppini.F90

    r11960 r12236  
    171171      !!---------------------------------------------------------------------- 
    172172      ! 
    173       llwrtlay = lwp .OR. ln_ctl .OR. sn_cfctl%l_layout 
     173      llwrtlay = lwm .OR. sn_cfctl%l_layout 
    174174      ! 
    175175      !  0. read namelists parameters 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/LDF/ldfslp.F90

    r12150 r12236  
    367367      CALL lbc_lnk_multi( 'ldfslp', uslp , 'U', -1. , vslp , 'V', -1. , wslpi, 'W', -1., wslpj, 'W', -1. ) 
    368368 
    369       IF(ln_ctl) THEN 
     369      IF(sn_cfctl%l_prtctl) THEN 
    370370         CALL prt_ctl(tab3d_1=uslp , clinfo1=' slp  - u : ', tab3d_2=vslp,  clinfo2=' v : ', kdim=jpk) 
    371371         CALL prt_ctl(tab3d_1=wslpi, clinfo1=' slp  - wi: ', tab3d_2=wslpj, clinfo2=' wj: ', kdim=jpk) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/SBC/cpl_oasis3.F90

    r12182 r12236  
    203203      paral(5) = jpiglo                                         ! global extent in x 
    204204       
    205       IF( ln_ctl ) THEN 
     205      IF( sn_cfctl%l_oasout ) THEN 
    206206         WRITE(numout,*) ' multiexchg: paral (1:5)', paral 
    207207         WRITE(numout,*) ' multiexchg: jpi, jpj =', jpi, jpj 
     
    243243                  ENDIF 
    244244#endif 
    245                   IF( ln_ctl ) WRITE(numout,*) "Define", ji, jc, jm, " "//TRIM(zclname), " for ", OASIS_Out 
     245                  IF( sn_cfctl%l_oasout ) WRITE(numout,*) "Define", ji, jc, jm, " "//TRIM(zclname), " for ", OASIS_Out 
    246246                  CALL oasis_def_var (ssnd(ji)%nid(jc,jm), zclname, id_part   , (/ 2, 1 /),   & 
    247247                     &                OASIS_Out          , ishape , OASIS_REAL, nerror ) 
     
    250250                     CALL oasis_abort ( ssnd(ji)%nid(jc,jm), 'cpl_define', 'Failure in oasis_def_var' ) 
    251251                  ENDIF 
    252                   IF( ln_ctl .AND. ssnd(ji)%nid(jc,jm) /= -1 ) WRITE(numout,*) "variable defined in the namcouple" 
    253                   IF( ln_ctl .AND. ssnd(ji)%nid(jc,jm) == -1 ) WRITE(numout,*) "variable NOT defined in the namcouple" 
     252                  IF( sn_cfctl%l_oasout .AND. ssnd(ji)%nid(jc,jm) /= -1 ) WRITE(numout,*) "variable defined in the namcouple" 
     253                  IF( sn_cfctl%l_oasout .AND. ssnd(ji)%nid(jc,jm) == -1 ) WRITE(numout,*) "variable NOT defined in the namcouple" 
    254254               END DO 
    255255            END DO 
     
    288288                  ENDIF 
    289289#endif 
    290                   IF( ln_ctl ) WRITE(numout,*) "Define", ji, jc, jm, " "//TRIM(zclname), " for ", OASIS_In 
     290                  IF( sn_cfctl%l_oasout ) WRITE(numout,*) "Define", ji, jc, jm, " "//TRIM(zclname), " for ", OASIS_In 
    291291                  CALL oasis_def_var (srcv(ji)%nid(jc,jm), zclname, id_part   , (/ 2, 1 /),   & 
    292292                     &                OASIS_In           , ishape , OASIS_REAL, nerror ) 
     
    295295                     CALL oasis_abort ( srcv(ji)%nid(jc,jm), 'cpl_define', 'Failure in oasis_def_var' ) 
    296296                  ENDIF 
    297                   IF( ln_ctl .AND. srcv(ji)%nid(jc,jm) /= -1 ) WRITE(numout,*) "variable defined in the namcouple" 
    298                   IF( ln_ctl .AND. srcv(ji)%nid(jc,jm) == -1 ) WRITE(numout,*) "variable NOT defined in the namcouple" 
     297                  IF( sn_cfctl%l_oasout .AND. srcv(ji)%nid(jc,jm) /= -1 ) WRITE(numout,*) "variable defined in the namcouple" 
     298                  IF( sn_cfctl%l_oasout .AND. srcv(ji)%nid(jc,jm) == -1 ) WRITE(numout,*) "variable NOT defined in the namcouple" 
    299299 
    300300               END DO 
     
    349349               CALL oasis_put ( ssnd(kid)%nid(jc,jm), kstep, pdata(nldi:nlei, nldj:nlej,jc), kinfo ) 
    350350                
    351                IF( ln_ctl ) THEN         
    352                   IF( kinfo == OASIS_Sent     .OR. kinfo == OASIS_ToRest .OR.   & 
     351               IF ( sn_cfctl%l_oasout ) THEN         
     352                  IF ( kinfo == OASIS_Sent     .OR. kinfo == OASIS_ToRest .OR.   & 
    353353                     & kinfo == OASIS_SentOut  .OR. kinfo == OASIS_ToRestOut ) THEN 
    354354                     WRITE(numout,*) '****************' 
     
    420420                  &        kinfo == OASIS_RecvOut .OR. kinfo == OASIS_FromRestOut 
    421421                
    422                IF( ln_ctl )   WRITE(numout,*) "llaction, kinfo, kstep, ivarid: " , llaction, kinfo, kstep, srcv(kid)%nid(jc,jm) 
     422               IF ( sn_cfctl%l_oasout )   WRITE(numout,*) "llaction, kinfo, kstep, ivarid: " , llaction, kinfo, kstep, srcv(kid)%nid(jc,jm) 
    423423                
    424424               IF( llaction ) THEN 
     
    432432                  ENDIF 
    433433                   
    434                   IF( ln_ctl ) THEN         
     434                  IF ( sn_cfctl%l_oasout ) THEN         
    435435                     WRITE(numout,*) '****************' 
    436436                     WRITE(numout,*) 'oasis_get: Incoming ', srcv(kid)%clname 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/SBC/sbcblk.F90

    r12200 r12236  
    178178      ! 
    179179      !                             !** read bulk namelist 
    180       !REWIND( numnam_ref )                !* Namelist namsbc_blk in reference namelist : bulk parameters 
    181180      READ  ( numnam_ref, namsbc_blk, IOSTAT = ios, ERR = 901) 
    182181901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc_blk in reference namelist' ) 
    183182      ! 
    184       !REWIND( numnam_cfg )                !* Namelist namsbc_blk in configuration namelist : bulk parameters 
    185183      READ  ( numnam_cfg, namsbc_blk, IOSTAT = ios, ERR = 902 ) 
    186184902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namsbc_blk in configuration namelist' ) 
     
    703701         CALL lbc_lnk_multi( 'sbcblk', utau, 'U', -1., vtau, 'V', -1. ) 
    704702 
    705          IF(ln_ctl) THEN 
     703         IF(sn_cfctl%l_prtctl) THEN 
    706704            CALL prt_ctl( tab2d_1=wndm  , clinfo1=' blk_oce_1: wndm   : ') 
    707705            CALL prt_ctl( tab2d_1=utau  , clinfo1=' blk_oce_1: utau   : ', mask1=umask,   & 
     
    718716      ENDIF 
    719717 
    720       IF(ln_ctl) THEN 
     718      IF(sn_cfctl%l_prtctl) THEN 
    721719         CALL prt_ctl( tab2d_1=pevp  , clinfo1=' blk_oce_1: pevp   : ' ) 
    722720         CALL prt_ctl( tab2d_1=psen  , clinfo1=' blk_oce_1: psen   : ' ) 
     
    762760      ! local scalars ( place there for vector optimisation purposes) 
    763761 
     762 
    764763      ztskk(:,:) = ptsk(:,:) + rt0  ! => ptsk in Kelvin rather than Celsius 
    765764       
     
    782781      ENDDO 
    783782 
    784       IF(ln_ctl) THEN 
     783      IF(sn_cfctl%l_prtctl) THEN 
    785784         CALL prt_ctl( tab2d_1=zqla  , clinfo1=' blk_oce_2: zqla   : ' ) 
    786785         CALL prt_ctl( tab2d_1=zqlw  , clinfo1=' blk_oce_2: zqlw   : ', tab2d_2=qsr, clinfo2=' qsr : ' ) 
     
    826825      ENDIF 
    827826      ! 
    828       IF(ln_ctl) THEN 
     827      IF(sn_cfctl%l_prtctl) THEN 
    829828         CALL prt_ctl(tab2d_1=zqlw , clinfo1=' blk_oce_2: zqlw  : ') 
    830829         CALL prt_ctl(tab2d_1=zqla , clinfo1=' blk_oce_2: zqla  : ', tab2d_2=qsr  , clinfo2=' qsr   : ') 
     
    927926         CALL lbc_lnk_multi( 'sbcblk', putaui, 'U', -1., pvtaui, 'V', -1. ) 
    928927         ! 
    929          IF(ln_ctl)   CALL prt_ctl( tab2d_1=putaui  , clinfo1=' blk_ice: putaui : '   & 
    930             &                     , tab2d_2=pvtaui  , clinfo2='          pvtaui : ' ) 
     928         IF(sn_cfctl%l_prtctl)  CALL prt_ctl( tab2d_1=putaui  , clinfo1=' blk_ice: putaui : '   & 
     929            &                               , tab2d_2=pvtaui  , clinfo2='          pvtaui : ' ) 
    931930      ELSE 
    932931         zztmp1 = 11637800.0_wp 
     
    943942      ENDIF 
    944943      ! 
    945       IF(ln_ctl)  CALL prt_ctl(tab2d_1=wndm_ice  , clinfo1=' blk_ice: wndm_ice : ') 
     944      IF(sn_cfctl%l_prtctl)  CALL prt_ctl(tab2d_1=wndm_ice  , clinfo1=' blk_ice: wndm_ice : ') 
    946945      ! 
    947946   END SUBROUTINE blk_ice_1 
     
    11291128      ENDIF 
    11301129      ! 
    1131       IF(ln_ctl) THEN 
     1130      IF(sn_cfctl%l_prtctl) THEN 
    11321131         CALL prt_ctl(tab3d_1=qla_ice , clinfo1=' blk_ice: qla_ice  : ', tab3d_2=z_qsb   , clinfo2=' z_qsb    : ', kdim=jpl) 
    11331132         CALL prt_ctl(tab3d_1=z_qlw   , clinfo1=' blk_ice: z_qlw    : ', tab3d_2=dqla_ice, clinfo2=' dqla_ice : ', kdim=jpl) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/SBC/sbcmod.F90

    r12193 r12236  
    574574      CALL iom_put( "vtau", vtau )   ! j-wind stress 
    575575      ! 
    576       IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
     576      IF(sn_cfctl%l_prtctl) THEN     ! print mean trends (used for debugging) 
    577577         CALL prt_ctl(tab2d_1=fr_i             , clinfo1=' fr_i     - : ', mask1=tmask ) 
    578578         CALL prt_ctl(tab2d_1=(emp-rnf)        , clinfo1=' emp-rnf  - : ', mask1=tmask ) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/TRA/eosbn2.F90

    r12150 r12236  
    296296      END SELECT 
    297297      ! 
    298       IF(ln_ctl)   CALL prt_ctl( tab3d_1=prd, clinfo1=' eos-insitu  : ', kdim=jpk ) 
     298      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=prd, clinfo1=' eos-insitu  : ', kdim=jpk ) 
    299299      ! 
    300300      IF( ln_timing )   CALL timing_stop('eos-insitu') 
     
    463463      END SELECT 
    464464      ! 
    465       IF(ln_ctl)   CALL prt_ctl( tab3d_1=prd, clinfo1=' eos-pot: ', tab3d_2=prhop, clinfo2=' pot : ', kdim=jpk ) 
     465      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=prd, clinfo1=' eos-pot: ', tab3d_2=prhop, clinfo2=' pot : ', kdim=jpk ) 
    466466      ! 
    467467      IF( ln_timing )   CALL timing_stop('eos-pot') 
     
    558558      END SELECT 
    559559      ! 
    560       IF(ln_ctl)   CALL prt_ctl( tab2d_1=prd, clinfo1=' eos2d: ' ) 
     560      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab2d_1=prd, clinfo1=' eos2d: ' ) 
    561561      ! 
    562562      IF( ln_timing )   CALL timing_stop('eos2d') 
     
    671671      END SELECT 
    672672      ! 
    673       IF(ln_ctl)   CALL prt_ctl( tab3d_1=pab(:,:,:,jp_tem), clinfo1=' rab_3d_t: ', & 
    674          &                       tab3d_2=pab(:,:,:,jp_sal), clinfo2=' rab_3d_s : ', kdim=jpk ) 
     673      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pab(:,:,:,jp_tem), clinfo1=' rab_3d_t: ', & 
     674         &                                  tab3d_2=pab(:,:,:,jp_sal), clinfo2=' rab_3d_s : ', kdim=jpk ) 
    675675      ! 
    676676      IF( ln_timing )   CALL timing_stop('rab_3d') 
     
    786786      END SELECT 
    787787      ! 
    788       IF(ln_ctl)   CALL prt_ctl( tab2d_1=pab(:,:,jp_tem), clinfo1=' rab_2d_t: ', & 
    789          &                       tab2d_2=pab(:,:,jp_sal), clinfo2=' rab_2d_s : ' ) 
     788      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab2d_1=pab(:,:,jp_tem), clinfo1=' rab_2d_t: ', & 
     789         &                                  tab2d_2=pab(:,:,jp_sal), clinfo2=' rab_2d_s : ' ) 
    790790      ! 
    791791      IF( ln_timing )   CALL timing_stop('rab_2d') 
     
    932932      END DO 
    933933      ! 
    934       IF(ln_ctl)   CALL prt_ctl( tab3d_1=pn2, clinfo1=' bn2  : ', kdim=jpk ) 
     934      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pn2, clinfo1=' bn2  : ', kdim=jpk ) 
    935935      ! 
    936936      IF( ln_timing )   CALL timing_stop('bn2') 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/TRA/traadv.F90

    r12193 r12236  
    171171      ENDIF 
    172172      !                                              ! print mean trends (used for debugging) 
    173       IF(ln_ctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' adv  - Ta: ', mask1=tmask,               & 
    174          &                       tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
     173      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' adv  - Ta: ', mask1=tmask,               & 
     174         &                                  tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
    175175      ! 
    176176      IF( ln_timing )   CALL timing_stop( 'tra_adv' ) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/TRA/traatf.F90

    r12156 r12236  
    178178      ! 
    179179      !                        ! control print 
    180       IF(ln_ctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Kmm), clinfo1=' nxt  - Tn: ', mask1=tmask,   & 
    181          &                       tab3d_2=pts(:,:,:,jp_sal,Kmm), clinfo2=       ' Sn: ', mask2=tmask ) 
     180      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Kmm), clinfo1=' nxt  - Tn: ', mask1=tmask,   & 
     181         &                                  tab3d_2=pts(:,:,:,jp_sal,Kmm), clinfo2=       ' Sn: ', mask2=tmask ) 
    182182      ! 
    183183      IF( ln_timing )   CALL timing_stop('tra_atf') 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/TRA/trabbc.F90

    r12193 r12236  
    103103      ! 
    104104      CALL iom_put ( "hfgeou" , rau0_rcp * qgh_trd0(:,:) ) 
    105       IF(ln_ctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' bbc  - Ta: ', mask1=tmask, clinfo3='tra-ta' ) 
     105      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' bbc  - Ta: ', mask1=tmask, clinfo3='tra-ta' ) 
    106106      ! 
    107107      IF( ln_timing )   CALL timing_stop('tra_bbc') 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/TRA/trabbl.F90

    r11960 r12236  
    121121         ! 
    122122         CALL tra_bbl_dif( pts(:,:,:,:,Kbb), pts(:,:,:,:,Krhs), jpts, Kmm ) 
    123          IF( ln_ctl )  & 
     123         IF( sn_cfctl%l_prtctl )  & 
    124124         CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' bbl_ldf  - Ta: ', mask1=tmask, & 
    125125            &          tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2=           ' Sa: ', mask2=tmask, clinfo3='tra' ) 
     
    134134         ! 
    135135         CALL tra_bbl_adv( pts(:,:,:,:,Kbb), pts(:,:,:,:,Krhs), jpts, Kmm ) 
    136          IF(ln_ctl)   & 
     136         IF(sn_cfctl%l_prtctl)   & 
    137137         CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' bbl_adv  - Ta: ', mask1=tmask,   & 
    138138            &          tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2=           ' Sa: ', mask2=tmask, clinfo3='tra' ) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/TRA/tradmp.F90

    r11960 r12236  
    159159      ENDIF 
    160160      !                           ! Control print 
    161       IF(ln_ctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' dmp  - Ta: ', mask1=tmask,   & 
    162          &                       tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
     161      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' dmp  - Ta: ', mask1=tmask,   & 
     162         &                                  tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
    163163      ! 
    164164      IF( ln_timing )   CALL timing_stop('tra_dmp') 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/TRA/traldf.F90

    r11949 r12236  
    8787      ENDIF 
    8888      !                                        !* print mean trends (used for debugging) 
    89       IF(ln_ctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' ldf  - Ta: ', mask1=tmask,               & 
    90          &                       tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
     89      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' ldf  - Ta: ', mask1=tmask,               & 
     90         &                                  tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
    9191      ! 
    9292      IF( ln_timing )   CALL timing_stop('tra_ldf') 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/TRA/traqsr.F90

    r11960 r12236  
    302302      ENDIF 
    303303      !                       ! print mean trends (used for debugging) 
    304       IF(ln_ctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' qsr  - Ta: ', mask1=tmask, clinfo3='tra-ta' ) 
     304      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' qsr  - Ta: ', mask1=tmask, clinfo3='tra-ta' ) 
    305305      ! 
    306306      IF( ln_timing )   CALL timing_stop('tra_qsr') 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/TRA/trasbc.F90

    r12150 r12236  
    217217      ENDIF 
    218218      ! 
    219       IF(ln_ctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' sbc  - Ta: ', mask1=tmask,   & 
    220          &                       tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
     219      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' sbc  - Ta: ', mask1=tmask,   & 
     220         &                                  tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
    221221      ! 
    222222      IF( ln_timing )   CALL timing_stop('tra_sbc') 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/TRA/trazdf.F90

    r11949 r12236  
    101101      ENDIF 
    102102      !                                          ! print mean trends (used for debugging) 
    103       IF(ln_ctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Kaa), clinfo1=' zdf  - Ta: ', mask1=tmask,               & 
    104          &                       tab3d_2=pts(:,:,:,jp_sal,Kaa), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
     103      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Kaa), clinfo1=' zdf  - Ta: ', mask1=tmask,               & 
     104         &                                  tab3d_2=pts(:,:,:,jp_sal,Kaa), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
    105105      ! 
    106106      IF( ln_timing )   CALL timing_stop('tra_zdf') 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/TRD/trdmxl.F90

    r11960 r12236  
    372372         hmxlbn(:,:) = hmxl(:,:) 
    373373 
    374          IF( ln_ctl ) THEN 
     374         IF( sn_cfctl%l_prtctl ) THEN 
    375375            WRITE(numout,*) '             we reach kt == nit000 + 1 = ', nit000+1 
    376376            CALL prt_ctl(tab2d_1=tmlbb   , clinfo1=' tmlbb   -   : ', mask1=tmask) 
     
    381381      END IF 
    382382 
    383       IF( ( ln_rstart ) .AND. ( kt == nit000 ) .AND. ( ln_ctl ) ) THEN 
     383      IF( ( ln_rstart ) .AND. ( kt == nit000 ) .AND. sn_cfctl%l_prtctl ) THEN 
    384384         IF( ln_trdmxl_instant ) THEN 
    385385            WRITE(numout,*) '             restart from kt == nit000 = ', nit000 
     
    549549         hmxlbn         (:,:)   = hmxl    (:,:) 
    550550          
    551          IF( ln_ctl ) THEN 
     551         IF( sn_cfctl%l_prtctl ) THEN 
    552552            IF( ln_trdmxl_instant ) THEN 
    553553               CALL prt_ctl(tab2d_1=tmlbb   , clinfo1=' tmlbb   -   : ', mask1=tmask) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/ZDF/zdfddm.F90

    r11949 r12236  
    164164      !                                                   ! =============== 
    165165      ! 
    166       IF(ln_ctl) THEN 
     166      IF(sn_cfctl%l_prtctl) THEN 
    167167         CALL prt_ctl(tab3d_1=avt , clinfo1=' ddm  - t: ', tab3d_2=avs , clinfo2=' s: ', kdim=jpk) 
    168168      ENDIF 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/ZDF/zdfdrg.F90

    r11960 r12236  
    140140      ENDIF 
    141141      ! 
    142       IF(ln_ctl)   CALL prt_ctl( tab2d_1=pCdU, clinfo1=' Cd*U ') 
     142      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab2d_1=pCdU, clinfo1=' Cd*U ') 
    143143      ! 
    144144   END SUBROUTINE zdf_drg 
     
    215215      ENDIF 
    216216      !                                          ! print mean trends (used for debugging) 
    217       IF(ln_ctl)   CALL prt_ctl( tab3d_1=pua, clinfo1=' bfr  - Ua: ', mask1=umask,               & 
    218          &                       tab3d_2=pva, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
     217      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pua, clinfo1=' bfr  - Ua: ', mask1=umask,               & 
     218         &                                  tab3d_2=pva, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
    219219      ! 
    220220   END SUBROUTINE zdf_drg_exp 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/ZDF/zdfgls.F90

    r11960 r12236  
    825825      p_avt(:,:,1) = 0._wp 
    826826      ! 
    827       IF(ln_ctl) THEN 
     827      IF(sn_cfctl%l_prtctl) THEN 
    828828         CALL prt_ctl( tab3d_1=en   , clinfo1=' gls  - e: ', tab3d_2=p_avt, clinfo2=' t: ', kdim=jpk) 
    829829         CALL prt_ctl( tab3d_1=p_avm, clinfo1=' gls  - m: ', kdim=jpk ) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/ZDF/zdfiwm.F90

    r12182 r12236  
    384384      CALL iom_put( "emix_iwm", zemx_iwm ) 
    385385       
    386       IF(ln_ctl)   CALL prt_ctl(tab3d_1=zav_wave , clinfo1=' iwm - av_wave: ', tab3d_2=avt, clinfo2=' avt: ', kdim=jpk) 
     386      IF(sn_cfctl%l_prtctl)   CALL prt_ctl(tab3d_1=zav_wave , clinfo1=' iwm - av_wave: ', tab3d_2=avt, clinfo2=' avt: ', kdim=jpk) 
    387387      ! 
    388388   END SUBROUTINE zdf_iwm 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/ZDF/zdfmxl.F90

    r12150 r12236  
    139139      ENDIF 
    140140      ! 
    141       IF(ln_ctl)   CALL prt_ctl( tab2d_1=REAL(nmln,wp), clinfo1=' nmln : ', tab2d_2=hmlp, clinfo2=' hmlp : ' ) 
     141      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab2d_1=REAL(nmln,wp), clinfo1=' nmln : ', tab2d_2=hmlp, clinfo2=' hmlp : ' ) 
    142142      ! 
    143143   END SUBROUTINE zdf_mxl 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/ZDF/zdfosm.F90

    r11960 r12236  
    16641664      ENDIF 
    16651665 
    1666       IF(ln_ctl) THEN 
     1666      IF(sn_cfctl%l_prtctl) THEN 
    16671667         CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' osm  - Ta: ', mask1=tmask,   & 
    16681668         &             tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/ZDF/zdftke.F90

    r11960 r12236  
    622622      ENDIF 
    623623      ! 
    624       IF(ln_ctl) THEN 
     624      IF(sn_cfctl%l_prtctl) THEN 
    625625         CALL prt_ctl( tab3d_1=en   , clinfo1=' tke  - e: ', tab3d_2=p_avt, clinfo2=' t: ', kdim=jpk) 
    626626         CALL prt_ctl( tab3d_1=p_avm, clinfo1=' tke  - m: ', kdim=jpk ) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/nemogcm.F90

    r12205 r12236  
    267267      INTEGER ::   ios, ilocal_comm   ! local integers 
    268268      !! 
    269       NAMELIST/namctl/ ln_ctl   , sn_cfctl, nn_print, nn_ictls, nn_ictle,   & 
     269      NAMELIST/namctl/ sn_cfctl,  nn_print, nn_ictls, nn_ictle,             & 
    270270         &             nn_isplt , nn_jsplt, nn_jctls, nn_jctle,             & 
    271271         &             ln_timing, ln_diacfl 
     
    318318      ! 
    319319      !                             !--------------------! 
    320       !                             ! Open listing units !  -> need ln_ctl from namctl to define lwp 
     320      !                             ! Open listing units !  -> need sn_cfctl from namctl to define lwp 
    321321      !                             !--------------------! 
    322322      ! 
     
    326326902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namctl in configuration namelist' ) 
    327327      ! 
    328       lwp = (narea == 1) .OR. ln_ctl    ! control of all listing output print 
     328      ! finalize the definition of namctl variables 
     329      IF( sn_cfctl%l_allon ) THEN 
     330         ! Turn on all options. 
     331         CALL nemo_set_cfctl( sn_cfctl, .TRUE., .TRUE. ) 
     332         ! Ensure all processors are active 
     333         sn_cfctl%procmin = 0 ; sn_cfctl%procmax = 1000000 ; sn_cfctl%procincr = 1 
     334      ELSEIF( sn_cfctl%l_config ) THEN 
     335         ! Activate finer control of report outputs 
     336         ! optionally switch off output from selected areas (note this only 
     337         ! applies to output which does not involve global communications) 
     338         IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
     339           & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
     340           &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
     341      ELSE 
     342         ! turn off all options. 
     343         CALL nemo_set_cfctl( sn_cfctl, .FALSE., .TRUE. ) 
     344      ENDIF 
     345      ! 
     346      lwp = (narea == 1) .OR. sn_cfctl%l_oceout    ! control of all listing output print 
    329347      ! 
    330348      IF(lwp) THEN                      ! open listing units 
     
    358376      ENDIF 
    359377      ! 
    360       ! finalize the definition of namctl variables 
    361       IF( sn_cfctl%l_config ) THEN 
    362          ! Activate finer control of report outputs 
    363          ! optionally switch off output from selected areas (note this only 
    364          ! applies to output which does not involve global communications) 
    365          IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
    366            & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
    367            &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
    368       ELSE 
    369          ! Use ln_ctl to turn on or off all options. 
    370          CALL nemo_set_cfctl( sn_cfctl, ln_ctl, .TRUE. ) 
    371       ENDIF 
    372       ! 
    373378      IF(lwm) WRITE( numond, namctl ) 
    374379      ! 
     
    417422                           CALL     dom_init( Nbb, Nnn, Naa, "OPA") ! Domain 
    418423      IF( ln_crs       )   CALL     crs_init(      Nnn )       ! coarsened grid: domain initialization  
    419       IF( ln_ctl       )   CALL prt_ctl_init        ! Print control 
     424      IF( sn_cfctl%l_prtctl )   & 
     425         &                 CALL prt_ctl_init        ! Print control 
    420426       
    421       CALL diurnal_sst_bulk_init                ! diurnal sst 
     427                           CALL diurnal_sst_bulk_init       ! diurnal sst 
    422428      IF( ln_diurnal   )   CALL diurnal_sst_coolskin_init   ! cool skin    
    423429      !                             
    424       IF( ln_diurnal_only ) THEN                   ! diurnal only: a subset of the initialisation routines 
    425          CALL  istate_init( Nbb, Nnn, Naa )           ! ocean initial state (Dynamics and tracers) 
    426          CALL     sbc_init( Nbb, Nnn, Naa )           ! Forcings : surface module 
    427          CALL tra_qsr_init                            ! penetrative solar radiation qsr 
    428          IF( ln_diaobs ) THEN                         ! Observation & model comparison 
    429             CALL dia_obs_init( Nnn )                     ! Initialize observational data 
    430             CALL dia_obs( nit000 - 1, Nnn )              ! Observation operator for restart 
     430      IF( ln_diurnal_only ) THEN                    ! diurnal only: a subset of the initialisation routines 
     431         CALL  istate_init( Nbb, Nnn, Naa )         ! ocean initial state (Dynamics and tracers) 
     432         CALL     sbc_init( Nbb, Nnn, Naa )         ! Forcings : surface module 
     433         CALL tra_qsr_init                          ! penetrative solar radiation qsr 
     434         IF( ln_diaobs ) THEN                       ! Observation & model comparison 
     435            CALL dia_obs_init( Nnn )                ! Initialize observational data 
     436            CALL dia_obs( nit000 - 1, Nnn )         ! Observation operator for restart 
    431437         ENDIF      
    432438         IF( lk_asminc )   CALL asm_inc_init( Nbb, Nnn, Nrhs )   ! Assimilation increments 
     
    521527         WRITE(numout,*) '~~~~~~~~' 
    522528         WRITE(numout,*) '   Namelist namctl' 
    523          WRITE(numout,*) '      run control (for debugging)     ln_ctl     = ', ln_ctl 
     529         WRITE(numout,*) '                              sn_cfctl%l_glochk  = ', sn_cfctl%l_glochk 
     530         WRITE(numout,*) '                              sn_cfctl%l_allon   = ', sn_cfctl%l_allon 
    524531         WRITE(numout,*) '       finer control over o/p sn_cfctl%l_config  = ', sn_cfctl%l_config 
    525532         WRITE(numout,*) '                              sn_cfctl%l_runstat = ', sn_cfctl%l_runstat 
     
    527534         WRITE(numout,*) '                              sn_cfctl%l_oceout  = ', sn_cfctl%l_oceout 
    528535         WRITE(numout,*) '                              sn_cfctl%l_layout  = ', sn_cfctl%l_layout 
    529          WRITE(numout,*) '                              sn_cfctl%l_mppout  = ', sn_cfctl%l_mppout 
    530          WRITE(numout,*) '                              sn_cfctl%l_mpptop  = ', sn_cfctl%l_mpptop 
     536         WRITE(numout,*) '                              sn_cfctl%l_prtctl  = ', sn_cfctl%l_prtctl 
     537         WRITE(numout,*) '                              sn_cfctl%l_prttrc  = ', sn_cfctl%l_prttrc 
     538         WRITE(numout,*) '                              sn_cfctl%l_oasout  = ', sn_cfctl%l_oasout 
    531539         WRITE(numout,*) '                              sn_cfctl%procmin   = ', sn_cfctl%procmin   
    532540         WRITE(numout,*) '                              sn_cfctl%procmax   = ', sn_cfctl%procmax   
     
    566574      !                             ! Parameter control 
    567575      ! 
    568       IF( ln_ctl ) THEN                 ! sub-domain area indices for the control prints 
     576      IF( sn_cfctl%l_prtctl .OR. sn_cfctl%l_prttrc ) THEN              ! sub-domain area indices for the control prints 
    569577         IF( lk_mpp .AND. jpnij > 1 ) THEN 
    570578            isplt = jpni   ;   jsplt = jpnj   ;   ijsplt = jpni*jpnj   ! the domain is forced to the real split domain 
     
    692700      sn_cfctl%l_oceout  = setto 
    693701      sn_cfctl%l_layout  = setto 
    694       sn_cfctl%l_mppout  = setto 
    695       sn_cfctl%l_mpptop  = setto 
     702      sn_cfctl%l_prtctl  = setto 
     703      sn_cfctl%l_prttrc  = setto 
     704      sn_cfctl%l_oasout  = setto 
    696705   END SUBROUTINE nemo_set_cfctl 
    697706 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/stpctl.F90

    r11949 r12236  
    7373      ! 
    7474      ll_wrtstp  = ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 
    75       ll_colruns = ll_wrtstp .AND. ( ln_ctl .OR. sn_cfctl%l_runstat ) 
     75      ll_colruns = ll_wrtstp .AND. ( sn_cfctl%l_runstat ) 
    7676      ll_wrtruns = ll_colruns .AND. lwm 
    7777      IF( kt == nit000 .AND. lwp ) THEN 
     
    8383         !                                ! open run.stat file(s) at start whatever 
    8484         !                                ! the value of sn_cfctl%ptimincr 
    85          IF( lwm .AND. ( ln_ctl .OR. sn_cfctl%l_runstat ) ) THEN 
     85         IF( lwm .AND. ( sn_cfctl%l_runstat ) ) THEN 
    8686            CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    8787            clname = 'run.stat.nc' 
     
    148148      END IF 
    149149      !                                   !==  error handling  ==! 
    150       IF( ( ln_ctl .OR. lsomeoce ) .AND. (   &             ! have use mpp_max (because ln_ctl=.T.) or contains some ocean points 
     150      IF( ( sn_cfctl%l_glochk .OR. lsomeoce ) .AND. (   &  ! domain contains some ocean points, check for sensible ranges 
    151151         &  zmax(1) >   20._wp .OR.   &                    ! too large sea surface height ( > 20 m ) 
    152152         &  zmax(2) >   10._wp .OR.   &                    ! too large velocity ( > 10 m/s) 
     
    155155         &  zmax(4) <    0._wp .OR.   &                    ! too large sea surface salinity (keep this line for sea-ice) 
    156156         &  ISNAN( zmax(1) + zmax(2) + zmax(3) ) ) ) THEN   ! NaN encounter in the tests 
    157          IF( lk_mpp .AND. ln_ctl ) THEN 
     157         IF( lk_mpp .AND. sn_cfctl%l_glochk ) THEN 
     158            ! have use mpp_max (because sn_cfctl%l_glochk=.T. and distributed) 
    158159            CALL mpp_maxloc( 'stpctl', ABS(ssh(:,:,Kmm))        , ssmask(:,:)  , zzz, ih  ) 
    159160            CALL mpp_maxloc( 'stpctl', ABS(uu(:,:,:,Kmm))          , umask (:,:,:), zzz, iu  ) 
     
    161162            CALL mpp_maxloc( 'stpctl', ts(:,:,:,jp_sal,Kmm), tmask (:,:,:), zzz, is2 ) 
    162163         ELSE 
     164            ! find local min and max locations 
    163165            ih(:)  = MAXLOC( ABS( ssh(:,:,Kmm)   )                              ) + (/ nimpp - 1, njmpp - 1    /) 
    164166            iu(:)  = MAXLOC( ABS( uu  (:,:,:,Kmm) )                              ) + (/ nimpp - 1, njmpp - 1, 0 /) 
     
    176178         CALL dia_wri_state( Kmm, 'output.abort' )     ! create an output.abort file 
    177179          
    178          IF( .NOT. ln_ctl ) THEN 
     180         IF( .NOT. sn_cfctl%l_glochk ) THEN 
    179181            WRITE(ctmp8,*) 'E R R O R message from sub-domain: ', narea 
    180182            CALL ctl_stop( 'STOP', ctmp1, ' ', ctmp8, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ctmp6 ) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OFF/dtadyn.F90

    r11960 r12236  
    179179      CALL eos( ts(:,:,:,:,Kmm), rhd, rhop, gdept_0(:,:,:) ) ! In any case, we need rhop 
    180180      ! 
    181       IF(ln_ctl) THEN                  ! print control 
     181      IF(sn_cfctl%l_prtctl) THEN                 ! print control 
    182182         CALL prt_ctl(tab3d_1=ts(:,:,:,jp_tem,Kmm), clinfo1=' tn      - : ', mask1=tmask,  kdim=jpk   ) 
    183183         CALL prt_ctl(tab3d_1=ts(:,:,:,jp_sal,Kmm), clinfo1=' sn      - : ', mask1=tmask,  kdim=jpk   ) 
     
    448448      CALL eos    ( ts(:,:,:,:,Kmm), rhd, rhop, gdept_0(:,:,:) ) ! In any case, we need rhop 
    449449 
    450       IF(ln_ctl) THEN                  ! print control 
     450      IF(sn_cfctl%l_prtctl) THEN                     ! print control 
    451451         CALL prt_ctl(tab3d_1=ts(:,:,:,jp_tem,Kmm), clinfo1=' tn      - : ', mask1=tmask,  kdim=jpk   ) 
    452452         CALL prt_ctl(tab3d_1=ts(:,:,:,jp_sal,Kmm), clinfo1=' sn      - : ', mask1=tmask,  kdim=jpk   ) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OFF/nemogcm.F90

    r11960 r12236  
    175175      INTEGER ::   ios, ilocal_comm   ! local integers 
    176176      !! 
    177       NAMELIST/namctl/ ln_ctl   , sn_cfctl, nn_print, nn_ictls, nn_ictle,   & 
     177      NAMELIST/namctl/ sn_cfctl, nn_print, nn_ictls, nn_ictle,              & 
    178178         &             nn_isplt , nn_jsplt, nn_jctls, nn_jctle,             & 
    179179         &             ln_timing, ln_diacfl 
     
    212212      ! 
    213213      !                             !--------------------! 
    214       !                             ! Open listing units !  -> need ln_ctl from namctl to define lwp 
     214      !                             ! Open listing units !  -> need sn_cfctl from namctl to define lwp 
    215215      !                             !--------------------! 
    216216      ! 
     
    220220902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namctl in configuration namelist' ) 
    221221      ! 
    222       lwp = (narea == 1) .OR. ln_ctl    ! control of all listing output print 
     222      ! finalize the definition of namctl variables 
     223      IF( sn_cfctl%l_allon ) THEN 
     224         ! Turn on all options. 
     225         CALL nemo_set_cfctl( sn_cfctl, .TRUE., .TRUE. ) 
     226         ! Ensure all processors are active 
     227         sn_cfctl%procmin = 0 ; sn_cfctl%procmax = 1000000 ; sn_cfctl%procincr = 1 
     228      ELSEIF( sn_cfctl%l_config ) THEN 
     229         ! Activate finer control of report outputs 
     230         ! optionally switch off output from selected areas (note this only 
     231         ! applies to output which does not involve global communications) 
     232         IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
     233           & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
     234           &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
     235      ELSE 
     236         ! turn off all options. 
     237         CALL nemo_set_cfctl( sn_cfctl, .FALSE., .TRUE. ) 
     238      ENDIF 
     239      ! 
     240      lwp = (narea == 1) .OR. sn_cfctl%l_oceout    ! control of all listing output print 
    223241      ! 
    224242      IF(lwp) THEN                            ! open listing units 
     
    252270      ENDIF 
    253271      ! 
    254       ! finalize the definition of namctl variables 
    255       IF( sn_cfctl%l_config ) THEN 
    256          ! Activate finer control of report outputs 
    257          ! optionally switch off output from selected areas (note this only 
    258          ! applies to output which does not involve global communications) 
    259          IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
    260            & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
    261            &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
    262       ELSE 
    263          ! Use ln_ctl to turn on or off all options. 
    264          CALL nemo_set_cfctl( sn_cfctl, ln_ctl, .TRUE. ) 
    265       ENDIF 
    266       ! 
    267272      IF(lwm) WRITE( numond, namctl ) 
    268273      ! 
     
    312317      IF( lk_c1d       )   CALL     c1d_init        ! 1D column configuration 
    313318                           CALL     dom_init( Nbb, Nnn, Naa, "OPA") ! Domain 
    314       IF( ln_ctl       )   CALL prt_ctl_init        ! Print control 
     319      IF( sn_cfctl%l_prtctl )   & 
     320         &                 CALL prt_ctl_init        ! Print control 
    315321 
    316322                           CALL  istate_init( Nnn, Naa )    ! ocean initial state (Dynamics and tracers) 
     
    351357      !! ** Purpose :   control print setting 
    352358      !! 
    353       !! ** Method  : - print namctl information and check some consistencies 
     359      !! ** Method  : - print namctl and namcfg information and check some consistencies 
    354360      !!---------------------------------------------------------------------- 
    355361      ! 
     
    359365         WRITE(numout,*) '~~~~~~~~' 
    360366         WRITE(numout,*) '   Namelist namctl' 
    361          WRITE(numout,*) '      run control (for debugging)     ln_ctl     = ', ln_ctl 
     367         WRITE(numout,*) '                              sn_cfctl%l_glochk  = ', sn_cfctl%l_glochk 
     368         WRITE(numout,*) '                              sn_cfctl%l_allon   = ', sn_cfctl%l_allon 
    362369         WRITE(numout,*) '       finer control over o/p sn_cfctl%l_config  = ', sn_cfctl%l_config 
    363370         WRITE(numout,*) '                              sn_cfctl%l_runstat = ', sn_cfctl%l_runstat 
     
    365372         WRITE(numout,*) '                              sn_cfctl%l_oceout  = ', sn_cfctl%l_oceout 
    366373         WRITE(numout,*) '                              sn_cfctl%l_layout  = ', sn_cfctl%l_layout 
    367          WRITE(numout,*) '                              sn_cfctl%l_mppout  = ', sn_cfctl%l_mppout 
    368          WRITE(numout,*) '                              sn_cfctl%l_mpptop  = ', sn_cfctl%l_mpptop 
     374         WRITE(numout,*) '                              sn_cfctl%l_prtctl  = ', sn_cfctl%l_prtctl 
     375         WRITE(numout,*) '                              sn_cfctl%l_prttrc  = ', sn_cfctl%l_prttrc 
     376         WRITE(numout,*) '                              sn_cfctl%l_oasout  = ', sn_cfctl%l_oasout 
    369377         WRITE(numout,*) '                              sn_cfctl%procmin   = ', sn_cfctl%procmin   
    370378         WRITE(numout,*) '                              sn_cfctl%procmax   = ', sn_cfctl%procmax   
     
    404412      !                             ! Parameter control 
    405413      ! 
    406       IF( ln_ctl ) THEN                 ! sub-domain area indices for the control prints 
     414      IF( sn_cfctl%l_prtctl .OR. sn_cfctl%l_prttrc ) THEN              ! sub-domain area indices for the control prints 
    407415         IF( lk_mpp .AND. jpnij > 1 ) THEN 
    408416            isplt = jpni   ;   jsplt = jpnj   ;   ijsplt = jpni*jpnj   ! the domain is forced to the real split domain 
     
    516524      sn_cfctl%l_oceout  = setto 
    517525      sn_cfctl%l_layout  = setto 
    518       sn_cfctl%l_mppout  = setto 
    519       sn_cfctl%l_mpptop  = setto 
     526      sn_cfctl%l_prtctl  = setto 
     527      sn_cfctl%l_prttrc  = setto 
     528      sn_cfctl%l_oasout  = setto 
    520529   END SUBROUTINE nemo_set_cfctl 
    521530 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/SAO/nemogcm.F90

    r11960 r12236  
    9191      INTEGER ::   ios, ilocal_comm   ! local integer 
    9292      ! 
    93       NAMELIST/namctl/ ln_ctl   , sn_cfctl, nn_print, nn_ictls, nn_ictle,   & 
     93      NAMELIST/namctl/ sn_cfctl,  nn_print, nn_ictls, nn_ictle,             & 
    9494         &             nn_isplt , nn_jsplt, nn_jctls, nn_jctle,             & 
    9595         &             ln_timing, ln_diacfl 
     
    142142      ! 
    143143      !                             !--------------------! 
    144       !                             ! Open listing units !  -> need ln_ctl from namctl to define lwp 
     144      !                             ! Open listing units !  -> need sn_cfctl from namctl to define lwp 
    145145      !                             !--------------------! 
    146146      ! 
     
    150150902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namctl in configuration namelist' ) 
    151151      ! 
    152       lwp = (narea == 1) .OR. ln_ctl    ! control of all listing output print 
     152      ! finalize the definition of namctl variables 
     153      IF( sn_cfctl%l_allon ) THEN 
     154         ! Turn on all options. 
     155         CALL nemo_set_cfctl( sn_cfctl, .TRUE., .TRUE. ) 
     156         ! Ensure all processors are active 
     157         sn_cfctl%procmin = 0 ; sn_cfctl%procmax = 1000000 ; sn_cfctl%procincr = 1 
     158      ELSEIF( sn_cfctl%l_config ) THEN 
     159         ! Activate finer control of report outputs 
     160         ! optionally switch off output from selected areas (note this only 
     161         ! applies to output which does not involve global communications) 
     162         IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
     163           & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
     164           &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
     165      ELSE 
     166         ! turn off all options. 
     167         CALL nemo_set_cfctl( sn_cfctl, .FALSE., .TRUE. ) 
     168      ENDIF 
     169      ! 
     170      lwp = (narea == 1) .OR. sn_cfctl%l_oceout    ! control of all listing output print 
    153171      ! 
    154172      IF(lwp) THEN                      ! open listing units 
     
    182200      ENDIF 
    183201      ! 
    184       ! finalize the definition of namctl variables 
    185       IF( sn_cfctl%l_config ) THEN 
    186          ! Activate finer control of report outputs 
    187          ! optionally switch off output from selected areas (note this only 
    188          ! applies to output which does not involve global communications) 
    189          IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
    190            & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
    191            &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
    192       ELSE 
    193          ! Use ln_ctl to turn on or off all options. 
    194          CALL nemo_set_cfctl( sn_cfctl, ln_ctl, .TRUE. ) 
    195       ENDIF 
    196       ! 
    197202      IF(lwm) WRITE( numond, namctl ) 
    198203      ! 
     
    237242 
    238243 
    239       IF( ln_ctl       )   CALL prt_ctl_init    ! Print control 
    240  
    241                            CALL istate_init     ! ocean initial state (Dynamics and tracers) 
     244      IF( sn_cfctl%l_prtctl )   & 
     245         &                 CALL prt_ctl_init       ! Print control 
     246 
     247                           CALL istate_init        ! ocean initial state (Dynamics and tracers) 
    242248   END SUBROUTINE nemo_init 
    243249 
     
    249255      !! ** Purpose :   control print setting 
    250256      !! 
    251       !! ** Method  : - print namctl information and check some consistencies 
     257      !! ** Method  : - print namctl and namcfg information and check some consistencies 
    252258      !!---------------------------------------------------------------------- 
    253259      ! 
     
    257263         WRITE(numout,*) '~~~~~~~~' 
    258264         WRITE(numout,*) '   Namelist namctl' 
    259          WRITE(numout,*) '      run control (for debugging)     ln_ctl     = ', ln_ctl 
     265         WRITE(numout,*) '                              sn_cfctl%l_glochk  = ', sn_cfctl%l_glochk 
     266         WRITE(numout,*) '                              sn_cfctl%l_allon   = ', sn_cfctl%l_allon 
    260267         WRITE(numout,*) '       finer control over o/p sn_cfctl%l_config  = ', sn_cfctl%l_config 
    261268         WRITE(numout,*) '                              sn_cfctl%l_runstat = ', sn_cfctl%l_runstat 
     
    263270         WRITE(numout,*) '                              sn_cfctl%l_oceout  = ', sn_cfctl%l_oceout 
    264271         WRITE(numout,*) '                              sn_cfctl%l_layout  = ', sn_cfctl%l_layout 
    265          WRITE(numout,*) '                              sn_cfctl%l_mppout  = ', sn_cfctl%l_mppout 
    266          WRITE(numout,*) '                              sn_cfctl%l_mpptop  = ', sn_cfctl%l_mpptop 
     272         WRITE(numout,*) '                              sn_cfctl%l_prtctl  = ', sn_cfctl%l_prtctl 
     273         WRITE(numout,*) '                              sn_cfctl%l_prttrc  = ', sn_cfctl%l_prttrc 
     274         WRITE(numout,*) '                              sn_cfctl%l_oasout  = ', sn_cfctl%l_oasout 
    267275         WRITE(numout,*) '                              sn_cfctl%procmin   = ', sn_cfctl%procmin   
    268276         WRITE(numout,*) '                              sn_cfctl%procmax   = ', sn_cfctl%procmax   
     
    302310      !                             ! Parameter control 
    303311      ! 
    304       IF( ln_ctl ) THEN                 ! sub-domain area indices for the control prints 
     312      IF( sn_cfctl%l_prtctl .OR. sn_cfctl%l_prttrc ) THEN              ! sub-domain area indices for the control prints 
    305313         IF( lk_mpp .AND. jpnij > 1 ) THEN 
    306314            isplt = jpni   ;   jsplt = jpnj   ;   ijsplt = jpni*jpnj   ! the domain is forced to the real split domain 
     
    418426      sn_cfctl%l_oceout  = setto 
    419427      sn_cfctl%l_layout  = setto 
    420       sn_cfctl%l_mppout  = setto 
    421       sn_cfctl%l_mpptop  = setto 
     428      sn_cfctl%l_prtctl  = setto 
     429      sn_cfctl%l_prttrc  = setto 
     430      sn_cfctl%l_oasout  = setto 
    422431   END SUBROUTINE nemo_set_cfctl 
    423432 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/SAS/daymod.F90

    r10068 r12236  
    275275      IF( nsec_week > 7*nsecd )   nsec_week = ndt05     ! New week 
    276276 
    277       IF(ln_ctl) THEN 
     277      IF(sn_cfctl%l_prtctl) THEN 
    278278         WRITE(charout,FMT="('kt =', I4,'  d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear 
    279279         CALL prt_ctl_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/SAS/nemogcm.F90

    r11960 r12236  
    198198      INTEGER ::   ios, ilocal_comm   ! local integers 
    199199      !! 
    200       NAMELIST/namctl/ ln_ctl   , sn_cfctl, nn_print, nn_ictls, nn_ictle,   & 
     200      NAMELIST/namctl/ sn_cfctl, nn_print, nn_ictls, nn_ictle,              & 
    201201         &             nn_isplt , nn_jsplt, nn_jctls, nn_jctle,             & 
    202202         &             ln_timing, ln_diacfl 
     
    259259      ! 
    260260      !                             !--------------------! 
    261       !                             ! Open listing units !  -> need ln_ctl from namctl to define lwp 
     261      !                             ! Open listing units !  -> need sn_cfctl from namctl to define lwp 
    262262      !                             !--------------------! 
    263263      ! 
     
    267267902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namctl in configuration namelist' ) 
    268268      ! 
    269       lwp = (narea == 1) .OR. ln_ctl    ! control of all listing output print 
     269      ! finalize the definition of namctl variables 
     270      IF( sn_cfctl%l_allon ) THEN 
     271         ! Turn on all options. 
     272         CALL nemo_set_cfctl( sn_cfctl, .TRUE., .TRUE. ) 
     273         ! Ensure all processors are active 
     274         sn_cfctl%procmin = 0 ; sn_cfctl%procmax = 1000000 ; sn_cfctl%procincr = 1 
     275      ELSEIF( sn_cfctl%l_config ) THEN 
     276         ! Activate finer control of report outputs 
     277         ! optionally switch off output from selected areas (note this only 
     278         ! applies to output which does not involve global communications) 
     279         IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
     280           & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
     281           &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
     282      ELSE 
     283         ! turn off all options. 
     284         CALL nemo_set_cfctl( sn_cfctl, .FALSE., .TRUE. ) 
     285      ENDIF 
     286      ! 
     287      lwp = (narea == 1) .OR. sn_cfctl%l_oceout    ! control of all listing output print 
    270288      ! 
    271289      IF(lwp) THEN                      ! open listing units 
     
    302320         ! 
    303321      ENDIF 
    304      ! 
    305       ! finalize the definition of namctl variables 
    306       IF( sn_cfctl%l_config ) THEN 
    307          ! Activate finer control of report outputs 
    308          ! optionally switch off output from selected areas (note this only 
    309          ! applies to output which does not involve global communications) 
    310          IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
    311            & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
    312            &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
    313       ELSE 
    314          ! Use ln_ctl to turn on or off all options. 
    315          CALL nemo_set_cfctl( sn_cfctl, ln_ctl, .TRUE. ) 
    316       ENDIF 
    317322      ! 
    318323      IF(lwm) WRITE( numond, namctl ) 
     
    359364                           CALL eos_init        ! Equation of seawater 
    360365                           CALL dom_init( Nbb, Nnn, Naa, 'SAS') ! Domain 
    361       IF( ln_ctl      )    CALL prt_ctl_init    ! Print control 
     366      IF( sn_cfctl%l_prtctl )   & 
     367         &                 CALL prt_ctl_init        ! Print control 
    362368       
    363369                           CALL day_init        ! model calendar (using both namelist and restart infos) 
     
    387393      !! ** Purpose :   control print setting 
    388394      !! 
    389       !! ** Method  : - print namctl information and check some consistencies 
     395      !! ** Method  : - print namctl and namcfg information and check some consistencies 
    390396      !!---------------------------------------------------------------------- 
    391397      ! 
     
    395401         WRITE(numout,*) '~~~~~~~~' 
    396402         WRITE(numout,*) '   Namelist namctl' 
    397          WRITE(numout,*) '      run control (for debugging)     ln_ctl     = ', ln_ctl 
     403         WRITE(numout,*) '                              sn_cfctl%l_glochk  = ', sn_cfctl%l_glochk 
     404         WRITE(numout,*) '                              sn_cfctl%l_allon   = ', sn_cfctl%l_allon 
    398405         WRITE(numout,*) '       finer control over o/p sn_cfctl%l_config  = ', sn_cfctl%l_config 
    399406         WRITE(numout,*) '                              sn_cfctl%l_runstat = ', sn_cfctl%l_runstat 
     
    401408         WRITE(numout,*) '                              sn_cfctl%l_oceout  = ', sn_cfctl%l_oceout 
    402409         WRITE(numout,*) '                              sn_cfctl%l_layout  = ', sn_cfctl%l_layout 
    403          WRITE(numout,*) '                              sn_cfctl%l_mppout  = ', sn_cfctl%l_mppout 
    404          WRITE(numout,*) '                              sn_cfctl%l_mpptop  = ', sn_cfctl%l_mpptop 
     410         WRITE(numout,*) '                              sn_cfctl%l_prtctl  = ', sn_cfctl%l_prtctl 
     411         WRITE(numout,*) '                              sn_cfctl%l_prttrc  = ', sn_cfctl%l_prttrc 
     412         WRITE(numout,*) '                              sn_cfctl%l_oasout  = ', sn_cfctl%l_oasout 
    405413         WRITE(numout,*) '                              sn_cfctl%procmin   = ', sn_cfctl%procmin   
    406414         WRITE(numout,*) '                              sn_cfctl%procmax   = ', sn_cfctl%procmax   
     
    440448      !                             ! Parameter control 
    441449      ! 
    442       IF( ln_ctl ) THEN                 ! sub-domain area indices for the control prints 
     450      IF( sn_cfctl%l_prtctl .OR. sn_cfctl%l_prttrc ) THEN              ! sub-domain area indices for the control prints 
    443451         IF( lk_mpp .AND. jpnij > 1 ) THEN 
    444452            isplt = jpni   ;   jsplt = jpnj   ;   ijsplt = jpni*jpnj   ! the domain is forced to the real split domain 
     
    560568      sn_cfctl%l_oceout  = setto 
    561569      sn_cfctl%l_layout  = setto 
    562       sn_cfctl%l_mppout  = setto 
    563       sn_cfctl%l_mpptop  = setto 
     570      sn_cfctl%l_prtctl  = setto 
     571      sn_cfctl%l_prttrc  = setto 
     572      sn_cfctl%l_oasout  = setto 
    564573   END SUBROUTINE nemo_set_cfctl 
    565574 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/SAS/sbcssm.F90

    r11960 r12236  
    133133      vv (:,:,1,Kbb) = ssv_m(:,:) 
    134134  
    135       IF(ln_ctl) THEN                  ! print control 
     135      IF(sn_cfctl%l_prtctl) THEN            ! print control 
    136136         CALL prt_ctl(tab2d_1=sst_m, clinfo1=' sst_m   - : ', mask1=tmask   ) 
    137137         CALL prt_ctl(tab2d_1=sss_m, clinfo1=' sss_m   - : ', mask1=tmask   ) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/SAS/stpctl.F90

    r10603 r12236  
    6363      ! 
    6464      ll_wrtstp  = ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 
    65       ll_colruns = ll_wrtstp .AND. ( ln_ctl .OR. sn_cfctl%l_runstat ) 
     65      ll_colruns = ll_wrtstp .AND. ( sn_cfctl%l_runstat ) 
    6666      ll_wrtruns = ll_colruns .AND. lwm 
    6767      IF( kt == nit000 .AND. lwp ) THEN 
     
    7373         !                                ! open run.stat file(s) at start whatever 
    7474         !                                ! the value of sn_cfctl%ptimincr 
    75          IF( lwm .AND. ( ln_ctl .OR. sn_cfctl%l_runstat ) ) THEN 
     75         IF( lwm .AND. ( sn_cfctl%l_runstat ) ) THEN 
    7676            CALL ctl_opn( numrun, 'run.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    7777            clname = 'run.stat.nc' 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P2Z/p2zbio.F90

    r11960 r12236  
    368368      ENDIF 
    369369 
    370       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     370      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    371371         WRITE(charout, FMT="('bio')") 
    372372         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P2Z/p2zexp.F90

    r11949 r12236  
    147147      ENDIF 
    148148      ! 
    149       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     149      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    150150         WRITE(charout, FMT="('exp')") 
    151151         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P2Z/p2zopt.F90

    r11960 r12236  
    134134 
    135135 
    136       IF(ln_ctl) THEN      ! print mean trends (used for debugging) 
     136      IF(sn_cfctl%l_prttrc) THEN      ! print mean trends (used for debugging) 
    137137         WRITE(charout, FMT="('opt')") 
    138138         CALL prt_ctl_trc_info( charout ) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P2Z/p2zsed.F90

    r11960 r12236  
    108108      ! 
    109109 
    110       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     110      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    111111         WRITE(charout, FMT="('sed')") 
    112112         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P4Z/p4zagg.F90

    r11949 r12236  
    174174      ENDIF 
    175175      ! 
    176       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     176      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    177177         WRITE(charout, FMT="('agg')") 
    178178         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P4Z/p4zbio.F90

    r11949 r12236  
    107107      & CALL p4z_ligand( kt, knt, Kbb,      Krhs ) 
    108108      !                                                             ! 
    109       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     109      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    110110         WRITE(charout, FMT="('bio ')") 
    111111         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P4Z/p4zfechem.F90

    r12193 r12236  
    221221      ENDIF 
    222222 
    223       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     223      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    224224         WRITE(charout, FMT="('fechem')") 
    225225         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P4Z/p4zflx.F90

    r12193 r12236  
    180180      t_atm_co2_flx     =  atcco2      ! Total atmospheric pCO2 
    181181  
    182       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     182      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    183183         WRITE(charout, FMT="('flx ')") 
    184184         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P4Z/p4zligand.F90

    r11960 r12236  
    9595      ENDIF 
    9696      ! 
    97       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     97      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    9898         WRITE(charout, FMT="('ligand1')") 
    9999         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P4Z/p4zlys.F90

    r11960 r12236  
    130130      ENDIF 
    131131      ! 
    132       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     132      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    133133        WRITE(charout, FMT="('lys ')") 
    134134        CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P4Z/p4zmeso.F90

    r11960 r12236  
    256256      IF (ln_ligand)  DEALLOCATE( zz2ligprod ) 
    257257      ! 
    258       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     258      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    259259        WRITE(charout, FMT="('meso')") 
    260260        CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P4Z/p4zmicro.F90

    r11960 r12236  
    208208      IF (ln_ligand)  DEALLOCATE( zzligprod ) 
    209209      ! 
    210       IF(ln_ctl) THEN      ! print mean trends (used for debugging) 
     210      IF(sn_cfctl%l_prttrc) THEN      ! print mean trends (used for debugging) 
    211211         WRITE(charout, FMT="('micro')") 
    212212         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P4Z/p4zmort.F90

    r11960 r12236  
    120120      END DO 
    121121      ! 
    122        IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     122       IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    123123         WRITE(charout, FMT="('nano')") 
    124124         CALL prt_ctl_trc_info(charout) 
     
    196196      END DO 
    197197      ! 
    198       IF(ln_ctl) THEN      ! print mean trends (used for debugging) 
     198      IF(sn_cfctl%l_prttrc) THEN      ! print mean trends (used for debugging) 
    199199         WRITE(charout, FMT="('diat')") 
    200200         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P4Z/p4zpoc.F90

    r11960 r12236  
    249249      ENDIF 
    250250 
    251      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     251     IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    252252        WRITE(charout, FMT="('poc1')") 
    253253        CALL prt_ctl_trc_info(charout) 
     
    461461     ENDIF 
    462462 
    463       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     463      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    464464         WRITE(charout, FMT="('poc2')") 
    465465         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P4Z/p4zprod.F90

    r11960 r12236  
    457457     ENDIF 
    458458 
    459      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     459     IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    460460         WRITE(charout, FMT="('prod')") 
    461461         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P4Z/p4zrem.F90

    r11960 r12236  
    208208      END DO 
    209209 
    210        IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     210       IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    211211         WRITE(charout, FMT="('rem1')") 
    212212         CALL prt_ctl_trc_info(charout) 
     
    234234      END DO 
    235235 
    236        IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     236       IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    237237         WRITE(charout, FMT="('rem2')") 
    238238         CALL prt_ctl_trc_info(charout) 
     
    269269      END DO 
    270270 
    271       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     271      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    272272         WRITE(charout, FMT="('rem3')") 
    273273         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P4Z/p4zsed.F90

    r12193 r12236  
    349349      ENDIF 
    350350      ! 
    351       IF(ln_ctl) THEN  ! print mean trends (USEd for debugging) 
     351      IF(sn_cfctl%l_prttrc) THEN  ! print mean trends (USEd for debugging) 
    352352         WRITE(charout, fmt="('sed ')") 
    353353         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P4Z/p4zsink.F90

    r11949 r12236  
    173173      ENDIF 
    174174      ! 
    175       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     175      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    176176         WRITE(charout, FMT="('sink')") 
    177177         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P4Z/p5zmeso.F90

    r11960 r12236  
    377377      ENDIF 
    378378      ! 
    379       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     379      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    380380        WRITE(charout, FMT="('meso')") 
    381381        CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P4Z/p5zmicro.F90

    r11960 r12236  
    319319      ENDIF 
    320320      ! 
    321       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     321      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    322322         WRITE(charout, FMT="('micro')") 
    323323         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P4Z/p5zmort.F90

    r11960 r12236  
    121121      END DO 
    122122      ! 
    123        IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     123       IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    124124         WRITE(charout, FMT="('nano')") 
    125125         CALL prt_ctl_trc_info(charout) 
     
    183183      END DO 
    184184      ! 
    185        IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     185       IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    186186         WRITE(charout, FMT="('pico')") 
    187187         CALL prt_ctl_trc_info(charout) 
     
    262262      END DO 
    263263      ! 
    264       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     264      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    265265         WRITE(charout, FMT="('diat')") 
    266266         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P4Z/p5zprod.F90

    r11960 r12236  
    555555     ENDIF 
    556556 
    557       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     557      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    558558         WRITE(charout, FMT="('prod')") 
    559559         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/SED/trcdmp_sed.F90

    r11949 r12236  
    107107      ! 
    108108      !                                          ! print mean trends (used for debugging) 
    109       IF( ln_ctl ) THEN 
     109      IF( sn_cfctl%l_prttrc ) THEN 
    110110         WRITE(charout, FMT="('dmp ')") 
    111111         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/TRP/trcadv.F90

    r11960 r12236  
    137137      END SELECT 
    138138      !                   
    139       IF( ln_ctl ) THEN                         !== print mean trends (used for debugging) 
     139      IF( sn_cfctl%l_prttrc ) THEN        !== print mean trends (used for debugging) 
    140140         WRITE(charout, FMT="('adv ')") 
    141141         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/TRP/trcatf.F90

    r11949 r12236  
    170170      IF( l_trdtrc ) DEALLOCATE( ztrdt )  
    171171      ! 
    172       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     172      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    173173         WRITE(charout, FMT="('nxt')") 
    174174         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/TRP/trcbbl.F90

    r11949 r12236  
    6969         ! 
    7070         CALL tra_bbl_dif( ptr(:,:,:,:,Kbb), ptr(:,:,:,:,Krhs), jptra, Kmm )   
    71          IF( ln_ctl )   THEN 
     71         IF( sn_cfctl%l_prttrc )   THEN 
    7272            WRITE(charout, FMT="(' bbl_dif')")  ;  CALL prt_ctl_trc_info(charout) 
    7373            CALL prt_ctl_trc( tab4d=ptr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
     
    8080         ! 
    8181         CALL tra_bbl_adv( ptr(:,:,:,:,Kbb), ptr(:,:,:,:,Krhs), jptra, Kmm )   
    82          IF( ln_ctl )   THEN 
     82         IF( sn_cfctl%l_prttrc )   THEN 
    8383            WRITE(charout, FMT="(' bbl_adv')")  ;  CALL prt_ctl_trc_info(charout) 
    8484            CALL prt_ctl_trc( tab4d=ptr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/TRP/trcdmp.F90

    r11960 r12236  
    158158      IF( l_trdtrc )  DEALLOCATE( ztrtrd ) 
    159159      !                                          ! print mean trends (used for debugging) 
    160       IF( ln_ctl ) THEN 
     160      IF( sn_cfctl%l_prttrc ) THEN 
    161161         WRITE(charout, FMT="('dmp ')") 
    162162         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/TRP/trcldf.F90

    r11960 r12236  
    116116      ENDIF 
    117117      !                 
    118       IF( ln_ctl ) THEN                        ! print mean trends (used for debugging) 
     118      IF( sn_cfctl%l_prttrc ) THEN ! print mean trends (used for debugging) 
    119119         WRITE(charout, FMT="('ldf ')") 
    120120         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/TRP/trcrad.F90

    r11960 r12236  
    6868      IF( ln_my_trc  )   CALL trc_rad_sms( kt, Kbb, Kmm, ptr, jp_myt0, jp_myt1               )  !  MY_TRC model 
    6969      ! 
    70       IF(ln_ctl) THEN      ! print mean trends (used for debugging) 
     70      IF(sn_cfctl%l_prttrc) THEN      ! print mean trends (used for debugging) 
    7171         WRITE(charout, FMT="('rad')") 
    7272         CALL prt_ctl_trc_info( charout ) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/TRP/trcsbc.F90

    r11949 r12236  
    193193      ENDIF 
    194194      ! 
    195       IF( ln_ctl )   THEN 
     195      IF( sn_cfctl%l_prttrc )   THEN 
    196196         WRITE(charout, FMT="('sbc ')") ;  CALL prt_ctl_trc_info(charout) 
    197197                                           CALL prt_ctl_trc( tab4d=ptr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/TRP/trczdf.F90

    r11949 r12236  
    6767      ENDIF 
    6868      !                                          ! print mean trends (used for debugging) 
    69       IF( ln_ctl )   THEN 
     69      IF( sn_cfctl%l_prttrc )   THEN 
    7070         WRITE(charout, FMT="('zdf ')") 
    7171         CALL prt_ctl_trc_info(charout) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/prtctl_trc.F90

    r10570 r12236  
    3535   SUBROUTINE prt_ctl_trc( tab4d, mask, clinfo, ovlap, kdim, clinfo2 ) 
    3636      !!---------------------------------------------------------------------- 
    37       !!                     ***  ROUTINE prt_ctl  *** 
     37      !!                     ***  ROUTINE prt_ctl_trc  *** 
    3838      !! 
    3939      !! ** Purpose : - print sum control 3D arrays over the same area  
     
    4141      !!                debugging a new parametrization in mono or mpp.  
    4242      !! 
    43       !! ** Method  : 2 possibilities exist when setting the ln_ctl parameter to 
     43      !! ** Method  : 2 possibilities exist when setting the sn_cfctl%prttrc parameter to 
    4444      !!                .true. in the ocean namelist: 
    4545      !!              - to debug a MPI run .vs. a mono-processor one;  
     
    5454      !!              - All arguments of the above calling sequence are optional so their 
    5555      !!                name must be explicitly typed if used. For instance if the mask 
    56       !!                array tmask(:,:,:) must be passed through the prt_ctl subroutine,  
    57       !!                it must looks like: CALL prt_ctl( mask=tmask ). 
     56      !!                array tmask(:,:,:) must be passed through the prt_ctl_trc subroutine,  
     57      !!                it must look like: CALL prt_ctl_trc( mask=tmask ). 
    5858      !!---------------------------------------------------------------------- 
    5959      REAL(wp)         , DIMENSION(:,:,:,:), INTENT(in), OPTIONAL ::   tab4d     ! 4D array 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/trcini.F90

    r12193 r12236  
    140140      ENDIF 
    141141      IF(lwp) WRITE(numout,*) 
    142       IF(ln_ctl) THEN            ! print mean trends (used for debugging) 
     142      IF(sn_cfctl%l_prttrc) THEN            ! print mean trends (used for debugging) 
    143143         CALL prt_ctl_trc_init 
    144144         WRITE(charout, FMT="('ini ')") 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/trcsms.F90

    r11949 r12236  
    5656      IF( ln_my_trc  )   CALL trc_sms_my_trc ( kt, Kbb, Kmm, Krhs )    ! MY_TRC  tracers 
    5757 
    58       IF(ln_ctl) THEN      ! print mean trends (used for debugging) 
     58      IF(sn_cfctl%l_prttrc) THEN                       ! print mean trends (used for debugging) 
    5959         WRITE(charout, FMT="('sms ')") 
    6060         CALL prt_ctl_trc_info( charout ) 
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/trcstp.F90

    r12041 r12236  
    7070      ENDIF 
    7171      ! 
    72       ll_trcstat  = ( ln_ctl .OR. sn_cfctl%l_trcstat ) .AND. & 
     72      ll_trcstat  = ( sn_cfctl%l_trcstat ) .AND. & 
    7373     &              ( ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) ) 
    7474      IF( kt == nittrc000 .AND. lk_trdmxl_trc )  CALL trd_mxl_trc_init    ! trends: Mixed-layer 
     
    7878            cvol(:,:,jk) = e1e2t(:,:) * e3t(:,:,jk,Kmm) * tmask(:,:,jk) 
    7979         END DO 
    80          IF ( ln_ctl .OR. kt == nitrst .OR. ( ln_check_mass .AND. kt == nitend )              & 
     80         IF ( ll_trcstat .OR. kt == nitrst .OR. ( ln_check_mass .AND. kt == nitend )   & 
    8181            & .OR. iom_use( "pno3tot" ) .OR. iom_use( "ppo4tot" ) .OR. iom_use( "psiltot" )   & 
    8282            & .OR. iom_use( "palktot" ) .OR. iom_use( "pfertot" ) )                           & 
     
    8787      !     
    8888      ! 
    89       IF(ln_ctl) THEN 
     89      IF(sn_cfctl%l_prttrc) THEN 
    9090         WRITE(charout,FMT="('kt =', I4,'  d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear 
    9191         CALL prt_ctl_trc_info(charout) 
Note: See TracChangeset for help on using the changeset viewer.