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 11398 for NEMO – NEMO

Changeset 11398 for NEMO


Ignore:
Timestamp:
2019-08-02T18:43:29+02:00 (5 years ago)
Author:
smasson
Message:

dev_r10984_HPC-13 : add nammpp parameter ln_listonly, see #2285

Location:
NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/cfgs/SHARED/namelist_ref

    r11385 r11398  
    13041304&nammpp        !   Massively Parallel Processing                        ("key_mpp_mpi") 
    13051305!----------------------------------------------------------------------- 
     1306   ln_listonly =  .false.  !  do nothing else than listing the best domain decompositions (with land domains suppression) 
     1307   !                       !  if T: the largest number of cores tested is defined by max(mppsize, jpni*jpnj) 
    13061308   ln_nnogather =  .true.  !  activate code to avoid mpi_allgather use at the northfold 
    1307    jpni        =   0       !  jpni   number of processors following i (set automatically if < 1) 
    1308    jpnj        =   0       !  jpnj   number of processors following j (set automatically if < 1) 
     1309   jpni        =   0       !  number of processors following i (set automatically if < 1), see also ln_listonly = T 
     1310   jpnj        =   0       !  number of processors following j (set automatically if < 1), see also ln_listonly = T 
    13091311/ 
    13101312!----------------------------------------------------------------------- 
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/OCE/LBC/lib_mpp.F90

    r11389 r11398  
    663663 
    664664 
    665    SUBROUTINE mppstop( ldfinal, ld_force_abort )  
     665   SUBROUTINE mppstop( ld_abort )  
    666666      !!---------------------------------------------------------------------- 
    667667      !!                  ***  routine mppstop  *** 
     
    670670      !! 
    671671      !!---------------------------------------------------------------------- 
    672       LOGICAL, OPTIONAL, INTENT(in) :: ldfinal    ! source process number 
    673       LOGICAL, OPTIONAL, INTENT(in) :: ld_force_abort    ! source process number 
    674       LOGICAL ::   llfinal, ll_force_abort 
     672      LOGICAL, OPTIONAL, INTENT(in) :: ld_abort    ! source process number 
     673      LOGICAL ::   ll_abort 
    675674      INTEGER ::   info 
    676675      !!---------------------------------------------------------------------- 
    677       llfinal = .FALSE. 
    678       IF( PRESENT(ldfinal) ) llfinal = ldfinal 
    679       ll_force_abort = .FALSE. 
    680       IF( PRESENT(ld_force_abort) ) ll_force_abort = ld_force_abort 
    681       ! 
    682 #if defined key_mpp_mpi 
    683       IF(ll_force_abort) THEN 
     676      ll_abort = .FALSE. 
     677      IF( PRESENT(ld_abort) ) ll_abort = ld_abort 
     678      ! 
     679#if defined key_mpp_mpi 
     680      IF(ll_abort) THEN 
    684681         CALL mpi_abort( MPI_COMM_WORLD ) 
    685682      ELSE 
     
    688685      ENDIF 
    689686#endif 
    690       IF( .NOT. llfinal ) STOP 123 
     687      IF( ll_abort ) STOP 123 
    691688      ! 
    692689   END SUBROUTINE mppstop 
     
    11181115         WRITE(numout,*)  'huge E-R-R-O-R : immediate stop' 
    11191116         WRITE(numout,*)   
    1120          CALL mppstop( ld_force_abort = .true. ) 
     1117         CALL mppstop( ld_abort = .true. ) 
    11211118      ENDIF 
    11221119      ! 
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/OCE/LBC/mppini.F90

    r11317 r11398  
    154154      LOGICAL ::   llbest, llauto 
    155155      LOGICAL ::   llwrtlay 
     156      LOGICAL ::   ln_listonly 
    156157      INTEGER, ALLOCATABLE, DIMENSION(:)     ::   iin, ii_nono, ii_noea          ! 1D workspace 
    157158      INTEGER, ALLOCATABLE, DIMENSION(:)     ::   ijn, ii_noso, ii_nowe          !  -     - 
     
    168169           &             rn_ice_tem, rn_ice_sal, rn_ice_age,                     & 
    169170           &             ln_vol, nn_volctl, nn_rimwidth 
    170       NAMELIST/nammpp/ jpni, jpnj, ln_nnogather 
     171      NAMELIST/nammpp/ jpni, jpnj, ln_nnogather, ln_listonly 
    171172      !!---------------------------------------------------------------------- 
    172173      ! 
     
    206207      IF(               ln_read_cfg ) CALL iom_open( cn_domcfg,    numbot ) 
    207208      IF( ln_bdy .AND. ln_mask_file ) CALL iom_open( cn_mask_file, numbdy ) 
     209      ! 
     210      IF( ln_listonly )   CALL mpp_init_bestpartition( MAX(mppsize,jpni*jpnj), ldlist = .TRUE. )   ! must be done by all core 
    208211      ! 
    209212      !  1. Dimension arrays for subdomains 
     
    268271         CALL ctl_stop( ctmp1, ctmp2, ctmp3, ' ', ctmp4, ' ' ) 
    269272         CALL mpp_init_bestpartition( mppsize, ldlist = .TRUE. )   ! must be done by all core 
    270          CALL ctl_stop( 'STOP' ) 
    271273      ENDIF 
    272274 
     
    293295         ENDIF 
    294296         CALL mpp_init_bestpartition( mppsize, ldlist = .TRUE. )   ! must be done by all core 
    295          CALL ctl_stop( 'STOP' ) 
    296297      ENDIF 
    297298 
     
    843844      INTEGER :: isziref, iszjref 
    844845      INTEGER :: inbij, iszij 
    845       INTEGER :: inbimax, inbjmax, inbijmax 
     846      INTEGER :: inbimax, inbjmax, inbijmax, inbijold 
    846847      INTEGER :: isz0, isz1 
    847848      INTEGER, DIMENSION(  :), ALLOCATABLE :: indexok 
     
    968969      DEALLOCATE( indexok, inbi1, inbj1, iszi1, iszj1 ) 
    969970 
    970       IF( llist ) THEN  ! we print about 21 best partitions 
     971      IF( llist ) THEN 
    971972         IF(lwp) THEN 
    972973            WRITE(numout,*) 
    973             WRITE(numout,         *) '                  For your information:' 
    974             WRITE(numout,'(a,i5,a)') '  list of the best partitions around ',   knbij, ' mpi processes' 
    975             WRITE(numout,         *) '  --------------------------------------', '-----', '--------------' 
     974            WRITE(numout,*) '                  For your information:' 
     975            WRITE(numout,*) '  list of the best partitions including land supression' 
     976            WRITE(numout,*) '  -----------------------------------------------------' 
    976977            WRITE(numout,*) 
    977978         END IF 
    978          iitarget = MINLOC( inbi0(:)*inbj0(:), mask = inbi0(:)*inbj0(:) >= knbij, dim = 1 ) 
    979          DO ji = MAX(1,iitarget-10), MIN(isz0,iitarget+10) 
     979         ji = isz0   ! initialization with the largest value 
     980         ALLOCATE( llisoce(inbi0(ji), inbj0(ji)) ) 
     981         CALL mpp_init_isoce( inbi0(ji), inbj0(ji), llisoce ) ! Warning: must be call by all cores (call mpp_sum) 
     982         inbijold = COUNT(llisoce) 
     983         DEALLOCATE( llisoce ) 
     984         DO ji =isz0-1,1,-1 
    980985            ALLOCATE( llisoce(inbi0(ji), inbj0(ji)) ) 
    981986            CALL mpp_init_isoce( inbi0(ji), inbj0(ji), llisoce ) ! Warning: must be call by all cores (call mpp_sum) 
    982987            inbij = COUNT(llisoce) 
    983988            DEALLOCATE( llisoce ) 
    984             IF(lwp) WRITE(numout,'(a, i5, a, i5, a, i4, a, i4, a, i9, a, i5, a, i5, a)')    & 
    985                &     'nb_cores ' , inbij,' oce + ', inbi0(ji)*inbj0(ji) - inbij             & 
    986                &                                , ' land ( ', inbi0(ji),' x ', inbj0(ji),   & 
    987                & ' ), nb_points ', iszi0(ji)*iszj0(ji),' ( ', iszi0(ji),' x ', iszj0(ji),' )' 
     989            IF(lwp .AND. inbij < inbijold) THEN 
     990               WRITE(numout,'(a, i6, a, i6, a, f4.1, a, i9, a, i6, a, i6, a)')                                 & 
     991                  &   'nb_cores oce: ', inbij, ', land domains excluded: ', inbi0(ji)*inbj0(ji) - inbij,       & 
     992                  &   ' (', REAL(inbi0(ji)*inbj0(ji) - inbij,wp) / REAL(inbi0(ji)*inbj0(ji),wp) *100.,         & 
     993                  &   '%), largest oce domain: ', iszi0(ji)*iszj0(ji), ' ( ', iszi0(ji),' x ', iszj0(ji), ' )' 
     994               inbijold = inbij 
     995            END IF 
    988996         END DO 
    989997         DEALLOCATE( inbi0, inbj0, iszi0, iszj0 ) 
    990          RETURN 
     998         IF(lwp) THEN 
     999            WRITE(numout,*) 
     1000            WRITE(numout,*)  '  -----------------------------------------------------------' 
     1001         ENDIF 
     1002         CALL mppsync 
     1003         CALL mppstop( ld_abort = .TRUE. ) 
    9911004      ENDIF 
    9921005       
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/OCE/nemogcm.F90

    r11389 r11398  
    242242#else 
    243243      IF    ( lk_oasis ) THEN   ;   CALL cpl_finalize   ! end coupling and mpp communications with OASIS 
    244       ELSEIF( lk_mpp   ) THEN   ;   CALL mppstop( ldfinal = .TRUE. )   ! end mpp communications 
     244      ELSEIF( lk_mpp   ) THEN   ;   CALL mppstop      ! end mpp communications 
    245245      ENDIF 
    246246#endif 
  • NEMO/branches/2019/dev_r10984_HPC-13_IRRMANN_BDY_optimization/src/SAS/nemogcm.F90

    r11317 r11398  
    164164#else 
    165165      IF    ( lk_oasis ) THEN   ;   CALL cpl_finalize   ! end coupling and mpp communications with OASIS 
    166       ELSEIF( lk_mpp   ) THEN   ;   CALL mppstop( ldfinal = .TRUE. )   ! end mpp communications 
     166      ELSEIF( lk_mpp   ) THEN   ;   CALL mppstop        ! end mpp communications 
    167167      ENDIF 
    168168#endif 
Note: See TracChangeset for help on using the changeset viewer.