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 6808 for branches/NERC/dev_r5549_BDY_ZEROGRAD/NEMOGCM/NEMO/OPA_SRC/stpctl.F90 – NEMO

Ignore:
Timestamp:
2016-07-19T10:38:35+02:00 (8 years ago)
Author:
jamesharle
Message:

merge with trunk@6232 for consistency with SSB code

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/NERC/dev_r5549_BDY_ZEROGRAD/NEMOGCM/NEMO/OPA_SRC/stpctl.F90

    r3294 r6808  
    1616   USE oce             ! ocean dynamics and tracers variables 
    1717   USE dom_oce         ! ocean space and time domain variables  
    18    USE sol_oce         ! ocean space and time domain variables  
     18   USE c1d             ! 1D vertical configuration 
     19   ! 
    1920   USE in_out_manager  ! I/O manager 
    2021   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    2122   USE lib_mpp         ! distributed memory computing 
    22    USE dynspg_oce      ! pressure gradient schemes  
    23    USE c1d             ! 1D vertical configuration 
    2423 
    2524   IMPLICIT NONE 
     
    3231   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    3332   !!---------------------------------------------------------------------- 
    34  
    3533CONTAINS 
    3634 
     
    4341      !! ** Method  : - Save the time step in numstp 
    4442      !!              - Print it each 50 time steps 
    45       !!              - Print solver statistics in numsol  
    46       !!              - Stop the run IF problem for the solver ( indec < 0 ) 
     43      !!              - Stop the run IF problem ( indic < 0 ) 
    4744      !! 
    4845      !! ** Actions :   'time.step' file containing the last ocean time-step 
    4946      !!                 
    5047      !!---------------------------------------------------------------------- 
    51       INTEGER, INTENT( in ) ::   kt         ! ocean time-step index 
    52       INTEGER, INTENT( inout ) ::   kindic  ! indicator of solver convergence 
     48      INTEGER, INTENT(in   ) ::   kt       ! ocean time-step index 
     49      INTEGER, INTENT(inout) ::   kindic   ! error indicator 
    5350      !! 
    54       INTEGER  ::   ji, jj, jk              ! dummy loop indices 
    55       INTEGER  ::   ii, ij, ik              ! temporary integers 
    56       REAL(wp) ::   zumax, zsmin, zssh2     ! temporary scalars 
    57       INTEGER, DIMENSION(3) ::   ilocu      !  
    58       INTEGER, DIMENSION(2) ::   ilocs      !  
     51      INTEGER  ::   ji, jj, jk             ! dummy loop indices 
     52      INTEGER  ::   ii, ij, ik             ! local integers 
     53      REAL(wp) ::   zumax, zsmin, zssh2    ! local scalars 
     54      INTEGER, DIMENSION(3) ::   ilocu     !  
     55      INTEGER, DIMENSION(2) ::   ilocs     !  
    5956      !!---------------------------------------------------------------------- 
    60  
     57      ! 
    6158      IF( kt == nit000 .AND. lwp ) THEN 
    6259         WRITE(numout,*) 
     
    6663         CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    6764      ENDIF 
    68  
     65      ! 
    6966      IF(lwp) WRITE ( numstp, '(1x, i8)' )   kt      !* save the current time step in numstp 
    7067      IF(lwp) REWIND( numstp )                       !  -------------------------- 
    71  
     68      ! 
    7269      !                                              !* Test maximum of velocity (zonal only) 
    7370      !                                              !  ------------------------ 
     
    105102      ENDIF 
    1061039400  FORMAT (' kt=',i6,' max abs(U): ',1pg11.4,', i j k: ',3i5) 
    107  
     104      ! 
    108105      !                                              !* Test minimum of salinity 
    109106      !                                              !  ------------------------ 
    110107      !! zsmin = MINVAL( tsn(:,:,1,jp_sal), mask = tmask(:,:,1) == 1.e0 )  slower than the following loop on NEC SX5 
    111       zsmin = 100.e0 
     108      zsmin = 100._wp 
    112109      DO jj = 2, jpjm1 
    113110         DO ji = 1, jpi 
     
    139136      ENDIF 
    1401379500  FORMAT (' kt=',i6,' min SSS: ',1pg11.4,', i j: ',2i5) 
    141  
    142        
     138      ! 
     139      ! 
    143140      IF( lk_c1d )  RETURN          ! No log file in case of 1D vertical configuration 
    144141 
    145       ! log file (solver or ssh statistics) 
    146       ! -------- 
    147       IF( lk_dynspg_flt ) THEN      ! elliptic solver statistics (if required) 
    148          ! 
    149          IF(lwp) WRITE(numsol,9200) kt, niter, res, SQRT(epsr)/eps       ! Solver 
    150          ! 
    151          IF( kindic < 0 .AND. zsmin > 0.e0 .AND. zumax <= 20.e0 ) THEN   ! create a abort file if problem found  
    152             IF(lwp) THEN 
    153                WRITE(numout,*) ' stpctl: the elliptic solver DO not converge or explode' 
    154                WRITE(numout,*) ' ====== ' 
    155                WRITE(numout,9200) kt, niter, res, sqrt(epsr)/eps 
    156                WRITE(numout,*) 
    157                WRITE(numout,*) ' stpctl: output of last fields' 
    158                WRITE(numout,*) ' ======  ' 
    159             ENDIF 
    160          ENDIF 
    161          ! 
    162       ELSE                                   !* ssh statistics (and others...) 
    163          IF( kt == nit000 .AND. lwp ) THEN   ! open ssh statistics file (put in solver.stat file) 
    164             CALL ctl_opn( numsol, 'solver.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    165          ENDIF 
    166          ! 
    167          zssh2 = SUM( sshn(:,:) * sshn(:,:) * tmask_i(:,:) ) 
    168          IF( lk_mpp )   CALL mpp_sum( zssh2 )      ! sum over the global domain 
    169          ! 
    170          IF(lwp) WRITE(numsol,9300) kt, zssh2, zumax, zsmin      ! ssh statistics 
    171          ! 
     142      ! log file (ssh statistics) 
     143      ! --------                                   !* ssh statistics (and others...) 
     144      IF( kt == nit000 .AND. lwp ) THEN   ! open ssh statistics file (put in solver.stat file) 
     145         CALL ctl_opn( numsol, 'solver.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    172146      ENDIF 
    173  
     147      ! 
     148      zssh2 = SUM( sshn(:,:) * sshn(:,:) * tmask_i(:,:) ) 
     149      IF( lk_mpp )   CALL mpp_sum( zssh2 )      ! sum over the global domain 
     150      ! 
     151      IF(lwp) WRITE(numsol,9300) kt, zssh2, zumax, zsmin      ! ssh statistics 
     152      ! 
    1741539200  FORMAT('it:', i8, ' iter:', i4, ' r: ',e16.10, ' b: ',e16.10 ) 
    1751549300  FORMAT(' it :', i8, ' ssh2: ', e16.10, ' Umax: ',e16.10,' Smin: ',e16.10) 
Note: See TracChangeset for help on using the changeset viewer.