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 12807 for NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/DOM – NEMO

Ignore:
Timestamp:
2020-04-23T15:14:45+02:00 (4 years ago)
Author:
smasson
Message:

Extra_Halo: input file only over inner domain + new variables names, see #2366

Location:
NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/DOM
Files:
5 edited
1 moved

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/DOM/dom_oce.F90

    r12586 r12807  
    7575   !                                 !  domain MPP decomposition parameters 
    7676   INTEGER             , PUBLIC ::   nimpp, njmpp     !: i- & j-indexes for mpp-subdomain left bottom 
    77    INTEGER             , PUBLIC ::   nreci, nrecj     !: overlap region in i and j 
    7877   INTEGER             , PUBLIC ::   nproc            !: number for local processor 
    7978   INTEGER             , PUBLIC ::   narea            !: number for local area 
     
    8584 
    8685   INTEGER, PUBLIC ::   npolj             !: north fold mark (0, 3 or 4) 
    87    INTEGER, PUBLIC ::   nlci, nldi, nlei  !: i-dimensions of the local subdomain and its first and last indoor indices 
    88    INTEGER, PUBLIC ::   nlcj, nldj, nlej  !: i-dimensions of the local subdomain and its first and last indoor indices 
    8986   INTEGER, PUBLIC ::   noea, nowe        !: index of the local neighboring processors in 
    9087   INTEGER, PUBLIC ::   noso, nono        !: east, west, south and north directions 
     
    9794   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   mj0, mj1   !: global ==> local  domain j-index (mj0=1 and mj1=0 if the global index 
    9895   !                                                                !                                             is not in the local domain) 
    99    INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   nimppt, njmppt   !: i-, j-indexes for each processor 
    100    INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   ibonit, ibonjt   !: i-, j- processor neighbour existence 
    101    INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   nlcit , nlcjt    !: dimensions of every subdomain 
    102    INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   nldit , nldjt    !: first, last indoor index for each i-domain 
    103    INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   nleit , nlejt    !: first, last indoor index for each j-domain 
    104    INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: nfiimpp, nfipproc, nfilcit 
     96   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::    nimppt, njmppt   !: i-, j-indexes for each processor 
     97   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::    ibonit, ibonjt   !: i-, j- processor neighbour existence 
     98   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::    jpiall,  jpjall   !: dimensions of all subdomain 
     99   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   nis0all, njs0all   !: first, last indoor index for all i-subdomain 
     100   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   nie0all, nje0all   !: first, last indoor index for all j-subdomain 
     101   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: nfiimpp, nfipproc, nfijpit 
    105102 
    106103   !!---------------------------------------------------------------------- 
     
    185182   REAL(wp), PUBLIC, POINTER, SAVE, DIMENSION(:,:,:) :: tmask, umask, vmask, wmask  !: land/ocean mask at T-, U-, V-pts 
    186183   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:), TARGET :: wumask, wvmask        !: land/ocean mask at WT-, WU- and WV-pts 
    187  
    188    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   tpol, fpol          !: north fold mask (jperio= 3 or 4) 
    189184 
    190185   !!---------------------------------------------------------------------- 
     
    250245      ALLOCATE( mig(jpi), mjg(jpj), STAT=ierr(1) ) 
    251246         ! 
    252       ALLOCATE( mi0(jpiglo)   , mi1 (jpiglo),  mj0(jpjglo)   , mj1 (jpjglo) ,     & 
    253          &      tpol(jpiglo)  , fpol(jpiglo)                                , STAT=ierr(2) ) 
     247      ALLOCATE( mi0(jpiglo), mi1(jpiglo), mj0(jpjglo), mj1(jpjglo), STAT=ierr(2) ) 
    254248         ! 
    255249      ALLOCATE( glamt(jpi,jpj) ,    glamu(jpi,jpj) ,  glamv(jpi,jpj) ,  glamf(jpi,jpj) ,     & 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/DOM/domhgr.F90

    r12738 r12807  
    3131   USE iom            ! I/O library 
    3232   USE lib_mpp        ! MPP library 
     33   USE lbclnk         ! lateal boundary condition / mpp exchanges 
    3334   USE timing         ! Timing 
    3435 
     
    199200      CALL iom_get( inum, jpdom_global, 'gphif', pphif, cd_type = 'F', psgn = 1._wp ) 
    200201      ! 
    201       CALL iom_get( inum, jpdom_global, 'e1t'  , pe1t , cd_type = 'T', psgn = 1._wp ) 
    202       CALL iom_get( inum, jpdom_global, 'e1u'  , pe1u , cd_type = 'U', psgn = 1._wp ) 
    203       CALL iom_get( inum, jpdom_global, 'e1v'  , pe1v , cd_type = 'V', psgn = 1._wp ) 
    204       CALL iom_get( inum, jpdom_global, 'e1f'  , pe1f , cd_type = 'F', psgn = 1._wp ) 
    205       ! 
    206       CALL iom_get( inum, jpdom_global, 'e2t'  , pe2t , cd_type = 'T', psgn = 1._wp ) 
    207       CALL iom_get( inum, jpdom_global, 'e2u'  , pe2u , cd_type = 'U', psgn = 1._wp ) 
    208       CALL iom_get( inum, jpdom_global, 'e2v'  , pe2v , cd_type = 'V', psgn = 1._wp ) 
    209       CALL iom_get( inum, jpdom_global, 'e2f'  , pe2f , cd_type = 'F', psgn = 1._wp ) 
     202      CALL iom_get( inum, jpdom_global, 'e1t'  , pe1t , cd_type = 'T', psgn = 1._wp, kfill = jpfillcopy ) 
     203      CALL iom_get( inum, jpdom_global, 'e1u'  , pe1u , cd_type = 'U', psgn = 1._wp, kfill = jpfillcopy ) 
     204      CALL iom_get( inum, jpdom_global, 'e1v'  , pe1v , cd_type = 'V', psgn = 1._wp, kfill = jpfillcopy ) 
     205      CALL iom_get( inum, jpdom_global, 'e1f'  , pe1f , cd_type = 'F', psgn = 1._wp, kfill = jpfillcopy ) 
     206      ! 
     207      CALL iom_get( inum, jpdom_global, 'e2t'  , pe2t , cd_type = 'T', psgn = 1._wp, kfill = jpfillcopy ) 
     208      CALL iom_get( inum, jpdom_global, 'e2u'  , pe2u , cd_type = 'U', psgn = 1._wp, kfill = jpfillcopy ) 
     209      CALL iom_get( inum, jpdom_global, 'e2v'  , pe2v , cd_type = 'V', psgn = 1._wp, kfill = jpfillcopy ) 
     210      CALL iom_get( inum, jpdom_global, 'e2f'  , pe2f , cd_type = 'F', psgn = 1._wp, kfill = jpfillcopy ) 
    210211      ! 
    211212      IF(  iom_varid( inum, 'ff_f', ldstop = .FALSE. ) > 0  .AND.  & 
     
    221222      IF( iom_varid( inum, 'e1e2u', ldstop = .FALSE. ) > 0 ) THEN 
    222223         IF(lwp) WRITE(numout,*) '           e1e2u & e1e2v read in ', TRIM( cn_domcfg ), ' file' 
    223          CALL iom_get( inum, jpdom_global, 'e1e2u', pe1e2u, cd_type = 'U', psgn = 1._wp ) 
    224          CALL iom_get( inum, jpdom_global, 'e1e2v', pe1e2v, cd_type = 'V', psgn = 1._wp ) 
     224         CALL iom_get( inum, jpdom_global, 'e1e2u', pe1e2u, cd_type = 'U', psgn = 1._wp, kfill = jpfillcopy ) 
     225         CALL iom_get( inum, jpdom_global, 'e1e2v', pe1e2v, cd_type = 'V', psgn = 1._wp, kfill = jpfillcopy ) 
    225226         ke1e2u_v = 1 
    226227      ELSE 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/DOM/dommsk.F90

    r12738 r12807  
    2525   USE oce            ! ocean dynamics and tracers 
    2626   USE dom_oce        ! ocean space and time domain 
     27   USE domutl         !  
    2728   USE usrdef_fmask   ! user defined fmask 
    2829   USE bdy_oce        ! open boundary 
     
    8889      ! 
    8990      INTEGER  ::   ji, jj, jk     ! dummy loop indices 
    90       INTEGER  ::   iif, iil       ! local integers 
    91       INTEGER  ::   ijf, ijl       !   -       - 
    9291      INTEGER  ::   iktop, ikbot   !   -       - 
    9392      INTEGER  ::   ios, inum 
     
    131130      ! 
    132131      tmask(:,:,:) = 0._wp 
    133       DO_2D_11_11 
     132      DO_2D_00_00 
    134133         iktop = k_top(ji,jj) 
    135134         ikbot = k_bot(ji,jj) 
    136135         IF( iktop /= 0 ) THEN       ! water in the column 
    137             tmask(ji,jj,iktop:ikbot  ) = 1._wp 
     136            tmask(ji,jj,iktop:ikbot) = 1._wp 
    138137         ENDIF 
    139138      END_2D 
    140139      ! 
    141       ! the following call is mandatory 
     140      ! the following is mandatory 
    142141      ! it masks boundaries (bathy=0) where needed depending on the configuration (closed, periodic...)   
    143       CALL lbc_lnk( 'dommsk', tmask  , 'T', 1._wp )      ! Lateral boundary conditions 
     142      IF( .NOT. (nbondj == 1 .OR. nbondj == 0 .OR. l_Jperio) ) THEN 
     143         tmask(mi0(  1 ):mi1(jpiglo),mj0(Njs0):mj1(Njs0  ),:) = 0._wp   ! line   number Njs0 at 0 
     144      ENDIF 
     145      IF( .NOT. (nbondi == 1 .OR. nbondi == 0 .OR. l_Iperio) ) THEN 
     146         tmask(mi0(Nis0):mi1(  Nis0),mj0(  1 ):mj1(jpjglo),:) = 0._wp   ! column number Nis0 at 0 
     147      ENDIF 
     148      CALL lbc_lnk( 'dommsk', tmask, 'T', 1._wp )      ! Lateral boundary conditions 
    144149 
    145150     ! Mask corrections for bdy (read in mppini2) 
     
    186191      END DO 
    187192 
    188  
    189193      ! Ocean/land column mask at t-, u-, and v-points   (i.e. at least 1 wet cell in the vertical) 
    190194      ! ---------------------------------------------- 
     
    193197      ssvmask(:,:) = MAXVAL( vmask(:,:,:), DIM=3 ) 
    194198 
    195  
    196199      ! Interior domain mask  (used for global sum) 
    197200      ! -------------------- 
    198201      ! 
    199       iif = nn_hls   ;   iil = nlci - nn_hls + 1 
    200       ijf = nn_hls   ;   ijl = nlcj - nn_hls + 1 
    201       ! 
    202       !                          ! halo mask : 0 on the halo and 1 elsewhere 
    203       tmask_h(:,:) = 1._wp                   
    204       tmask_h( 1 :iif,   :   ) = 0._wp      ! first columns 
    205       tmask_h(iil:jpi,   :   ) = 0._wp      ! last  columns (including mpp extra columns) 
    206       tmask_h(   :   , 1 :ijf) = 0._wp      ! first rows 
    207       tmask_h(   :   ,ijl:jpj) = 0._wp      ! last  rows (including mpp extra rows) 
    208       ! 
    209       !                          ! north fold mask 
    210       tpol(1:jpiglo) = 1._wp  
    211       fpol(1:jpiglo) = 1._wp 
    212       IF( jperio == 3 .OR. jperio == 4 ) THEN      ! T-point pivot 
    213          tpol(jpiglo/2+1:jpiglo) = 0._wp 
    214          fpol(     1    :jpiglo) = 0._wp 
    215          IF( mjg(nlej) == jpjglo ) THEN                  ! only half of the nlcj-1 row for tmask_h 
    216             DO ji = iif+1, iil-1 
    217                tmask_h(ji,nlej-1) = tmask_h(ji,nlej-1) * tpol(mig(ji)) 
    218             END DO 
    219          ENDIF 
    220       ENDIF 
    221       ! 
    222       IF( jperio == 5 .OR. jperio == 6 ) THEN      ! F-point pivot 
    223          tpol(     1    :jpiglo) = 0._wp 
    224          fpol(jpiglo/2+1:jpiglo) = 0._wp 
    225       ENDIF 
     202      CALL dom_uniq( tmask_h, 'T' ) 
    226203      ! 
    227204      !                          ! interior mask : 2D ocean mask x halo mask  
    228205      tmask_i(:,:) = ssmask(:,:) * tmask_h(:,:) 
    229  
    230206 
    231207      ! Lateral boundary conditions on velocity (modify fmask) 
     
    261237#if defined key_agrif  
    262238            IF( .NOT. AGRIF_Root() ) THEN  
    263                IF ((nbondi ==  1).OR.(nbondi == 2)) fmask(nlci-1 , :     ,jk) = 0.e0      ! east  
    264                IF ((nbondi == -1).OR.(nbondi == 2)) fmask(1      , :     ,jk) = 0.e0      ! west  
    265                IF ((nbondj ==  1).OR.(nbondj == 2)) fmask(:      ,nlcj-1 ,jk) = 0.e0      ! north  
    266                IF ((nbondj == -1).OR.(nbondj == 2)) fmask(:      ,1      ,jk) = 0.e0      ! south  
     239               IF ((nbondi ==  1).OR.(nbondi == 2)) fmask(jpi-1, :   ,jk) = 0.e0      ! east  
     240               IF ((nbondi == -1).OR.(nbondi == 2)) fmask(1    , :   ,jk) = 0.e0      ! west  
     241               IF ((nbondj ==  1).OR.(nbondj == 2)) fmask(:    ,jpj-1,jk) = 0.e0      ! north  
     242               IF ((nbondj == -1).OR.(nbondj == 2)) fmask(:    ,1    ,jk) = 0.e0      ! south  
    267243            ENDIF  
    268244#endif  
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/DOM/domutl.F90

    r12766 r12807  
    1 MODULE domngb 
     1MODULE domutl 
    22   !!====================================================================== 
    3    !!                       ***  MODULE  domngb  *** 
    4    !! Grid search:  find the closest grid point from a given on/lat position 
     3   !!                       ***  MODULE  domutl  *** 
     4   !! Grid utilities: 
    55   !!====================================================================== 
    6    !! History : 3.2  !  2009-11  (S. Masson)  Original code 
     6   !! History : 4.2  !  2020-04  (S. Masson)  Original code 
    77   !!---------------------------------------------------------------------- 
    88 
    99   !!---------------------------------------------------------------------- 
    1010   !!   dom_ngb       : find the closest grid point from a given lon/lat position 
     11   !!   dom_uniq      : identify unique point of a grid (TUVF) 
    1112   !!---------------------------------------------------------------------- 
     13   ! 
    1214   USE dom_oce        ! ocean space and time domain 
    1315   ! 
    1416   USE in_out_manager ! I/O manager 
     17   USE lbclnk         ! ocean lateral boundary conditions (or mpp link) 
    1518   USE lib_mpp        ! for mppsum 
    1619 
     
    1821   PRIVATE 
    1922 
    20    PUBLIC   dom_ngb   ! routine called in iom.F90 module 
     23   PUBLIC dom_ngb    ! routine called in iom.F90 module 
     24   PUBLIC dom_uniq   ! Called by dommsk and domwri 
    2125 
    2226   !!---------------------------------------------------------------------- 
    23    !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     27   !! NEMO/OCE 4.2 , NEMO Consortium (2020) 
    2428   !! $Id$  
    2529   !! Software governed by the CeCILL license (see ./LICENSE) 
     
    4751      !!-------------------------------------------------------------------- 
    4852      ! 
    49       zmask(:,:) = 0._wp 
    5053      ik = 1 
    5154      IF ( PRESENT(kkk) ) ik=kkk 
     55      ! 
     56      CALL dom_uniq(zmask,cdgrid) 
     57      ! 
    5258      SELECT CASE( cdgrid ) 
    53       CASE( 'U' )  ; zglam(:,:) = glamu(:,:) ; zgphi(:,:) = gphiu(:,:) ; zmask(nldi:nlei,nldj:nlej) = umask(nldi:nlei,nldj:nlej,ik) 
    54       CASE( 'V' )  ; zglam(:,:) = glamv(:,:) ; zgphi(:,:) = gphiv(:,:) ; zmask(nldi:nlei,nldj:nlej) = vmask(nldi:nlei,nldj:nlej,ik) 
    55       CASE( 'F' )  ; zglam(:,:) = glamf(:,:) ; zgphi(:,:) = gphif(:,:) ; zmask(nldi:nlei,nldj:nlej) = fmask(nldi:nlei,nldj:nlej,ik) 
    56       CASE DEFAULT ; zglam(:,:) = glamt(:,:) ; zgphi(:,:) = gphit(:,:) ; zmask(nldi:nlei,nldj:nlej) = tmask(nldi:nlei,nldj:nlej,ik) 
     59      CASE( 'U' )    ;   zglam(:,:) = glamu(:,:)   ;   zgphi(:,:) = gphiu(:,:)   ;   zmask(:,:) = zmask(:,:) * umask(:,:,ik) 
     60      CASE( 'V' )    ;   zglam(:,:) = glamv(:,:)   ;   zgphi(:,:) = gphiv(:,:)   ;   zmask(:,:) = zmask(:,:) * vmask(:,:,ik) 
     61      CASE( 'F' )    ;   zglam(:,:) = glamf(:,:)   ;   zgphi(:,:) = gphif(:,:)   ;   zmask(:,:) = zmask(:,:) * fmask(:,:,ik) 
     62      CASE DEFAULT   ;   zglam(:,:) = glamt(:,:)   ;   zgphi(:,:) = gphit(:,:)   ;   zmask(:,:) = zmask(:,:) * tmask(:,:,ik) 
    5763      END SELECT 
    58  
     64      ! 
    5965      zlon       = MOD( plon       + 720., 360. )                                     ! plon between    0 and 360 
    6066      zglam(:,:) = MOD( zglam(:,:) + 720., 360. )                                     ! glam between    0 and 360 
     
    7783   END SUBROUTINE dom_ngb 
    7884 
     85 
     86   SUBROUTINE dom_uniq( puniq, cdgrd ) 
     87      !!---------------------------------------------------------------------- 
     88      !!                  ***  ROUTINE dom_uniq  *** 
     89      !!                    
     90      !! ** Purpose :   identify unique point of a grid (TUVF) 
     91      !! 
     92      !! ** Method  :   1) aplly lbc_lnk on an array with different values for each element 
     93      !!                2) check which elements have been changed 
     94      !!---------------------------------------------------------------------- 
     95      CHARACTER(len=1)        , INTENT(in   ) ::   cdgrd   !  
     96      REAL(wp), DIMENSION(:,:), INTENT(inout) ::   puniq   !  
     97      ! 
     98      REAL(wp)                       ::  zshift   ! shift value link to the process number 
     99      INTEGER                        ::  ji       ! dummy loop indices 
     100      LOGICAL , DIMENSION(jpi,jpj,1) ::   lluniq  ! store whether each point is unique or not 
     101      REAL(wp), DIMENSION(jpi,jpj  ) ::   ztstref 
     102      !!---------------------------------------------------------------------- 
     103      ! 
     104      ! build an array with different values for each element  
     105      ! in mpp: make sure that these values are different even between process 
     106      ! -> apply a shift value according to the process number 
     107      zshift = jpimax * jpjmax * ( narea - 1 ) 
     108      ztstref(:,:) = RESHAPE( (/ (zshift + REAL(ji,wp), ji = 1, jpi*jpj) /), (/ jpi, jpj /) ) 
     109      ! 
     110      puniq(:,:) = ztstref(:,:)                    ! default definition 
     111      CALL lbc_lnk( 'domwri', puniq, cdgrd, 1. )   ! apply boundary conditions 
     112      lluniq(:,:,1) = puniq(:,:) == ztstref(:,:)   ! check which values have not been changed  
     113      ! 
     114      puniq(:,:) = REAL( COUNT( lluniq(:,:,:), dim = 3 ), wp ) 
     115      ! 
     116   END SUBROUTINE dom_uniq 
     117    
    79118   !!====================================================================== 
    80 END MODULE domngb 
     119END MODULE domutl 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/DOM/domwri.F90

    r12377 r12807  
    1313   !!---------------------------------------------------------------------- 
    1414   !!   dom_wri        : create and write mesh and mask file(s) 
    15    !!   dom_uniq       : identify unique point of a grid (TUVF) 
    1615   !!   dom_stiff      : diagnose maximum grid stiffness/hydrostatic consistency (s-coordinate) 
    1716   !!---------------------------------------------------------------------- 
    1817   ! 
    1918   USE dom_oce         ! ocean space and time domain 
     19   USE domutl          !  
    2020   USE phycst ,   ONLY :   rsmall 
    2121   USE wet_dry,   ONLY :   ll_wd  ! Wetting and drying 
     
    182182      !                                     ! ============================ 
    183183   END SUBROUTINE dom_wri 
    184  
    185  
    186    SUBROUTINE dom_uniq( puniq, cdgrd ) 
    187       !!---------------------------------------------------------------------- 
    188       !!                  ***  ROUTINE dom_uniq  *** 
    189       !!                    
    190       !! ** Purpose :   identify unique point of a grid (TUVF) 
    191       !! 
    192       !! ** Method  :   1) aplly lbc_lnk on an array with different values for each element 
    193       !!                2) check which elements have been changed 
    194       !!---------------------------------------------------------------------- 
    195       CHARACTER(len=1)        , INTENT(in   ) ::   cdgrd   !  
    196       REAL(wp), DIMENSION(:,:), INTENT(inout) ::   puniq   !  
    197       ! 
    198       REAL(wp) ::  zshift   ! shift value link to the process number 
    199       INTEGER  ::  ji       ! dummy loop indices 
    200       LOGICAL, DIMENSION(SIZE(puniq,1),SIZE(puniq,2),1) ::  lldbl  ! store whether each point is unique or not 
    201       REAL(wp), DIMENSION(jpi,jpj) ::   ztstref 
    202       !!---------------------------------------------------------------------- 
    203       ! 
    204       ! build an array with different values for each element  
    205       ! in mpp: make sure that these values are different even between process 
    206       ! -> apply a shift value according to the process number 
    207       zshift = jpi * jpj * ( narea - 1 ) 
    208       ztstref(:,:) = RESHAPE( (/ (zshift + REAL(ji,wp), ji = 1, jpi*jpj) /), (/ jpi, jpj /) ) 
    209       ! 
    210       puniq(:,:) = ztstref(:,:)                   ! default definition 
    211       CALL lbc_lnk( 'domwri', puniq, cdgrd, 1. )            ! apply boundary conditions 
    212       lldbl(:,:,1) = puniq(:,:) == ztstref(:,:)   ! check which values have been changed  
    213       ! 
    214       puniq(:,:) = 1.                             ! default definition 
    215       ! fill only the inner part of the cpu with llbl converted into real  
    216       puniq(nldi:nlei,nldj:nlej) = REAL( COUNT( lldbl(nldi:nlei,nldj:nlej,:), dim = 3 ) , wp ) 
    217       ! 
    218    END SUBROUTINE dom_uniq 
    219184 
    220185 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/DOM/domzgr.F90

    r12738 r12807  
    236236      CALL iom_get( inum, jpdom_unknown, 'e3w_1d'  , pe3w_1d  ) 
    237237      ! 
    238       CALL iom_get( inum, jpdom_global, 'e3t_0'  , pe3t , cd_type = 'T', psgn = 1._wp )    ! 3D coordinate 
    239       CALL iom_get( inum, jpdom_global, 'e3u_0'  , pe3u , cd_type = 'U', psgn = 1._wp ) 
    240       CALL iom_get( inum, jpdom_global, 'e3v_0'  , pe3v , cd_type = 'V', psgn = 1._wp ) 
    241       CALL iom_get( inum, jpdom_global, 'e3f_0'  , pe3f , cd_type = 'F', psgn = 1._wp ) 
    242       CALL iom_get( inum, jpdom_global, 'e3w_0'  , pe3w , cd_type = 'W', psgn = 1._wp ) 
    243       CALL iom_get( inum, jpdom_global, 'e3uw_0' , pe3uw, cd_type = 'U', psgn = 1._wp ) 
    244       CALL iom_get( inum, jpdom_global, 'e3vw_0' , pe3vw, cd_type = 'V', psgn = 1._wp ) 
     238      CALL iom_get( inum, jpdom_global, 'e3t_0'  , pe3t , cd_type = 'T', psgn = 1._wp, kfill = jpfillcopy )    ! 3D coordinate 
     239      CALL iom_get( inum, jpdom_global, 'e3u_0'  , pe3u , cd_type = 'U', psgn = 1._wp, kfill = jpfillcopy ) 
     240      CALL iom_get( inum, jpdom_global, 'e3v_0'  , pe3v , cd_type = 'V', psgn = 1._wp, kfill = jpfillcopy ) 
     241      CALL iom_get( inum, jpdom_global, 'e3f_0'  , pe3f , cd_type = 'F', psgn = 1._wp, kfill = jpfillcopy ) 
     242      CALL iom_get( inum, jpdom_global, 'e3w_0'  , pe3w , cd_type = 'W', psgn = 1._wp, kfill = jpfillcopy ) 
     243      CALL iom_get( inum, jpdom_global, 'e3uw_0' , pe3uw, cd_type = 'U', psgn = 1._wp, kfill = jpfillcopy ) 
     244      CALL iom_get( inum, jpdom_global, 'e3vw_0' , pe3vw, cd_type = 'V', psgn = 1._wp, kfill = jpfillcopy ) 
    245245      ! 
    246246      !                          !* depths 
     
    254254         CALL iom_get( inum, jpdom_unknown, 'gdept_1d', pdept_1d )    
    255255         CALL iom_get( inum, jpdom_unknown, 'gdepw_1d', pdepw_1d ) 
    256          CALL iom_get( inum, jpdom_global , 'gdept_0' , pdept  ) 
    257          CALL iom_get( inum, jpdom_global , 'gdepw_0' , pdepw  ) 
     256         CALL iom_get( inum, jpdom_global , 'gdept_0' , pdept, kfill = jpfillcopy ) 
     257         CALL iom_get( inum, jpdom_global , 'gdepw_0' , pdepw, kfill = jpfillcopy ) 
    258258         ! 
    259259      ELSE                                !- depths computed from e3. scale factors 
Note: See TracChangeset for help on using the changeset viewer.