New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 10570 for NEMO/trunk/src/SAO/nemogcm.F90 – NEMO

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

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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/SAO/nemogcm.F90

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