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 2462 – NEMO

Changeset 2462


Ignore:
Timestamp:
2010-12-07T18:56:19+01:00 (13 years ago)
Author:
acc
Message:

DEV_r2460_v3_3beta_NOL. Changes to v3.3beta to improve assignment of ocean processes to ioserver processes when discarding land-only regions. See ticket #776

Location:
branches/DEV_r2460_v3_3beta_NOL/NEMOGCM
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • branches/DEV_r2460_v3_3beta_NOL/NEMOGCM/EXTERNAL/XMLIO_SERVER/src/IOSERVER/mod_event_parameters.f90

    r2281 r2462  
    1919  INTEGER, PARAMETER :: event_id_set_calendar          = 117 
    2020  INTEGER, PARAMETER :: event_id_stop_ioserver         = 999 
     21  INTEGER, ALLOCATABLE, SAVE :: nregproc_in(:) 
    2122END MODULE mod_event_parameters 
  • branches/DEV_r2460_v3_3beta_NOL/NEMOGCM/EXTERNAL/XMLIO_SERVER/src/IOSERVER/mod_ioclient_para.F90

    r2281 r2462  
    1717#endif 
    1818  USE mpi_mod 
     19  USE mod_event_parameters 
    1920  IMPLICIT NONE 
    2021    INTEGER :: NEW_COMM 
     
    2627    INTEGER :: nb_server_io   
    2728    INTEGER,ALLOCATABLE :: proc_color(:)  
    28     INTEGER :: i 
     29    INTEGER :: i, ix, jpni_reg, jpnj_reg 
    2930    INTEGER :: div,remain 
    3031    INTEGER :: group_color 
    3132    INTEGER :: Comm_client_server 
    3233    CHARACTER(LEN=6) :: oasis_server_id 
     34    LOGICAL :: ln_around, ln_use_allproc 
    3335     
    3436    IF (using_oasis) THEN 
     
    5153 
    5254    nb_server_io=global_size-mpi_size 
    53     div=mpi_size/nb_server_io 
    54     remain=MOD(mpi_size,nb_server_io) 
    55      
    56     IF (mpi_rank<remain*(div+1)) THEN 
    57       group_color=mpi_rank/(div+1) 
     55!    
     56! Need to be cleverer at setting group_colour when jpni*jpnj /= jpnij 
     57! nregproc_in holds the list of equivalent ranks in a jpni by jpnj decomposition 
     58! which has retained the land-only areas. If jpni*jpnj= jpnij then nregproc_in(mpi_size) 
     59! should equal mpi_size-1 and nregproc_in(mpi_rank+1) = mpi_rank for all mpi_rank. 
     60! 
     61    ln_use_allproc = .true. 
     62    ALLOCATE(nregproc_in(mpi_size)) 
     63    INQUIRE (file='layout.dat', exist=ln_around) 
     64    IF (ln_around) THEN 
     65! use it 
     66     OPEN(UNIT=123,FILE='layout.dat') 
     67     READ(123,'(48X,2i8,/)',ERR=606,END=606) jpni_reg, jpnj_reg 
     68     do ix = 1,mpi_size 
     69      READ(123,'(45X,I5)',ERR=606,END=606) nregproc_in(ix) 
     70     end do 
     71     ln_use_allproc = .false. 
     72 606 CLOSE(123) 
     73    ENDIF 
     74    IF ( ln_use_allproc ) THEN 
     75! 
     76! Either layout.dat does not exist or the reading of nregproc_in has failed. 
     77! Default to regular decomposition with no omitted land-only regions. 
     78! 
     79     do ix = 1,mpi_size 
     80      nregproc_in(ix) = ix - 1 
     81     end do 
     82! 
     83! jpni_reg and jpnj_reg are not known; just have to make sure jpni_reg*jpnj_reg=mpi_size 
     84! 
     85     jpni_reg=mpi_size 
     86     jpnj_reg=1 
     87    ENDIF 
     88 
     89    div=(jpni_reg*jpnj_reg)/nb_server_io 
     90    remain=MOD(jpni_reg*jpnj_reg,nb_server_io) 
     91  
     92! 
     93! Note need to add 1 to mpi_rank when indexing nregproc_in since nregproc_in is  
     94! indexed 1 to mpi_size but mpi_rank ranges from 0 to mpi_size-1 
     95! 
     96    IF (nregproc_in(mpi_rank+1)<remain*(div+1)) THEN 
     97      group_color=nregproc_in(mpi_rank+1)/(div+1) 
    5898    ELSE 
    59       group_color=(nb_server_io-1)-(mpi_size-1-mpi_rank)/div 
     99      group_color=(nb_server_io-1)-(jpni_reg*jpnj_reg - 1 -nregproc_in(mpi_rank+1))/div 
    60100    ENDIF 
    61101 
  • branches/DEV_r2460_v3_3beta_NOL/NEMOGCM/NEMO/OPA_SRC/DOM/dom_oce.F90

    r2443 r2462  
    8989   !                                                  ! (mi0=1 and mi1=0 if the global index is not in the local domain) 
    9090   INTEGER, PUBLIC, DIMENSION(jpnij)  ::   nimppt, njmppt   !: i-, j-indexes for each processor 
     91   INTEGER, PUBLIC, DIMENSION(jpnij)  ::   nregproc_out     !: equivalent rank position when jpni*jpnj=jpnij 
    9192   INTEGER, PUBLIC, DIMENSION(jpnij)  ::   ibonit, ibonjt   !: i-, j- processor neighbour existence 
    9293   INTEGER, PUBLIC, DIMENSION(jpnij)  ::   nlcit , nlcjt    !: dimensions of every subdomain 
  • branches/DEV_r2460_v3_3beta_NOL/NEMOGCM/NEMO/OPA_SRC/LBC/mppini.F90

    r2442 r2462  
    1616   USE lib_mpp         ! distribued memory computing library 
    1717   USE ioipsl 
     18#if defined key_iomput 
     19   USE mod_event_client 
     20# endif 
    1821 
    1922   IMPLICIT NONE 
     
    278281         nldjt(jn) = nldj 
    279282         nlejt(jn) = nlej 
     283         nregproc_out(jn) = jn - 1 
    280284      END DO 
    281285       
     
    336340        CALL ctl_opn( inum, 'layout.dat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., narea ) 
    337341        WRITE(inum,'(a)') '   jpnij     jpi     jpj     jpk  jpiglo  jpjglo' 
    338         WRITE(inum,'(6i8)') jpnij,jpi,jpj,jpk,jpiglo,jpjglo 
    339         WRITE(inum,'(a)') 'NAREA nlci nlcj nldi nldj nlei nlej nimpp njmpp' 
     342        WRITE(inum,'(8i8)') jpnij,jpi,jpj,jpk,jpiglo,jpjglo,jpni,jpnj 
     343        WRITE(inum,'(a)') 'NAREA nlci nlcj nldi nldj nlei nlej nimpp njmpp nregproc_out' 
    340344 
    341345        DO  jn = 1, jpnij 
    342          WRITE(inum,'(9i5)') jn, nlcit(jn), nlcjt(jn), & 
     346         WRITE(inum,'(10i5)') jn, nlcit(jn), nlcjt(jn), & 
    343347                                      nldit(jn), nldjt(jn), & 
    344348                                      nleit(jn), nlejt(jn), & 
    345                                       nimppt(jn), njmppt(jn) 
     349                                      nimppt(jn), njmppt(jn), nregproc_out(jn) 
    346350        END DO 
    347351        CLOSE(inum)    
     352#ifdef key_iomput 
     353     ! Check nregproc_in matches nregproc_out and abort if it does not. 
     354     ! This should only occur on the first run of a new domain decomposition 
     355     ! when jpni*jpnj /= jpnij. If ioservers are not being used, Init_parallel  
     356     ! will not have been called and nregproc_in will not have been allocated. 
     357     ! In such a case the check is unnecessary so only check for a match if  
     358     ! nregproc_in has been allocated. 
     359      IF (ALLOCATED(nregproc_in)) THEN 
     360        DO  jn = 1, jpnij 
     361         IF ( nregproc_in(jn) /= nregproc_out(jn) ) THEN 
     362          WRITE(numout,*) ' nregproc_in and nregproc_out do not match.' 
     363          WRITE(numout,*) ' This is expected when starting a new domain docomposition.' 
     364          WRITE(numout,*) ' The layout.dat file has been updated and the model may be rerun.' 
     365          CALL ctl_stop( ' mpp_init: IO server domain colour assignment mismatch ') 
     366         END IF 
     367        END DO 
     368      ENDIF 
     369#endif 
    348370      END IF 
    349371 
  • branches/DEV_r2460_v3_3beta_NOL/NEMOGCM/NEMO/OPA_SRC/LBC/mppini_2.h90

    r2442 r2462  
    4141      USE in_out_manager  ! I/O Manager 
    4242      USE iom 
     43#if defined key_iomput 
     44      USE mod_event_client 
     45# endif 
    4346      !!  
    4447      INTEGER :: ji, jj, jn, jproc, jarea     ! dummy loop indices 
     
    288291            iin(icont+1) = ii 
    289292            ijn(icont+1) = ij 
     293            nregproc_out(icont+1) = jarea - 1 
    290294         ENDIF 
    291295      END DO 
     
    461465      IF (lwp) THEN 
    462466         CALL ctl_opn( inum, 'layout.dat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., narea ) 
    463          WRITE(inum,'(6i8)') jpnij,jpi,jpj,jpk,jpiglo,jpjglo 
    464          WRITE(inum,'(a)') 'NAREA nlci nlcj nldi nldj nlei nlej nimpp njmpp' 
     467         WRITE(inum,'(8i8)') jpnij,jpi,jpj,jpk,jpiglo,jpjglo,jpni,jpnj 
     468         WRITE(inum,'(a)') 'NAREA nlci nlcj nldi nldj nlei nlej nimpp njmpp nregproc_out' 
    465469 
    466470        DO  jproc = 1, jpnij 
    467          WRITE(inum,'(9i5)') jproc, nlcit(jproc), nlcjt(jproc), & 
     471         WRITE(inum,'(10i5)') jproc, nlcit(jproc), nlcjt(jproc), & 
    468472                                      nldit(jproc), nldjt(jproc), & 
    469473                                      nleit(jproc), nlejt(jproc), & 
    470                                       nimppt(jproc), njmppt(jproc) 
     474                                      nimppt(jproc), njmppt(jproc), nregproc_out(jproc) 
    471475        END DO 
    472476        CLOSE(inum)    
     477#ifdef key_iomput 
     478     ! Check nregproc_in matches nregproc_out and abort if it does not. 
     479     ! This should only occur on the first run of a new domain decomposition 
     480     ! when jpni*jpnj /= jpnij. If ioservers are not being used, Init_parallel 
     481     ! will not have been called and nregproc_in will not have been allocated. 
     482     ! In such a case the check is unnecessary so only check for a match if 
     483     ! nregproc_in has been allocated. 
     484       IF (ALLOCATED(nregproc_in)) THEN 
     485        DO  jn = 1, jpnij 
     486         IF ( nregproc_in(jn) /= nregproc_out(jn) ) THEN 
     487          WRITE(numout,*) ' nregproc_in and nregproc_out do not match.' 
     488          WRITE(numout,*) ' This is expected when starting a new domain docomposition.' 
     489          WRITE(numout,*) ' The layout.dat file has been updated and the model may be rerun.' 
     490          CALL ctl_stop( ' mpp_init: IO server domain colour assignment mismatch ') 
     491         END IF 
     492        END DO 
     493       END IF 
     494#endif 
    473495      END IF 
    474496 
Note: See TracChangeset for help on using the changeset viewer.