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

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 10745 for branches/UKMO/dev_r5518_GO6_package_text_diagnostics/NEMOGCM/NEMO/OPA_SRC/stpctl.F90 – NEMO

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

GMED 450 GO8 changes to namelist namctl

File:
1 edited

Legend:

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

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