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 12816 for NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE – NEMO

Ignore:
Timestamp:
2020-04-25T14:32:42+02:00 (4 years ago)
Author:
smasson
Message:

Clem's branch: update with trunk, update with UKMO/NEMO_4.0.1_remove_0.1m_snow_test and add default restart for pond and lid

Location:
NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/DOM/dom_oce.F90

    r10068 r12816  
    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/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/DOM/dommsk.F90

    r11536 r12816  
    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/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/DYN/divhor.F90

    r12141 r12816  
    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/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/DYN/dynldf_lap_blp.F90

    r10425 r12816  
    7474            DO ji = fs_2, jpi   ! vector opt. 
    7575               !                                      ! ahm * e3 * curl  (computed from 1 to jpim1/jpjm1) 
    76 !!gm open question here : e3f  at before or now ?    probably now... 
    77 !!gm note that ahmf has already been multiplied by fmask 
    78                zcur(ji-1,jj-1) = ahmf(ji-1,jj-1,jk) * e3f_n(ji-1,jj-1,jk) * r1_e1e2f(ji-1,jj-1)       & 
     76               zcur(ji-1,jj-1) = ahmf(ji-1,jj-1,jk) * e3f_n(ji-1,jj-1,jk) * r1_e1e2f(ji-1,jj-1)       &   ! ahmf already * by fmask 
    7977                  &     * (  e2v(ji  ,jj-1) * pvb(ji  ,jj-1,jk) - e2v(ji-1,jj-1) * pvb(ji-1,jj-1,jk)  & 
    8078                  &        - e1u(ji-1,jj  ) * pub(ji-1,jj  ,jk) + e1u(ji-1,jj-1) * pub(ji-1,jj-1,jk)  ) 
    8179               !                                      ! ahm * div        (computed from 2 to jpi/jpj) 
    82 !!gm note that ahmt has already been multiplied by tmask 
    83                zdiv(ji,jj)     = ahmt(ji,jj,jk) * r1_e1e2t(ji,jj) / e3t_b(ji,jj,jk)                                         & 
     80               zdiv(ji,jj)     = ahmt(ji,jj,jk) * r1_e1e2t(ji,jj) / e3t_b(ji,jj,jk)                   &   ! ahmt already * by tmask 
    8481                  &     * (  e2u(ji,jj)*e3u_b(ji,jj,jk) * pub(ji,jj,jk) - e2u(ji-1,jj)*e3u_b(ji-1,jj,jk) * pub(ji-1,jj,jk)  & 
    8582                  &        + e1v(ji,jj)*e3v_b(ji,jj,jk) * pvb(ji,jj,jk) - e1v(ji,jj-1)*e3v_b(ji,jj-1,jk) * pvb(ji,jj-1,jk)  ) 
     
    8986         DO jj = 2, jpjm1                             ! - curl( curl) + grad( div ) 
    9087            DO ji = fs_2, fs_jpim1   ! vector opt. 
    91                pua(ji,jj,jk) = pua(ji,jj,jk) + zsign * (                                                 & 
     88               pua(ji,jj,jk) = pua(ji,jj,jk) + zsign * umask(ji,jj,jk) * (       &    ! * by umask is mandatory for dyn_ldf_blp use 
    9289                  &              - ( zcur(ji  ,jj) - zcur(ji,jj-1) ) * r1_e2u(ji,jj) / e3u_n(ji,jj,jk)   & 
    9390                  &              + ( zdiv(ji+1,jj) - zdiv(ji,jj  ) ) * r1_e1u(ji,jj)                     ) 
    9491                  ! 
    95                pva(ji,jj,jk) = pva(ji,jj,jk) + zsign * (                                                 & 
     92               pva(ji,jj,jk) = pva(ji,jj,jk) + zsign * vmask(ji,jj,jk) * (       &    ! * by vmask is mandatory for dyn_ldf_blp use 
    9693                  &                ( zcur(ji,jj  ) - zcur(ji-1,jj) ) * r1_e1v(ji,jj) / e3v_n(ji,jj,jk)   & 
    9794                  &              + ( zdiv(ji,jj+1) - zdiv(ji  ,jj) ) * r1_e2v(ji,jj)                     ) 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/DYN/dynspg_ts.F90

    r12206 r12816  
    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/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/DYN/dynvor.F90

    r11536 r12816  
    881881               DO ji = 1, jpim1 
    882882                  IF(    tmask(ji,jj+1,jk) + tmask(ji+1,jj+1,jk)              & 
    883                      & + tmask(ji,jj  ,jk) + tmask(ji+1,jj+1,jk) == 3._wp )   fmask(ji,jj,jk) = 1._wp 
     883                     & + tmask(ji,jj  ,jk) + tmask(ji+1,jj  ,jk) == 3._wp )   fmask(ji,jj,jk) = 1._wp 
    884884               END DO 
    885885            END DO 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/DYN/sshwzv.F90

    r11414 r12816  
    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/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/LBC/mppini.F90

    r11640 r12816  
    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/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/SBC/sbcwave.F90

    r11536 r12816  
    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.