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 9467 for branches/2017 – NEMO

Changeset 9467 for branches/2017


Ignore:
Timestamp:
2018-04-11T13:22:29+02:00 (6 years ago)
Author:
acc
Message:

Branch 2017/dev_merge_2017. Fix for out of bounds error with the extended form of lbcnfd. See ticket #2074

Location:
branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/LBC/lbc_nfd_ext_generic.h90

    r9190 r9467  
    1212   SUBROUTINE ROUTINE_NFD( ptab, cd_nat, psgn, kextj ) 
    1313      !!---------------------------------------------------------------------- 
    14       ARRAY_TYPE(:,:,:,:,:)                             ! array or pointer of arrays on which the boundary condition is applied 
     14      ARRAY_TYPE(:,1-kextj:,:,:,:)                      ! array or pointer of arrays on which the boundary condition is applied 
    1515      CHARACTER(len=1) , INTENT(in   ) ::   NAT_IN(:)   ! nature of array grid-points 
    1616      REAL(wp)         , INTENT(in   ) ::   SGN_IN(:)   ! sign used across the north fold boundary 
     
    5656            CASE ( 'U' )                               ! U-point 
    5757               DO jh = 0, kextj 
    58                   DO ji = 1, jpiglo-1 
     58                  DO ji = 2, jpiglo-1 
    5959                     iju = jpiglo-ji+1 
    6060                     ARRAY_IN(ji,ipj+jh,:,:,jf) = SGN_IN(jf)  * ARRAY_IN(iju,ipj-2-jh,:,:,jf) 
     
    8383                     ARRAY_IN(ji,ipj+jh  ,:,:,jf) = SGN_IN(jf)  * ARRAY_IN(iju,ipj-3-jh,:,:,jf) 
    8484                  END DO 
     85               END DO 
     86               DO jh = 0, kextj 
    8587                  ARRAY_IN(   1  ,ipj+jh,:,:,jf) = SGN_IN(jf)  * ARRAY_IN(    2   ,ipj-3-jh,:,:,jf) 
    86                   ARRAY_IN(jpiglo,ipj+jh,:,:,jf) = SGN_IN(jf)  * ARRAY_IN(jpiglo-1,ipj-3-jh,:,:,jf)  
     88                  ARRAY_IN(jpiglo,ipj+jh,:,:,jf) = SGN_IN(jf)  * ARRAY_IN(jpiglo-1,ipj-3-jh,:,:,jf) 
    8789               END DO 
    8890            END SELECT 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/LBC/lib_mpp.F90

    r9438 r9467  
    13691369      ! 
    13701370      ipj=4 
    1371       ALLOCATE( ztab_e(jpiglo,ipj+kextj), znorthloc_e(  jpimax,ipj+kextj), & 
    1372      &                                    znorthgloio_e(jpimax,ipj+kextj,jpni) ) 
     1371      ALLOCATE(        ztab_e(jpiglo, 1-kextj:ipj+kextj)       ,       & 
     1372     &            znorthloc_e(jpimax, 1-kextj:ipj+kextj)       ,       & 
     1373     &          znorthgloio_e(jpimax, 1-kextj:ipj+kextj,jpni)    ) 
    13731374      ! 
    13741375      ztab_e(:,:)      = 0._wp 
    13751376      znorthloc_e(:,:) = 0._wp 
    13761377      ! 
    1377       ij = 0 
    1378       ! put the last ipj+kextj lines of pt2d into znorthloc_e  
    1379       DO jj = jpj - ipj + 1, jpj + kextj 
     1378      ij = 1 - kextj 
     1379      ! put the last ipj+2*kextj lines of pt2d into znorthloc_e  
     1380      DO jj = jpj - ipj + 1 - kextj , jpj + kextj 
     1381         znorthloc_e(1:jpi,ij)=pt2d(1:jpi,jj) 
    13801382         ij = ij + 1 
    1381          znorthloc_e(1:jpi,ij)=pt2d(1:jpi,jj) 
    13821383      END DO 
    13831384      ! 
    1384       itaille = jpimax * ( ipj + kextj ) 
    1385       CALL MPI_ALLGATHER( znorthloc_e(1,1)  , itaille, MPI_DOUBLE_PRECISION,    & 
    1386          &                znorthgloio_e(1,1,1), itaille, MPI_DOUBLE_PRECISION, ncomm_north, ierr ) 
     1385      itaille = jpimax * ( ipj + 2*kextj ) 
     1386      CALL MPI_ALLGATHER( znorthloc_e(1,1-kextj)    , itaille, MPI_DOUBLE_PRECISION,    & 
     1387         &                znorthgloio_e(1,1-kextj,1), itaille, MPI_DOUBLE_PRECISION,    & 
     1388         &                ncomm_north, ierr ) 
    13871389      ! 
    13881390      DO jr = 1, ndim_rank_north            ! recover the global north array 
     
    13911393         ilei = nleit (iproc) 
    13921394         iilb = nimppt(iproc) 
    1393          DO jj = 1, ipj+kextj 
     1395         DO jj = 1-kextj, ipj+kextj 
    13941396            DO ji = ildi, ilei 
    13951397               ztab_e(ji+iilb-1,jj) = znorthgloio_e(ji,jj,jr) 
     
    14001402      ! 2. North-Fold boundary conditions 
    14011403      ! ---------------------------------- 
    1402       CALL lbc_nfd( ztab_e(:,:), cd_type, psgn, kextj ) 
    1403  
    1404       ij = 0 
     1404      CALL lbc_nfd( ztab_e(:,1-kextj:ipj+kextj), cd_type, psgn, kextj ) 
     1405 
     1406      ij = 1 - kextj 
    14051407      !! Scatter back to pt2d 
    1406       DO jj = jpj - ipj + 1 , jpj + kextj 
    1407       ij  = ij +1 
     1408      DO jj = jpj - ipj + 1 - kextj , jpj + kextj 
    14081409         DO ji= 1, jpi 
    14091410            pt2d(ji,jj) = ztab_e(ji+nimpp-1,ij) 
    14101411         END DO 
     1412         ij  = ij +1 
    14111413      END DO 
    14121414      ! 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/SBC/geo2ocean.F90

    r9459 r9467  
    1111   !!---------------------------------------------------------------------- 
    1212!clem: these lines do not seem necessary anymore 
    13 !#if defined key_agrif 
    14 !!DIR$ OPTIMIZE:1        ! intel formulation 
     13#if defined key_agrif 
     14!DIR$ OPTIMIZE:1        ! intel formulation 
    1515!!DIR$ OPTIMIZE (-O 1)   ! cray formulation 
    16 !#endif 
     16#endif 
    1717   !!---------------------------------------------------------------------- 
    1818   !!   rot_rep       : Rotate the Repere: geographic grid <==> stretched coordinates grid 
Note: See TracChangeset for help on using the changeset viewer.