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

Changeset 12737


Ignore:
Timestamp:
2020-04-10T19:55:11+02:00 (4 years ago)
Author:
jchanut
Message:

Fixes AGRIF reproductibility with land processors removal, i.e. #2240. Trunk is not concerned by this problem since nbondi/nbondj variables are not used anymore.

Location:
NEMO/releases/r4.0/r4.0-HEAD/src
Files:
10 edited

Legend:

Unmodified
Added
Removed
  • NEMO/releases/r4.0/r4.0-HEAD/src/NST/agrif_oce_interp.F90

    r10068 r12737  
    9696      i1 =  1   ;   i2 = nlci 
    9797      j1 =  1   ;   j2 = nlcj 
    98       IF( nbondj == -1 .OR. nbondj == 2 )   j1 = 2 + nbghostcells 
    99       IF( nbondj == +1 .OR. nbondj == 2 )   j2 = nlcj - nbghostcells - 1 
    100       IF( nbondi == -1 .OR. nbondi == 2 )   i1 = 2 + nbghostcells  
    101       IF( nbondi == +1 .OR. nbondi == 2 )   i2 = nlci - nbghostcells - 1 
     98      IF( l_Northedge )   j1 = 2 + nbghostcells 
     99      IF( l_Southedge )   j2 = nlcj - nbghostcells - 1 
     100      IF( l_Westedge )    i1 = 2 + nbghostcells  
     101      IF( l_Eastedge )    i2 = nlci - nbghostcells - 1 
    102102 
    103103      ! --- West --- ! 
    104       IF( nbondi == -1 .OR. nbondi == 2 ) THEN 
     104      IF( l_Westedge ) THEN 
    105105         ibdy1 = 2 
    106106         ibdy2 = 1+nbghostcells  
     
    173173 
    174174      ! --- East --- ! 
    175       IF( nbondi ==  1 .OR. nbondi == 2 ) THEN 
     175      IF( l_Eastedge ) THEN 
    176176         ibdy1 = nlci-1-nbghostcells 
    177177         ibdy2 = nlci-2  
     
    246246 
    247247      ! --- South --- ! 
    248       IF( nbondj == -1 .OR. nbondj == 2 ) THEN 
     248      IF ( l_Southedge ) THEN 
    249249         jbdy1 = 2 
    250250         jbdy2 = 1+nbghostcells  
     
    318318 
    319319      ! --- North --- ! 
    320       IF( nbondj ==  1 .OR. nbondj == 2 ) THEN 
     320      IF( l_Northedge ) THEN 
    321321         jbdy1 = nlcj-1-nbghostcells 
    322322         jbdy2 = nlcj-2  
     
    405405      IF( Agrif_Root() )   RETURN 
    406406      ! 
    407       IF((nbondi == -1).OR.(nbondi == 2)) THEN 
     407      IF( l_Westedge ) THEN 
    408408         DO jj=1,jpj 
    409409            va_e(2:nbghostcells+1,jj) = vbdy_w(1:nbghostcells,jj) * hvr_e(2:nbghostcells+1,jj) 
     
    416416      ENDIF 
    417417      ! 
    418       IF((nbondi == 1).OR.(nbondi == 2)) THEN 
     418      IF( l_Eastedge ) THEN 
    419419         DO jj=1,jpj 
    420420            va_e(nlci-nbghostcells:nlci-1,jj)   = vbdy_e(1:nbghostcells,jj) * hvr_e(nlci-nbghostcells:nlci-1,jj) 
     
    427427      ENDIF 
    428428      ! 
    429       IF((nbondj == -1).OR.(nbondj == 2)) THEN 
     429      IF ( l_Southedge ) THEN 
    430430         DO ji=1,jpi 
    431431            ua_e(ji,2:nbghostcells+1) = ubdy_s(ji,1:nbghostcells) * hur_e(ji,2:nbghostcells+1) 
     
    438438      ENDIF 
    439439      ! 
    440       IF((nbondj == 1).OR.(nbondj == 2)) THEN 
     440      IF ( l_Northedge ) THEN 
    441441         DO ji=1,jpi 
    442442            ua_e(ji,nlcj-nbghostcells:nlcj-1)   = ubdy_n(ji,1:nbghostcells) * hur_e(ji,nlcj-nbghostcells:nlcj-1) 
     
    516516      ! 
    517517      ! --- West --- ! 
    518       IF((nbondi == -1).OR.(nbondi == 2)) THEN 
     518      IF( l_Westedge ) THEN 
    519519         indx = 1+nbghostcells 
    520520         DO jj = 1, jpj 
     
    526526      ! 
    527527      ! --- East --- ! 
    528       IF((nbondi == 1).OR.(nbondi == 2)) THEN 
     528      IF( l_Eastedge ) THEN 
    529529         indx = nlci-nbghostcells 
    530530         DO jj = 1, jpj 
     
    536536      ! 
    537537      ! --- South --- ! 
    538       IF((nbondj == -1).OR.(nbondj == 2)) THEN 
     538      IF ( l_Southedge ) THEN 
    539539         indy = 1+nbghostcells 
    540540         DO jj = 2, indy 
     
    546546      ! 
    547547      ! --- North --- ! 
    548       IF((nbondj == 1).OR.(nbondj == 2)) THEN 
     548      IF ( l_Northedge ) THEN 
    549549         indy = nlcj-nbghostcells 
    550550         DO jj = indy, nlcj-1 
     
    571571      ! 
    572572      ! --- West --- ! 
    573       IF((nbondi == -1).OR.(nbondi == 2)) THEN 
     573      IF( l_Westedge ) THEN 
    574574         indx = 1+nbghostcells 
    575575         DO jj = 1, jpj 
     
    581581      ! 
    582582      ! --- East --- ! 
    583       IF((nbondi == 1).OR.(nbondi == 2)) THEN 
     583      IF( l_Eastedge ) THEN 
    584584         indx = nlci-nbghostcells 
    585585         DO jj = 1, jpj 
     
    591591      ! 
    592592      ! --- South --- ! 
    593       IF((nbondj == -1).OR.(nbondj == 2)) THEN 
     593      IF( l_Southedge ) THEN 
    594594         indy = 1+nbghostcells 
    595595         DO jj = 2, indy 
     
    601601      ! 
    602602      ! --- North --- ! 
    603       IF((nbondj == 1).OR.(nbondj == 2)) THEN 
     603      IF( l_Northedge ) THEN 
    604604         indy = nlcj-nbghostcells 
    605605         DO jj = indy, nlcj-1 
     
    722722            !  
    723723            ! Remove CORNERS 
    724             IF((nbondj == -1).OR.(nbondj == 2)) jmin = 2 + nbghostcells 
    725             IF((nbondj == +1).OR.(nbondj == 2)) jmax = nlcj - nbghostcells - 1 
    726             IF((nbondi == -1).OR.(nbondi == 2)) imin = 2 + nbghostcells 
    727             IF((nbondi == +1).OR.(nbondi == 2)) imax = nlci - nbghostcells - 1       
     724            IF( l_Southedge ) jmin = 2 + nbghostcells 
     725            IF( l_Northedge ) jmax = nlcj - nbghostcells - 1 
     726            IF( l_Westedge ) imin = 2 + nbghostcells 
     727            IF( l_Eastedge ) imax = nlci - nbghostcells - 1       
    728728            ! 
    729729            IF( eastern_side ) THEN 
  • NEMO/releases/r4.0/r4.0-HEAD/src/NST/agrif_oce_sponge.F90

    r10425 r12737  
    109109 
    110110         ! --- West --- ! 
    111          IF( (nbondi == -1) .OR. (nbondi == 2) ) THEN 
     111         IF( l_Westedge ) THEN 
    112112            ind1 = 1+nbghostcells 
    113113            ind2 = 1+nbghostcells + ispongearea  
     
    120120 
    121121         ! --- East --- ! 
    122          IF( (nbondi == 1) .OR. (nbondi == 2) ) THEN 
     122         IF( l_Eastedge ) THEN 
    123123            ind1 = nlci - nbghostcells - ispongearea 
    124124            ind2 = nlci - nbghostcells 
     
    131131 
    132132         ! --- South --- ! 
    133          IF( (nbondj == -1) .OR. (nbondj == 2) ) THEN 
     133         IF( l_Southedge ) THEN 
    134134            ind1 = 1+nbghostcells 
    135135            ind2 = 1+nbghostcells + ispongearea 
     
    142142 
    143143         ! --- North --- ! 
    144          IF( (nbondj == 1) .OR. (nbondj == 2) ) THEN 
     144         IF( l_Northedge ) THEN 
    145145            ind1 = nlcj - nbghostcells - ispongearea 
    146146            ind2 = nlcj - nbghostcells 
     
    454454 
    455455         jmax = j2-1 
    456          IF ((nbondj == 1).OR.(nbondj == 2)) jmax = MIN(jmax,nlcj-nbghostcells-2)   ! North 
     456         IF ( l_Northedge ) jmax = MIN(jmax,nlcj-nbghostcells-2)   ! North 
    457457 
    458458         DO jj = j1+1, jmax 
     
    580580 
    581581         imax = i2 - 1 
    582          IF ((nbondi == 1).OR.(nbondi == 2))   imax = MIN(imax,nlci-nbghostcells-2)   ! East 
     582         IF ( l_Eastedge )   imax = MIN(imax,nlci-nbghostcells-2)   ! East 
    583583 
    584584         DO jj = j1+1, j2 
  • NEMO/releases/r4.0/r4.0-HEAD/src/NST/agrif_top_interp.F90

    r10068 r12737  
    136136            !  
    137137            ! Remove CORNERS 
    138             IF((nbondj == -1).OR.(nbondj == 2)) jmin = 2 + nbghostcells 
    139             IF((nbondj == +1).OR.(nbondj == 2)) jmax = nlcj - nbghostcells - 1 
    140             IF((nbondi == -1).OR.(nbondi == 2)) imin = 2 + nbghostcells 
    141             IF((nbondi == +1).OR.(nbondi == 2)) imax = nlci - nbghostcells - 1       
     138            IF( l_Southedge ) jmin = 2 + nbghostcells 
     139            IF( l_Northedge ) jmax = nlcj - nbghostcells - 1 
     140            IF( l_Westedge ) imin = 2 + nbghostcells 
     141            IF( l_Eastedge ) imax = nlci - nbghostcells - 1       
    142142            ! 
    143143            IF( eastern_side ) THEN 
  • NEMO/releases/r4.0/r4.0-HEAD/src/OCE/DOM/dom_oce.F90

    r10068 r12737  
    7474   !                                !  = 7 bi-cyclic East-West AND North-South 
    7575   LOGICAL, PUBLIC ::   l_Iperio, l_Jperio   !   should we explicitely take care I/J periodicity  
     76   LOGICAL, PUBLIC ::   l_Westedge, l_Eastedge, l_Northedge, l_Southedge ! flag to detect global domain edges 
     77                                                                         ! on local domain (needed for AGRIF) 
    7678 
    7779   !                                 !  domain MPP decomposition parameters 
  • NEMO/releases/r4.0/r4.0-HEAD/src/OCE/DOM/dommsk.F90

    r11536 r12737  
    273273#if defined key_agrif  
    274274            IF( .NOT. AGRIF_Root() ) THEN  
    275                IF ((nbondi ==  1).OR.(nbondi == 2)) fmask(nlci-1 , :     ,jk) = 0.e0      ! east  
    276                IF ((nbondi == -1).OR.(nbondi == 2)) fmask(1      , :     ,jk) = 0.e0      ! west  
    277                IF ((nbondj ==  1).OR.(nbondj == 2)) fmask(:      ,nlcj-1 ,jk) = 0.e0      ! north  
    278                IF ((nbondj == -1).OR.(nbondj == 2)) fmask(:      ,1      ,jk) = 0.e0      ! south  
     275               IF ( l_Eastedge ) fmask(nlci-1 , :     ,jk) = 0.e0      ! east  
     276               IF ( l_Westedge ) fmask(1      , :     ,jk) = 0.e0      ! west  
     277               IF ( l_Northedge ) fmask(:      ,nlcj-1 ,jk) = 0.e0      ! north  
     278               IF ( l_Southedge ) fmask(:      ,1      ,jk) = 0.e0      ! south  
    279279            ENDIF  
    280280#endif  
  • NEMO/releases/r4.0/r4.0-HEAD/src/OCE/DYN/divhor.F90

    r12141 r12737  
    8888#if defined key_agrif 
    8989      IF( .NOT. Agrif_Root() ) THEN 
    90          IF( nbondi == -1 .OR. nbondi == 2 )   hdivn(   2   ,  :   ,:) = 0._wp      ! west 
    91          IF( nbondi ==  1 .OR. nbondi == 2 )   hdivn( nlci-1,  :   ,:) = 0._wp      ! east 
    92          IF( nbondj == -1 .OR. nbondj == 2 )   hdivn(   :   ,  2   ,:) = 0._wp      ! south 
    93          IF( nbondj ==  1 .OR. nbondj == 2 )   hdivn(   :   ,nlcj-1,:) = 0._wp      ! north 
     90         IF( l_Westedge )   hdivn(   2   ,  :   ,:) = 0._wp      ! west 
     91         IF( l_Eastedge )   hdivn( nlci-1,  :   ,:) = 0._wp      ! east 
     92         IF( l_Southedge )  hdivn(   :   ,  2   ,:) = 0._wp      ! south 
     93         IF( l_Northedge )  hdivn(   :   ,nlcj-1,:) = 0._wp      ! north 
    9494      ENDIF 
    9595#endif 
  • NEMO/releases/r4.0/r4.0-HEAD/src/OCE/DYN/dynspg_ts.F90

    r12206 r12737  
    487487         ! Set fluxes during predictor step to ensure volume conservation 
    488488         IF( .NOT.Agrif_Root() .AND. ln_bt_fw ) THEN 
    489             IF((nbondi == -1).OR.(nbondi == 2)) THEN 
     489            IF( l_Westedge ) THEN 
    490490               DO jj = 1, jpj 
    491491                  zhU(2:nbghostcells+1,jj) = ubdy_w(1:nbghostcells,jj) * e2u(2:nbghostcells+1,jj) 
     
    493493               END DO 
    494494            ENDIF 
    495             IF((nbondi ==  1).OR.(nbondi == 2)) THEN 
     495            IF( l_Eastedge ) THEN 
    496496               DO jj=1,jpj 
    497497                  zhU(nlci-nbghostcells-1:nlci-2,jj) = ubdy_e(1:nbghostcells,jj) * e2u(nlci-nbghostcells-1:nlci-2,jj) 
     
    499499               END DO 
    500500            ENDIF 
    501             IF((nbondj == -1).OR.(nbondj == 2)) THEN 
     501            IF( l_Southedge ) THEN 
    502502               DO ji=1,jpi 
    503503                  zhV(ji,2:nbghostcells+1) = vbdy_s(ji,1:nbghostcells) * e1v(ji,2:nbghostcells+1) 
     
    505505               END DO 
    506506            ENDIF 
    507             IF((nbondj ==  1).OR.(nbondj == 2)) THEN 
     507            IF( l_Northedge ) THEN 
    508508               DO ji=1,jpi 
    509509                  zhV(ji,nlcj-nbghostcells-1:nlcj-2) = vbdy_n(ji,1:nbghostcells) * e1v(ji,nlcj-nbghostcells-1:nlcj-2) 
  • NEMO/releases/r4.0/r4.0-HEAD/src/OCE/DYN/sshwzv.F90

    r11414 r12737  
    203203#if defined key_agrif  
    204204      IF( .NOT. AGRIF_Root() ) THEN  
    205          IF ((nbondi ==  1).OR.(nbondi == 2)) wn(nlci-1 , :     ,:) = 0.e0      ! east  
    206          IF ((nbondi == -1).OR.(nbondi == 2)) wn(2      , :     ,:) = 0.e0      ! west  
    207          IF ((nbondj ==  1).OR.(nbondj == 2)) wn(:      ,nlcj-1 ,:) = 0.e0      ! north  
    208          IF ((nbondj == -1).OR.(nbondj == 2)) wn(:      ,2      ,:) = 0.e0      ! south  
     205         IF ( l_Eastedge ) wn(nlci-1 , :     ,:) = 0.e0      ! east  
     206         IF ( l_Westedge ) wn(2      , :     ,:) = 0.e0      ! west  
     207         IF ( l_Northedge ) wn(:      ,nlcj-1 ,:) = 0.e0      ! north  
     208         IF ( l_Southedge ) wn(:      ,2      ,:) = 0.e0      ! south  
    209209      ENDIF  
    210210#endif  
  • NEMO/releases/r4.0/r4.0-HEAD/src/OCE/LBC/mppini.F90

    r11640 r12737  
    9090      l_Jperio = jpnj == 1 .AND. (jperio == 2 .OR. jperio == 7) 
    9191      ! 
     92      ! Set flags to detect global domain edges for AGRIF 
     93      l_Westedge = .true. ; l_Eastedge = .true. ; l_Northedge = .true.; l_Southedge = .true. 
     94      ! 
    9295      IF(lwp) THEN 
    9396         WRITE(numout,*) 
     
    162165      INTEGER, ALLOCATABLE, DIMENSION(:,:) ::   ilej, ildj, ioso, iowe         !  -     - 
    163166      LOGICAL, ALLOCATABLE, DIMENSION(:,:) ::   llisoce                        !  -     - 
     167      LOGICAL, ALLOCATABLE, DIMENSION(:,:) ::   lliswest, lliseast, llisnorth, llissouth  !  -     - 
    164168      NAMELIST/nambdy/ ln_bdy, nb_bdy, ln_coords_file, cn_coords_file,           & 
    165169           &             ln_mask_file, cn_mask_file, cn_dyn2d, nn_dyn2d_dta,     & 
     
    331335         &       ilei(jpni,jpnj), ildi(jpni,jpnj), iono(jpni,jpnj), ioea(jpni,jpnj),   & 
    332336         &       ilej(jpni,jpnj), ildj(jpni,jpnj), ioso(jpni,jpnj), iowe(jpni,jpnj),   & 
     337#if defined key_agrif 
     338                 lliswest(jpni,jpnj), lliseast(jpni,jpnj),  &  
     339         &       llisnorth(jpni,jpnj),llissouth(jpni,jpnj), & 
     340#endif 
    333341         &       STAT=ierr ) 
    334342      CALL mpp_sum( 'mppini', ierr ) 
     
    343351         IF( ln_use_jattr )   CALL ctl_stop( 'STOP', 'mpp_init:Agrif children requires ln_use_jattr = .false. ' ) 
    344352      ENDIF 
     353      lliswest(:,:) = .false. ; lliseast(:,:) = .false. ; llisnorth(:,:) = .false. ; llissouth(:,:) = .false. 
    345354#endif 
    346355      ! 
     
    430439         ENDIF 
    431440         ! 
     441#if defined key_agrif 
     442         IF ((ibondi(ii,ij) ==  1).OR.(ibondi(ii,ij) == 2)) lliseast(ii,ij)  = .true.      ! east  
     443         IF ((ibondi(ii,ij) == -1).OR.(ibondi(ii,ij) == 2)) lliswest(ii,ij)  = .true.      ! west  
     444         IF ((ibondj(ii,ij) ==  1).OR.(ibondj(ii,ij) == 2)) llisnorth(ii,ij) = .true.      ! north  
     445         IF ((ibondj(ii,ij) == -1).OR.(ibondj(ii,ij) == 2)) llissouth(ii,ij) = .true.      ! south  
     446#endif 
    432447      END DO 
    433  
    434448      ! 4. deal with land subdomains 
    435449      ! ---------------------------- 
     
    601615      ! Suppress once vertical online interpolation is ok 
    602616!!$      IF(.NOT.Agrif_Root())   jpkglo = Agrif_Parent( jpkglo ) 
     617      l_Westedge  = lliswest(ii,ij) 
     618      l_Eastedge  = lliseast(ii,ij) 
     619      l_Northedge = llisnorth(ii,ij) 
     620      l_Southedge = llissouth(ii,ij)  
    603621#endif 
    604622      jpim1 = jpi-1                                            ! inner domain indices 
     
    716734         &       ilci, ilcj, ilei, ilej, ildi, ildj,              & 
    717735         &       iono, ioea, ioso, iowe, llisoce) 
     736#if defined key_agrif 
     737      DEALLOCATE(lliswest, lliseast, llisnorth, llissouth) 
     738#endif 
    718739      ! 
    719740    END SUBROUTINE mpp_init 
  • NEMO/releases/r4.0/r4.0-HEAD/src/OCE/SBC/sbcwave.F90

    r11536 r12737  
    233233#if defined key_agrif 
    234234      IF( .NOT. Agrif_Root() ) THEN 
    235          IF( nbondi == -1 .OR. nbondi == 2 )   ze3divh( 2:nbghostcells+1,:        ,:) = 0._wp      ! west 
    236          IF( nbondi ==  1 .OR. nbondi == 2 )   ze3divh( nlci-nbghostcells:nlci-1,:,:) = 0._wp      ! east 
    237          IF( nbondj == -1 .OR. nbondj == 2 )   ze3divh( :,2:nbghostcells+1        ,:) = 0._wp      ! south 
    238          IF( nbondj ==  1 .OR. nbondj == 2 )   ze3divh( :,nlcj-nbghostcells:nlcj-1,:) = 0._wp      ! north 
     235         IF( l_Westedge )    ze3divh( 2:nbghostcells+1,:        ,:) = 0._wp      ! west 
     236         IF( l_Eastedge )    ze3divh( nlci-nbghostcells:nlci-1,:,:) = 0._wp      ! east 
     237         IF( l_Southedge )   ze3divh( :,2:nbghostcells+1        ,:) = 0._wp      ! south 
     238         IF( l_Northedge )   ze3divh( :,nlcj-nbghostcells:nlcj-1,:) = 0._wp      ! north 
    239239      ENDIF 
    240240#endif 
Note: See TracChangeset for help on using the changeset viewer.