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 14072 for NEMO/trunk/tests/STATION_ASF/MY_SRC/stpctl.F90 – NEMO

Ignore:
Timestamp:
2020-12-04T08:48:38+01:00 (3 years ago)
Author:
laurent
Message:

Merging branch "2020/dev_r13648_ASINTER-04_laurent_bulk_ice", ticket #2369

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/tests/STATION_ASF/MY_SRC/stpctl.F90

    r13616 r14072  
    4343      !!---------------------------------------------------------------------- 
    4444      !!                    ***  ROUTINE stp_ctl  *** 
    45       !!                      
     45      !! 
    4646      !! ** Purpose :   Control the run 
    4747      !! 
     
    6363      INTEGER , DIMENSION(4)          ::   iareasum, iareamin, iareamax 
    6464      INTEGER , DIMENSION(3,3)        ::   iloc                                  ! min/max loc indices 
    65       REAL(wp)                        ::   zzz                                   ! local real  
     65      REAL(wp)                        ::   zzz                                   ! local real 
    6666      REAL(wp), DIMENSION(4)          ::   zmax, zmaxlocal 
    6767      LOGICAL                         ::   ll_wrtstp, ll_colruns, ll_wrtruns, ll_0oce 
     
    7272      ! 
    7373      ll_wrtstp  = ( MOD( kt-nit000, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) 
    74       ll_colruns = ll_wrtstp .AND. sn_cfctl%l_runstat .AND. jpnij > 1  
     74      ll_colruns = ll_wrtstp .AND. sn_cfctl%l_runstat .AND. jpnij > 1 
    7575      ll_wrtruns = ( ll_colruns .OR. jpnij == 1 ) .AND. lwm 
    7676      ! 
     
    9898            istatus = NF90_ENDDEF(nrunid) 
    9999         ENDIF 
    100          !     
     100         ! 
    101101      ENDIF 
    102102      ! 
     
    158158            IF( lwm .AND. kt /= nitend )   istatus = NF90_CLOSE(nrunid) 
    159159            ! get global loc on the min/max 
    160             CALL mpp_maxloc( 'stpctl',    taum(:,:)  , llmsk, zzz, iloc(1:2,1) )   ! mpp_maxloc ok if mask = F  
     160            CALL mpp_maxloc( 'stpctl',    taum(:,:)  , llmsk, zzz, iloc(1:2,1) )   ! mpp_maxloc ok if mask = F 
    161161            CALL mpp_maxloc( 'stpctl',ABS( qns(:,:) ), llmsk, zzz, iloc(1:2,2) ) 
    162162            CALL mpp_minloc( 'stpctl',ABS( emp(:,:) ), llmsk, zzz, iloc(1:2,3) ) 
     
    194194         CALL dia_wri_state( Kmm, 'output.abort' )     ! create an output.abort file 
    195195         ! 
    196          IF( ll_colruns .or. jpnij == 1 ) THEN   ! all processes synchronized -> use lwp to print in opened ocean.output files 
    197             IF(lwp) THEN   ;   CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 
    198             ELSE           ;   nstop = MAX(1, nstop)   ! make sure nstop > 0 (automatically done when calling ctl_stop) 
     196         IF( ll_colruns .OR. jpnij == 1 ) THEN   ! all processes synchronized -> use lwp to print in opened ocean.output files 
     197            IF(lwp) THEN 
     198               CALL ctl_stop( ctmp1, ' ', ctmp2, ctmp3, ctmp4, ctmp5, ' ', ctmp6 ) 
     199            ELSE 
     200               nstop = MAX(1, nstop)   ! make sure nstop > 0 (automatically done when calling ctl_stop) 
    199201            ENDIF 
    200202         ELSE                                    ! only mpi subdomains with errors are here -> STOP now 
     
    235237      !!---------------------------------------------------------------------- 
    236238      WRITE(clkt , '(i9)') kt 
    237        
     239 
    238240      WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpnij  ,wp))) + 1     ! how many digits to we need to write ? (we decide max = 9) 
    239       !!! WRITE(clsum, '(i'//clfmt//')') ksum                   ! this is creating a compilation error with AGRIF 
     241!!! WRITE(clsum, '(i'//clfmt//')') ksum                   ! this is creating a compilation error with AGRIF 
    240242      cl4 = '(i'//clfmt//')'   ;   WRITE(clsum, cl4) ksum 
    241243      WRITE(clfmt, '(i1)') INT(LOG10(REAL(MAX(1,jpnij-1),wp))) + 1    ! how many digits to we need to write ? (we decide max = 9) 
    242244      cl4 = '(i'//clfmt//')'   ;   WRITE(clmin, cl4) kmin-1 
    243                                    WRITE(clmax, cl4) kmax-1 
     245      WRITE(clmax, cl4) kmax-1 
    244246      ! 
    245247      WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpiglo,wp))) + 1      ! how many digits to we need to write jpiglo? (we decide max = 9) 
     
    257259      ELSE 
    258260         WRITE(clfmt, '(i1)') INT(LOG10(REAL(jpk,wp))) + 1      ! how many digits to we need to write jpk? (we decide max = 9) 
    259          !!! WRITE(clk, '(i'//clfmt//')') kloc(3)               ! this is creating a compilation error with AGRIF 
     261!!! WRITE(clk, '(i'//clfmt//')') kloc(3)               ! this is creating a compilation error with AGRIF 
    260262         cl4 = '(i'//clfmt//')'   ;   WRITE(clk, cl4) kloc(3)   ! this is ok with AGRIF 
    261263         WRITE(cdline,9400) TRIM(ADJUSTL(clkt)), TRIM(ADJUSTL(cdprefix)), pval, TRIM(cli), TRIM(clj),    TRIM(clk), TRIM(clsuff) 
Note: See TracChangeset for help on using the changeset viewer.