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 9449 for branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/LBC/mppini.F90 – NEMO

Ignore:
Timestamp:
2018-03-30T17:37:02+02:00 (6 years ago)
Author:
smasson
Message:

dev_merge_2017: agrif bugfix for non-constant jpi/jpj + some cleaning...

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/LBC/mppini.F90

    r9446 r9449  
    106106   !!---------------------------------------------------------------------- 
    107107 
     108 
    108109   SUBROUTINE mpp_init 
    109110      !!---------------------------------------------------------------------- 
     
    159160      ! If dimensions of processor grid weren't specified in the namelist file 
    160161      ! then we calculate them here now that we have our communicator size 
    161       IF( jpni < 1 .OR. jpnj < 1 ) THEN 
    162          IF( Agrif_Root() )   CALL mpp_init_partition( mppsize ) 
    163       ENDIF 
     162      IF( jpni < 1 .OR. jpnj < 1 )   CALL mpp_init_partition( mppsize ) 
    164163      ! 
    165164#if defined key_agrif 
    166165      IF( jpnij /= jpni*jpnj ) CALL ctl_stop( 'STOP', 'Cannot remove land proc with AGRIF' ) 
    167166#endif 
    168  
    169167      ! 
    170168      ALLOCATE(  nfiimpp(jpni,jpnj), nfipproc(jpni,jpnj), nfilcit(jpni,jpnj) ,    & 
     
    183181       
    184182      ! 
    185 #if defined key_agrif 
    186183      IF( .NOT. Agrif_Root() ) THEN       ! AGRIF children: specific setting (cf. agrif_user.F90) 
    187          jpiglo  = nbcellsx + 2 + 2*nbghostcells 
    188          jpjglo  = nbcellsy + 2 + 2*nbghostcells 
    189          jpimax  = ( jpiglo-2*nn_hls + (jpni-1+0) ) / jpni + 2*nn_hls 
    190          jpjmax  = ( jpjglo-2*nn_hls + (jpnj-1+0) ) / jpnj + 2*nn_hls 
    191          jperio  = 0 
    192          ln_use_jattr = .false. 
    193       ENDIF 
     184         IF( jpiglo /= nbcellsx + 2 + 2*nbghostcells )   & 
     185            CALL ctl_stop( 'STOP', 'mpp_init: Agrif children requires jpiglo == nbcellsx + 2 + 2*nbghostcells' ) 
     186         IF( jpjglo /= nbcellsy + 2 + 2*nbghostcells )   & 
     187            CALL ctl_stop( 'STOP', 'mpp_init: Agrif children requires jpjglo == nbcellsy + 2 + 2*nbghostcells' ) 
     188         IF( ln_use_jattr )   CALL ctl_stop( 'STOP', 'mpp_init:Agrif children requires ln_use_jattr = .false. ' ) 
     189      ENDIF 
     190 
     191#if defined key_nemocice_decomp 
     192      jpimax = ( nx_global+2-2*nn_hls + (jpni-1) ) / jpni + 2*nn_hls    ! first  dim. 
     193      jpjmax = ( ny_global+2-2*nn_hls + (jpnj-1) ) / jpnj + 2*nn_hls    ! second dim.  
     194#else 
     195      jpimax = ( jpiglo - 2*nn_hls + (jpni-1) ) / jpni + 2*nn_hls    ! first  dim. 
     196      jpjmax = ( jpjglo - 2*nn_hls + (jpnj-1) ) / jpnj + 2*nn_hls    ! second dim. 
    194197#endif 
    195  
    196       IF( Agrif_Root() ) THEN       ! AGRIF mother: specific setting from jpni and jpnj 
    197 #if defined key_nemocice_decomp 
    198          jpimax = ( nx_global+2-2*nn_hls + (jpni-1) ) / jpni + 2*nn_hls    ! first  dim. 
    199          jpjmax = ( ny_global+2-2*nn_hls + (jpnj-1) ) / jpnj + 2*nn_hls    ! second dim.  
    200 #else 
    201          jpimax = ( jpiglo - 2*nn_hls + (jpni-1) ) / jpni + 2*nn_hls    ! first  dim. 
    202          jpjmax = ( jpjglo - 2*nn_hls + (jpnj-1) ) / jpnj + 2*nn_hls    ! second dim. 
    203 #endif 
    204       ENDIF 
    205198 
    206199      ! 
     
    449442      ii_noea(:) = -1 
    450443      ii_nowe(:) = -1  
    451       DO jarea = 1, jpnij 
    452          ii = iin(jarea) 
    453          ij = ijn(jarea) 
     444      DO jproc = 1, jpnij 
     445         ii = iin(jproc) 
     446         ij = ijn(jproc) 
    454447         IF( 0 <= ioso(ii,ij) .AND. ioso(ii,ij) <= (jpni*jpnj-1) ) THEN 
    455448            iiso = 1 + MOD( ioso(ii,ij) , jpni ) 
    456449            ijso = 1 +      ioso(ii,ij) / jpni 
    457             ii_noso(jarea) = ipproc(iiso,ijso) 
     450            ii_noso(jproc) = ipproc(iiso,ijso) 
    458451         ENDIF 
    459452         IF( 0 <= iowe(ii,ij) .AND. iowe(ii,ij) <= (jpni*jpnj-1) ) THEN 
    460453          iiwe = 1 + MOD( iowe(ii,ij) , jpni ) 
    461454          ijwe = 1 +      iowe(ii,ij) / jpni 
    462           ii_nowe(jarea) = ipproc(iiwe,ijwe) 
     455          ii_nowe(jproc) = ipproc(iiwe,ijwe) 
    463456         ENDIF 
    464457         IF( 0 <= ioea(ii,ij) .AND. ioea(ii,ij) <= (jpni*jpnj-1) ) THEN 
    465458            iiea = 1 + MOD( ioea(ii,ij) , jpni ) 
    466459            ijea = 1 +      ioea(ii,ij) / jpni 
    467             ii_noea(jarea)= ipproc(iiea,ijea) 
     460            ii_noea(jproc)= ipproc(iiea,ijea) 
    468461         ENDIF 
    469462         IF( 0 <= iono(ii,ij) .AND. iono(ii,ij) <= (jpni*jpnj-1) ) THEN 
    470463            iino = 1 + MOD( iono(ii,ij) , jpni ) 
    471464            ijno = 1 +      iono(ii,ij) / jpni 
    472             ii_nono(jarea)= ipproc(iino,ijno) 
     465            ii_nono(jproc)= ipproc(iino,ijno) 
    473466         ENDIF 
    474467      END DO 
     
    501494      ! Save maximum number of levels in jpkglo, then define all vertical grids with this number. 
    502495      ! Suppress once vertical online interpolation is ok 
    503       IF(.NOT.Agrif_Root())   jpkglo = Agrif_Parent( jpkglo ) 
     496!!$      IF(.NOT.Agrif_Root())   jpkglo = Agrif_Parent( jpkglo ) 
    504497#endif 
    505498      jpim1 = jpi-1                                            ! inner domain indices 
Note: See TracChangeset for help on using the changeset viewer.