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 14433 for NEMO/trunk/tests – NEMO

Changeset 14433 for NEMO/trunk/tests


Ignore:
Timestamp:
2021-02-11T09:06:49+01:00 (3 years ago)
Author:
smasson
Message:

trunk: merge dev_r14312_MPI_Interface into the trunk, #2598

Location:
NEMO/trunk/tests
Files:
43 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/tests/BENCH/EXPREF/namelist_cfg_orca025_like

    r14229 r14433  
    1818   nn_jsize   =   1206  !!  1049    ! number of point in j-direction of global(local) domain if >0 (<0)   
    1919   nn_ksize   =   75       ! total number of point in k-direction 
    20    nn_perio   =   4        ! periodicity 
     20   ln_Iperio  =   .true.   ! i-periodicity 
     21   ln_Jperio  =  .false.   ! j-periodicity 
     22   ln_NFold   =   .true.   ! North pole folding 
     23      cn_NFtype   =   'T'  ! Folding type: T or F 
    2124/ 
    2225!----------------------------------------------------------------------- 
  • NEMO/trunk/tests/BENCH/EXPREF/namelist_cfg_orca12_like

    r14229 r14433  
    1818   nn_jsize   =   3146     ! number of point in j-direction of global(local) domain if >0 (<0)   
    1919   nn_ksize   =   75       ! total number of point in k-direction 
    20    nn_perio   =   4        ! periodicity 
     20   ln_Iperio  =   .true.   ! i-periodicity 
     21   ln_Jperio  =  .false.   ! j-periodicity 
     22   ln_NFold   =   .true.   ! North pole folding 
     23      cn_NFtype   =   'T'  ! Folding type: T or F 
    2124/ 
    2225!----------------------------------------------------------------------- 
  • NEMO/trunk/tests/BENCH/EXPREF/namelist_cfg_orca1_like

    r14229 r14433  
    1818   nn_jsize   =   331      ! number of point in j-direction of global(local) domain if >0 (<0)   
    1919   nn_ksize   =   75       ! total number of point in k-direction 
    20    nn_perio   =   6        ! periodicity 
     20   ln_Iperio  =   .true.   ! i-periodicity 
     21   ln_Jperio  =  .false.   ! j-periodicity 
     22   ln_NFold   =   .true.   ! North pole folding 
     23      cn_NFtype   =   'F'  ! Folding type: T or F 
    2124/ 
    2225!----------------------------------------------------------------------- 
  • NEMO/trunk/tests/BENCH/MY_SRC/usrdef_nam.F90

    r13286 r14433  
    2929CONTAINS 
    3030 
    31    SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     31   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype ) 
    3232      !!---------------------------------------------------------------------- 
    3333      !!                     ***  ROUTINE dom_nam  *** 
     
    4141      !! ** input   : - namusr_def namelist found in namelist_cfg 
    4242      !!---------------------------------------------------------------------- 
    43       CHARACTER(len=*)              , INTENT(out) ::   cd_cfg          ! configuration name 
    44       INTEGER                       , INTENT(out) ::   kk_cfg          ! configuration resolution 
    45       INTEGER                       , INTENT(out) ::   kpi, kpj, kpk   ! global domain sizes  
    46       INTEGER                       , INTENT(out) ::   kperio          ! lateral global domain b.c.  
    47       ! 
     43      CHARACTER(len=*), INTENT(out) ::   cd_cfg               ! configuration name 
     44      INTEGER         , INTENT(out) ::   kk_cfg               ! configuration resolution 
     45      INTEGER         , INTENT(out) ::   kpi, kpj, kpk        ! global domain sizes  
     46      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity 
     47      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding 
     48      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F 
    4849      ! 
    4950      INTEGER ::   ios         ! Local integer 
     
    5253      INTEGER ::   nn_jsize    ! number of point in j-direction of global(local) domain if >0 (<0)   
    5354      INTEGER ::   nn_ksize    ! total number of point in k-direction 
    54       INTEGER ::   nn_perio    ! periodicity 
    5555      !                              !!* nammpp namelist *!! 
    5656      INTEGER          ::   jpni, jpnj 
    57       LOGICAL          ::   ln_nnogather, ln_listonly 
     57      LOGICAL          ::   ln_listonly 
     58      LOGICAL          ::   ln_Iperio, ln_Jperio 
     59      LOGICAL          ::   ln_NFold 
     60      character(len=1) ::   cn_NFtype 
    5861      !! 
    59       NAMELIST/namusr_def/ nn_isize, nn_jsize, nn_ksize, nn_perio 
    60       NAMELIST/nammpp/ jpni, jpnj, nn_hls, ln_nnogather, ln_listonly 
     62      NAMELIST/namusr_def/ nn_isize, nn_jsize, nn_ksize, ln_Iperio, ln_Jperio, ln_NFold, cn_NFtype 
     63      NAMELIST/nammpp/ jpni, jpnj, nn_hls, ln_nnogather, ln_listonly, nn_comm 
    6164      !!----------------------------------------------------------------------      
    6265      ! 
     
    8386         kpj = nn_jsize 
    8487      ENDIF 
     88      kpk = nn_ksize 
    8589      ! 
    86       kpk = nn_ksize 
    87       kperio = nn_perio 
     90      ldIperio = ln_Iperio   ;   ldJperio = ln_Jperio 
     91      ldNFold  = ln_NFold    ;   cdNFtype = cn_NFtype 
     92      ! 
    8893      !                             ! control print 
    8994      IF(lwp) THEN 
     
    107112         ENDIF 
    108113         WRITE(numout,*) '      global domain size-z            nn_ksize = ', nn_ksize 
    109          WRITE(numout,*) '      LBC of the global domain          kperio = ', kperio 
     114         WRITE(numout,*) '   ' 
    110115      ENDIF 
    111116      ! 
  • NEMO/trunk/tests/BENCH/MY_SRC/usrdef_sbc.F90

    r14273 r14433  
    110110      END_2D 
    111111 
    112       CALL lbc_lnk_multi( 'usrdef_sbc', utau_ice, 'U', -1., vtau_ice, 'V', -1. ) 
     112      CALL lbc_lnk( 'usrdef_sbc', utau_ice, 'U', -1., vtau_ice, 'V', -1. ) 
    113113#endif 
    114114      ! 
  • NEMO/trunk/tests/BENCH/MY_SRC/usrdef_zgr.F90

    r13286 r14433  
    197197      ! 
    198198       
    199 !!$      IF( jperio == 3 .OR. jperio == 4 ) THEN   ! add a small island in the upper corners to avoid model instabilities... 
     199!!$      IF( c_NFtype == 'T' ) THEN   ! add a small island in the upper corners to avoid model instabilities... 
    200200!!$         z2d(mi0(       nn_hls):mi1(                  nn_hls+2 ),mj0(jpjglo-nn_hls-1):mj1(jpjglo-nn_hls+1)) = 0. 
    201201!!$         z2d(mi0(jpiglo-nn_hls):mi1(MIN(jpiglo,jpiglo-nn_hls+2)),mj0(jpjglo-nn_hls-1):mj1(jpjglo-nn_hls+1)) = 0. 
     
    203203!!$      ENDIF 
    204204!!$      ! 
    205 !!$      IF( jperio == 5 .OR. jperio == 6 ) THEN   ! add a small island in the upper corners to avoid model instabilities... 
     205!!$      IF( c_NFtype == 'F' ) THEN   ! add a small island in the upper corners to avoid model instabilities... 
    206206!!$         z2d(mi0(       nn_hls):mi1(       nn_hls+1),mj0(jpjglo-nn_hls):mj1(jpjglo-nn_hls+1)) = 0. 
    207207!!$         z2d(mi0(jpiglo-nn_hls):mi1(jpiglo-nn_hls+1),mj0(jpjglo-nn_hls):mj1(jpjglo-nn_hls+1)) = 0. 
     
    210210 
    211211      ! 
    212       CALL lbc_lnk( 'usrdef_zgr', z2d, 'T', 1. )           ! set surrounding land to zero (here jperio=0 ==>> closed) 
     212      CALL lbc_lnk( 'usrdef_zgr', z2d, 'T', 1. )           ! set surrounding land to zero (closed boundaries) 
    213213      ! 
    214214      k_bot(:,:) = INT( z2d(:,:) )           ! =jpkm1 over the ocean point, =0 elsewhere 
  • NEMO/trunk/tests/C1D_ASICS/MY_SRC/usrdef_nam.F90

    r14021 r14433  
    3939CONTAINS 
    4040 
    41    SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     41   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype ) 
    4242      !!---------------------------------------------------------------------- 
    4343      !!                     ***  ROUTINE dom_nam  *** 
     
    5151      !! ** input   : - namusr_def namelist found in namelist_cfg 
    5252      !!---------------------------------------------------------------------- 
    53       CHARACTER(len=*)              , INTENT(out) ::   cd_cfg          ! configuration name 
    54       INTEGER                       , INTENT(out) ::   kk_cfg          ! configuration resolution 
    55       INTEGER                       , INTENT(out) ::   kpi, kpj, kpk   ! global domain sizes  
    56       INTEGER                       , INTENT(out) ::   kperio          ! lateral global domain b.c.  
     53      CHARACTER(len=*), INTENT(out) ::   cd_cfg               ! configuration name 
     54      INTEGER         , INTENT(out) ::   kk_cfg               ! configuration resolution 
     55      INTEGER         , INTENT(out) ::   kpi, kpj, kpk        ! global domain sizes 
     56      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity 
     57      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding 
     58      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F 
    5759      ! 
    5860      INTEGER ::   ios   ! Local integer 
     
    7274      kpi = 3 
    7375      kpj = 3 
    74       kpk = 75  
     76      kpk = 75 
    7577      !                             ! Set the lateral boundary condition of the global domain 
    76       kperio =  7                   ! C1D configuration : 3x3 basin with cyclic Est-West and Norht-South condition 
     78      ldIperio = .TRUE.    ;   ldJperio = .true.   ! C1D configuration : 3x3 basin with cyclic Est-West and Norht-South condition 
     79      ldNFold  = .FALSE.   ;   cdNFtype = '-' 
    7780      ! 
    7881      !                             ! control print 
     
    9093         WRITE(numout,*) '                                               jpjglo = ', kpj 
    9194         WRITE(numout,*) '                                               jpkglo = ', kpk 
    92          WRITE(numout,*) '   Lateral boundary condition of the global domain' 
    93          WRITE(numout,*) '      C1D : closed basin                       jperio = ', kperio 
     95      WRITE(numout,*) '   ' 
    9496      ENDIF 
    9597      ! 
  • NEMO/trunk/tests/CANAL/EXPREF/namelist_cfg

    r14229 r14433  
    4949   ln_sshnoise =  .FALSE.  !  add random noise on initial ssh 
    5050   rn_lambda   =     50.   !  gaussian lambda 
    51    nn_perio    = 1 
     51   ln_Iperio   =   .true.  ! i-periodicity 
     52   ln_Jperio   =  .false.  ! j-periodicity 
    5253/ 
    5354!----------------------------------------------------------------------- 
  • NEMO/trunk/tests/CANAL/MY_SRC/usrdef_hgr.F90

    r14223 r14433  
    6464      ! 
    6565      INTEGER  ::   ji, jj     ! dummy loop indices 
    66       REAL(wp) ::   zphi0, zlam0, zbeta, zf0 
     66      INTEGER  ::   ii0, ij0   ! dummy loop indices 
     67      REAL(wp) ::   zbeta, zf0 
    6768      REAL(wp) ::   zti, ztj   ! local scalars 
    6869      !!------------------------------------------------------------------------------- 
     
    7778      ! Position coordinates (in kilometers) 
    7879      !                          ========== 
    79       zlam0 = -REAL(Ni0glo, wp) * rn_0xratio * rn_dx 
    80       zphi0 = -REAL(Nj0glo, wp) * rn_0yratio * rn_dy 
     80      ii0 = NINT( REAL(Ni0glo, wp) * rn_0xratio ) 
     81      ij0 = NINT( REAL(Nj0glo, wp) * rn_0yratio ) 
    8182 
    8283#if defined key_agrif 
    8384      ! ! let lower left longitude and latitude from parent 
    8485      IF (.NOT.Agrif_root()) THEN 
    85           zlam0 = (0.5_wp-(Agrif_parent(jpiglo)-1)/2)*Agrif_irhox()*rn_dx & 
    86              &+(Agrif_Ix()+nbghostcells-1)*Agrif_irhox()*rn_dx-(0.5_wp+nbghostcells)*rn_dx 
    87           zphi0 = (0.5_wp-(Agrif_parent(jpjglo)-1)/2)*Agrif_irhoy()*rn_dy & 
    88              &+(Agrif_Iy()+nbghostcells-1)*Agrif_irhoy()*rn_dy-(0.5_wp+nbghostcells)*rn_dy 
     86          to be coded... 
    8987      ENDIF  
    9088#endif 
    9189          
    9290      DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )          
    93          zti = REAL( mig0(ji), wp ) - 0.5_wp  ! start at i=0.5 in the global grid without halos 
    94          ztj = REAL( mjg0(jj), wp ) - 0.5_wp  ! start at j=0.5 in the global grid without halos 
     91         zti = REAL( mig0(ji)-ii0, wp )   ! =0 at i=ii0 in the global grid without halos 
     92         ztj = REAL( mjg0(jj)-ij0, wp )   ! =0 at i=ij0 in the global grid without halos 
    9593          
    96          plamt(ji,jj) = zlam0 + rn_dx *   zti 
    97          plamu(ji,jj) = zlam0 + rn_dx * ( zti + 0.5_wp )  
     94         plamt(ji,jj) = rn_dx *   zti 
     95         plamu(ji,jj) = rn_dx * ( zti + 0.5_wp )  
    9896         plamv(ji,jj) = plamt(ji,jj)  
    9997         plamf(ji,jj) = plamu(ji,jj)  
    10098          
    101          pphit(ji,jj) = zphi0 + rn_dy *   ztj 
    102          pphiv(ji,jj) = zphi0 + rn_dy * ( ztj + 0.5_wp )  
     99         pphit(ji,jj) = rn_dy *   ztj 
     100         pphiv(ji,jj) = rn_dy * ( ztj + 0.5_wp )  
    103101         pphiu(ji,jj) = pphit(ji,jj)  
    104102         pphif(ji,jj) = pphiv(ji,jj)  
  • NEMO/trunk/tests/CANAL/MY_SRC/usrdef_istate.F90

    r14224 r14433  
    239239      ! 
    240240      CALL lbc_lnk( 'usrdef_istate', pts , 'T',  1. ) 
    241       CALL lbc_lnk_multi( 'usrdef_istate', pu, 'U', -1., pv, 'V', -1. ) 
     241      CALL lbc_lnk( 'usrdef_istate', pu, 'U', -1., pv, 'V', -1. ) 
    242242 
    243243   END SUBROUTINE usr_def_istate 
  • NEMO/trunk/tests/CANAL/MY_SRC/usrdef_nam.F90

    r13472 r14433  
    5050   LOGICAL , PUBLIC ::   ln_sshnoise=.false. ! add random noise on initial ssh 
    5151   REAL(wp), PUBLIC ::   rn_lambda  = 50.    ! gaussian lambda 
    52    INTEGER , PUBLIC ::   nn_perio   =    0   ! periodicity of the channel (0=closed, 1=E-W) 
    5352 
    5453   !!---------------------------------------------------------------------- 
     
    5958CONTAINS 
    6059 
    61    SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     60   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype ) 
    6261      !!---------------------------------------------------------------------- 
    6362      !!                     ***  ROUTINE dom_nam  *** 
     
    7170      !! ** input   : - namusr_def namelist found in namelist_cfg 
    7271      !!---------------------------------------------------------------------- 
    73       CHARACTER(len=*)              , INTENT(out) ::   cd_cfg          ! configuration name 
    74       INTEGER                       , INTENT(out) ::   kk_cfg          ! configuration resolution 
    75       INTEGER                       , INTENT(out) ::   kpi, kpj, kpk   ! global domain sizes  
    76       INTEGER                       , INTENT(out) ::   kperio          ! lateral global domain b.c.  
     72      CHARACTER(len=*), INTENT(out) ::   cd_cfg               ! configuration name 
     73      INTEGER         , INTENT(out) ::   kk_cfg               ! configuration resolution 
     74      INTEGER         , INTENT(out) ::   kpi, kpj, kpk        ! global domain sizes 
     75      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity 
     76      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding 
     77      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F 
    7778      ! 
    7879      INTEGER ::   ios      ! Local integer 
    7980      REAL(wp)::   zh       ! Local scalars 
     81      LOGICAL ::   ln_Iperio, ln_Jperio 
    8082      !! 
    8183      NAMELIST/namusr_def/  rn_domszx, rn_domszy, rn_domszz, rn_dx, rn_dy, rn_dz, rn_0xratio, rn_0yratio   & 
    8284         &                 , nn_fcase, rn_ppgphi0, rn_u10, rn_windszx, rn_windszy & !!, rn_uofac   & 
    8385         &                 , rn_vtxmax, rn_uzonal, rn_ujetszx, rn_ujetszy  & 
    84          &                 , nn_botcase, nn_initcase, ln_sshnoise, rn_lambda, nn_perio 
     86         &                 , nn_botcase, nn_initcase, ln_sshnoise, rn_lambda, ln_Iperio, ln_Jperio 
    8587      !!---------------------------------------------------------------------- 
    8688      ! 
     
    102104#endif 
    103105      ! 
    104       IF(lwm)   WRITE( numond, namusr_def ) 
    105       ! 
    106106      cd_cfg = 'EW_CANAL'             ! name & resolution (not used) 
    107107      kk_cfg = INT( rn_dx ) 
     
    109109      IF( Agrif_Root() ) THEN        ! Global Domain size:  EW_CANAL global domain is  1800 km x 1800 Km x 5000 m 
    110110         kpi = NINT( rn_domszx / rn_dx ) + 1 
    111          kpj = NINT( rn_domszy / rn_dy ) + 3 
     111         kpj = NINT( rn_domszy / rn_dy ) + 1 
    112112      ELSE                           ! Global Domain size: add nbghostcells + 1 "land" point on each side 
    113113         kpi  = nbcellsx + nbghostcells_x   + nbghostcells_x   + 2 
     
    117117      ! 
    118118      zh  = (kpk-1)*rn_dz 
    119       !                             ! Set the lateral boundary condition of the global domain 
    120       kperio = 1                    ! EW_CANAL configuration : closed basin 
    121119      !                             ! control print 
    122120      IF(lwp) THEN 
     
    149147         WRITE(numout,*) '      add random noise on initial ssh   ln_sshnoise= ', ln_sshnoise 
    150148         WRITE(numout,*) '      Gaussian lambda parameter          rn_lambda = ', rn_lambda 
    151          WRITE(numout,*) '      Periodicity of the basin            nn_perio = ', nn_perio 
     149         WRITE(numout,*) '      i and j Periodicity     ln_Iperio, ln_Jperio = ', ln_Iperio, ln_Jperio 
     150         WRITE(numout,*) '   ' 
    152151      ENDIF 
    153152      !                             ! Set the lateral boundary condition of the global domain 
    154       kperio = nn_perio                    ! EW_CANAL configuration : closed basin 
     153      ldIperio = ln_Iperio   ;   ldJperio = ln_Jperio   ! CANAL configuration 
     154      ldNFold  =  .FALSE.    ;   cdNFtype = '-' 
    155155      ! 
    156156   END SUBROUTINE usr_def_nam 
  • NEMO/trunk/tests/CANAL/MY_SRC/usrdef_zgr.F90

    r13472 r14433  
    202202      END SELECT 
    203203      ! 
    204       CALL lbc_lnk( 'usrdef_zgr', z2d, 'T', 1. )           ! set surrounding land to zero (here jperio=0 ==>> closed) 
     204      CALL lbc_lnk( 'usrdef_zgr', z2d, 'T', 1. )           ! set surrounding land to zero (closed boundaries) 
    205205      ! 
    206206      k_bot(:,:) = NINT( z2d(:,:) )          ! =jpkm1 over the ocean point, =0 elsewhere 
  • NEMO/trunk/tests/DOME/MY_SRC/usrdef_nam.F90

    r14254 r14433  
    4040CONTAINS 
    4141 
    42    SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     42   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype ) 
    4343      !!---------------------------------------------------------------------- 
    4444      !!                     ***  ROUTINE dom_nam  *** 
     
    5252      !! ** input   : - namusr_def namelist found in namelist_cfg 
    5353      !!---------------------------------------------------------------------- 
    54       CHARACTER(len=*)              , INTENT(out) ::   cd_cfg          ! configuration name 
    55       INTEGER                       , INTENT(out) ::   kk_cfg          ! configuration resolution 
    56       INTEGER                       , INTENT(out) ::   kpi, kpj, kpk   ! global domain sizes  
    57       INTEGER                       , INTENT(out) ::   kperio          ! lateral global domain b.c.  
     54      CHARACTER(len=*), INTENT(out) ::   cd_cfg               ! configuration name 
     55      INTEGER         , INTENT(out) ::   kk_cfg               ! configuration resolution 
     56      INTEGER         , INTENT(out) ::   kpi, kpj, kpk        ! global domain sizes 
     57      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity 
     58      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding 
     59      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F 
    5860      ! 
    5961      INTEGER ::   ios          ! Local integer 
     
    9799      zh  = (kpk-1)*rn_dz 
    98100      !                             ! Set the lateral boundary condition of the global domain 
    99       kperio = 0                    ! DOME configuration : closed basin 
     101      ldIperio = .FALSE.   ;   ldJperio = .FALSE.   ! DOME configuration : closed domain 
     102      ldNFold  = .FALSE.   ;   cdNFtype = '-' 
     103      ! 
    100104      !                             ! control print 
    101105      IF(lwp) THEN 
     
    118122         WRITE(numout,*) '      Coriolis frequency                rn_f0 = ', rn_f0, ' s-1' 
    119123         WRITE(numout,*) '   ' 
    120          WRITE(numout,*) '   Lateral boundary condition of the global domain' 
    121          WRITE(numout,*) '      DOME : closed basin            jperio = ', kperio 
    122124      ENDIF 
    123125      ! 
  • NEMO/trunk/tests/DOME/MY_SRC/usrdef_zgr.F90

    r14261 r14433  
    9898         END DO 
    9999      END DO 
    100       CALL lbc_lnk_multi( 'usrdef_zgr', zhu, 'U', 1.0_wp, zhv, 'V', 1.0_wp, zhf, 'F', 1.0_wp)       
     100      CALL lbc_lnk( 'usrdef_zgr', zhu, 'U', 1.0_wp, zhv, 'V', 1.0_wp, zhf, 'F', 1.0_wp)       
    101101      !      
    102102      CALL zgr_z1d( pdept_1d, pdepw_1d, pe3t_1d , pe3w_1d )   ! Reference z-coordinate system 
     
    106106      ! 
    107107      ! no ocean cavities : top ocean level is ONE, except over land 
    108       ! the ocean basin surrounded by land (1 grid-point) set through lbc_lnk call as jperio=0  
     108      ! the ocean basin surrounded by land (1+nn_hls grid-point) set through lbc_lnk call 
    109109      z2d(:,:) = 1._wp                    ! surface ocean is the 1st level 
    110110      WHERE (gphit(:,:)>0._wp) z2d(:,:) = 0._wp 
    111111      ! Dig inlet: 
    112112      WHERE ((gphit(:,:)>0._wp).AND.(glamt(:,:)>-50._wp).AND.(glamt(:,:)<50._wp)) z2d(:,:) = 1._wp 
    113       CALL lbc_lnk( 'usrdef_zgr', z2d, 'T', 1. )        ! closed basin since jperio = 0 (see userdef_nam.F90) 
     113      CALL lbc_lnk( 'usrdef_zgr', z2d, 'T', 1. )        ! closed basin, see userdef_nam.F90 
    114114      k_top(:,:) = NINT( z2d(:,:) ) 
    115115      ! 
  • NEMO/trunk/tests/ICB/MY_SRC/usrdef_nam.F90

    r13899 r14433  
    4242CONTAINS 
    4343 
    44    SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     44   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype ) 
    4545      !!---------------------------------------------------------------------- 
    4646      !!                     ***  ROUTINE dom_nam  *** 
     
    5454      !! ** input   : - namusr_def namelist found in namelist_cfg 
    5555      !!---------------------------------------------------------------------- 
    56       CHARACTER(len=*)              , INTENT(out) ::   cd_cfg          ! configuration name 
    57       INTEGER                       , INTENT(out) ::   kk_cfg          ! configuration resolution 
    58       INTEGER                       , INTENT(out) ::   kpi, kpj, kpk   ! global domain sizes  
    59       INTEGER                       , INTENT(out) ::   kperio          ! lateral global domain b.c.  
     56      CHARACTER(len=*), INTENT(out) ::   cd_cfg               ! configuration name 
     57      INTEGER         , INTENT(out) ::   kk_cfg               ! configuration resolution 
     58      INTEGER         , INTENT(out) ::   kpi, kpj, kpk        ! global domain sizes 
     59      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity 
     60      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding 
     61      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F 
    6062      ! 
    6163      INTEGER ::   ios   ! Local integer 
     
    7880      ! 
    7981      !                             ! Set the lateral boundary condition of the global domain 
    80       kperio = 0                    ! ICB configuration : box 
     82      ldIperio = .FALSE.   ;   ldJperio = .FALSE.   ! ICB configuration : closed domain 
     83      ldNFold  = .FALSE.   ;   cdNFtype = '-' 
    8184      ! 
    8285      !                             ! control print 
     
    99102         WRITE(numout,*) '                                               jpkglo   = ', kpk 
    100103         WRITE(numout,*) '   ' 
    101          WRITE(numout,*) '   Lateral boundary condition of the global domain' 
    102          WRITE(numout,*) '      ICB : closed basin                    jperio   = ', kperio 
    103104      ENDIF 
    104105      ! 
  • NEMO/trunk/tests/ICE_ADV1D/MY_SRC/usrdef_nam.F90

    r13286 r14433  
    3939CONTAINS 
    4040 
    41    SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     41   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype ) 
    4242      !!---------------------------------------------------------------------- 
    4343      !!                     ***  ROUTINE dom_nam  *** 
     
    5151      !! ** input   : - namusr_def namelist found in namelist_cfg 
    5252      !!---------------------------------------------------------------------- 
    53       CHARACTER(len=*)              , INTENT(out) ::   cd_cfg          ! configuration name 
    54       INTEGER                       , INTENT(out) ::   kk_cfg          ! configuration resolution 
    55       INTEGER                       , INTENT(out) ::   kpi, kpj, kpk   ! global domain sizes  
    56       INTEGER                       , INTENT(out) ::   kperio          ! lateral global domain b.c.  
     53      CHARACTER(len=*), INTENT(out) ::   cd_cfg               ! configuration name 
     54      INTEGER         , INTENT(out) ::   kk_cfg               ! configuration resolution 
     55      INTEGER         , INTENT(out) ::   kpi, kpj, kpk        ! global domain sizes 
     56      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity 
     57      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding 
     58      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F 
    5759      ! 
    5860      INTEGER ::   ios       ! Local integer 
     
    7880      zly = kpj*rn_dy*1.e-3 
    7981      !                             ! Set the lateral boundary condition of the global domain 
    80       kperio = 0                    ! ICE_ADV1D configuration : bi-periodic basin 
     82      ldIperio = .FALSE.   ;   ldJperio = .FALSE.   ! ICE_ADV1D configuration : closed domain 
     83      ldNFold  = .FALSE.   ;   cdNFtype = '-' 
     84      ! 
    8185      !                             ! control print 
    8286      IF(lwp) THEN 
     
    9599         WRITE(numout,*) '         Coriolis:', ln_corio 
    96100         WRITE(numout,*) '   ' 
    97          WRITE(numout,*) '   Lateral boundary condition of the global domain' 
    98          WRITE(numout,*) '      ICE_ADV1D : closed basin                 jperio = ', kperio 
    99101      ENDIF 
    100102      ! 
  • NEMO/trunk/tests/ICE_ADV2D/MY_SRC/usrdef_nam.F90

    r13286 r14433  
    4040CONTAINS 
    4141 
    42    SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     42   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype ) 
    4343      !!---------------------------------------------------------------------- 
    4444      !!                     ***  ROUTINE dom_nam  *** 
     
    5252      !! ** input   : - namusr_def namelist found in namelist_cfg 
    5353      !!---------------------------------------------------------------------- 
    54       CHARACTER(len=*)              , INTENT(out) ::   cd_cfg          ! configuration name 
    55       INTEGER                       , INTENT(out) ::   kk_cfg          ! configuration resolution 
    56       INTEGER                       , INTENT(out) ::   kpi, kpj, kpk   ! global domain sizes  
    57       INTEGER                       , INTENT(out) ::   kperio          ! lateral global domain b.c.  
     54      CHARACTER(len=*), INTENT(out) ::   cd_cfg               ! configuration name 
     55      INTEGER         , INTENT(out) ::   kk_cfg               ! configuration resolution 
     56      INTEGER         , INTENT(out) ::   kpi, kpj, kpk        ! global domain sizes  
     57      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity 
     58      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding 
     59      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F 
    5860      ! 
    5961      INTEGER ::   ios       ! Local integer 
     
    9698      zly = kpj*rn_dy*1.e-3 
    9799      ! 
    98       IF( Agrif_Root() ) THEN   ;   kperio = 7     ! ICE_AGRIF configuration : bi-periodic basin 
    99       ELSE                      ;   kperio = 0     ! closed periodicity for the zoom 
     100      IF( Agrif_Root() ) THEN   ;   ldIperio =  .TRUE.   ;   ldJperio =  .TRUE.     ! ICE_ADV2D configuration : bi-periodic basin 
     101      ELSE                      ;   ldIperio = .FALSE.   ;   ldJperio = .FALSE.     ! closed periodicity for the zoom 
    100102      ENDIF 
     103      ldNFold  = .FALSE.   ;   cdNFtype = '-' 
     104      ! 
    101105      !                             ! control print 
    102106      IF(lwp) THEN 
     
    115119         WRITE(numout,*) '         Coriolis:', ln_corio 
    116120         WRITE(numout,*) '   ' 
    117          WRITE(numout,*) '   Lateral boundary condition of the global domain' 
    118          WRITE(numout,*) '      ICE_ADV2D : bi-periodic basin            jperio = ', kperio 
    119121      ENDIF 
    120122      ! 
  • NEMO/trunk/tests/ICE_AGRIF/MY_SRC/usrdef_nam.F90

    r14223 r14433  
    4040CONTAINS 
    4141 
    42    SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     42   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype ) 
    4343      !!---------------------------------------------------------------------- 
    4444      !!                     ***  ROUTINE dom_nam  *** 
     
    5252      !! ** input   : - namusr_def namelist found in namelist_cfg 
    5353      !!---------------------------------------------------------------------- 
    54       CHARACTER(len=*)              , INTENT(out) ::   cd_cfg          ! configuration name 
    55       INTEGER                       , INTENT(out) ::   kk_cfg          ! configuration resolution 
    56       INTEGER                       , INTENT(out) ::   kpi, kpj, kpk   ! global domain sizes  
    57       INTEGER                       , INTENT(out) ::   kperio          ! lateral global domain b.c.  
     54      CHARACTER(len=*), INTENT(out) ::   cd_cfg               ! configuration name 
     55      INTEGER         , INTENT(out) ::   kk_cfg               ! configuration resolution 
     56      INTEGER         , INTENT(out) ::   kpi, kpj, kpk        ! global domain sizes  
     57      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity 
     58      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding 
     59      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F 
    5860      ! 
    5961      INTEGER ::   ios       ! Local integer 
     
    98100      zly = kpj*rn_dy*1.e-3 
    99101      ! 
    100       IF( Agrif_Root() ) THEN   ;   kperio = 7     ! ICE_AGRIF configuration : bi-periodic basin 
    101       ELSE                      ;   kperio = 0     ! closed periodicity for the zoom 
     102      IF( Agrif_Root() ) THEN   ;   ldIperio =  .TRUE.   ;   ldJperio =  .TRUE.     ! ICE_AGRIF configuration : bi-periodic basin 
     103      ELSE                      ;   ldIperio = .FALSE.   ;   ldJperio = .FALSE.     ! closed periodicity for the zoom 
    102104      ENDIF 
     105      ldNFold  = .FALSE.   ;   cdNFtype = '-' 
     106      ! 
    103107      !                             ! control print 
    104108      IF(lwp) THEN 
     
    117121         WRITE(numout,*) '         Coriolis:', ln_corio 
    118122         WRITE(numout,*) '   ' 
    119          WRITE(numout,*) '   Lateral boundary condition of the global domain' 
    120          WRITE(numout,*) '      ICE_AGRIF : bi-periodic basin            jperio = ', kperio 
    121123      ENDIF 
    122124      ! 
  • NEMO/trunk/tests/ICE_RHEO/MY_SRC/icedyn_rhg_eap.F90

    r14120 r14433  
    354354 
    355355      END_2D 
    356       CALL lbc_lnk_multi( 'icedyn_rhg_eap', zmf, 'T', 1.0_wp, zdt_m, 'T', 1.0_wp ) 
     356      CALL lbc_lnk( 'icedyn_rhg_eap', zmf, 'T', 1.0_wp, zdt_m, 'T', 1.0_wp ) 
    357357      ! 
    358358      !                                  !== Landfast ice parameterization ==! 
     
    492492            zs2(ji,jj) = ( zs2(ji,jj) * zalph1 + zstressmtmp ) * z1_alph1 
    493493         END_2D 
    494          CALL lbc_lnk_multi( 'icedyn_rhg_eap', zstress12tmp, 'T', 1.0_wp , paniso_11, 'T', 1.0_wp , paniso_12, 'T', 1.0_wp) 
     494         CALL lbc_lnk( 'icedyn_rhg_eap', zstress12tmp, 'T', 1.0_wp , paniso_11, 'T', 1.0_wp , paniso_12, 'T', 1.0_wp) 
    495495 
    496496        ! Save beta at T-points for further computations 
     
    520520 
    521521         END_2D 
    522          CALL lbc_lnk_multi( 'icedyn_rhg_eap', zs1, 'T', 1.0_wp, zs2, 'T', 1.0_wp, zs12, 'F', 1.0_wp ) 
     522         CALL lbc_lnk( 'icedyn_rhg_eap', zs1, 'T', 1.0_wp, zs2, 'T', 1.0_wp, zs12, 'F', 1.0_wp ) 
    523523 
    524524         ! --- Ice internal stresses (Appendix C of Hunke and Dukowicz, 2002) --- ! 
     
    832832 
    833833      END_2D 
    834       CALL lbc_lnk_multi( 'icedyn_rhg_eap', pshear_i, 'T', 1.0_wp, pdivu_i, 'T', 1.0_wp, pdelta_i, 'T', 1.0_wp, & 
    835          &                                    zten_i, 'T', 1.0_wp, zs1    , 'T', 1.0_wp, zs2     , 'T', 1.0_wp, & 
    836          &                                      zs12, 'F', 1.0_wp ) 
     834      CALL lbc_lnk( 'icedyn_rhg_eap', pshear_i, 'T', 1.0_wp, pdivu_i, 'T', 1.0_wp, pdelta_i, 'T', 1.0_wp, & 
     835         &                              zten_i, 'T', 1.0_wp, zs1    , 'T', 1.0_wp, zs2     , 'T', 1.0_wp, & 
     836         &                                zs12, 'F', 1.0_wp ) 
    837837 
    838838      ! --- Store the stress tensor for the next time step --- ! 
     
    849849         & iom_use('utau_bi') .OR. iom_use('vtau_bi') ) THEN 
    850850         ! 
    851          CALL lbc_lnk_multi( 'icedyn_rhg_eap', ztaux_oi, 'U', -1.0_wp, ztauy_oi, 'V', -1.0_wp, ztaux_ai, 'U', -1.0_wp, & 
    852             &                                  ztauy_ai, 'V', -1.0_wp, ztaux_bi, 'U', -1.0_wp, ztauy_bi, 'V', -1.0_wp ) 
     851         CALL lbc_lnk( 'icedyn_rhg_eap', ztaux_oi, 'U', -1.0_wp, ztauy_oi, 'V', -1.0_wp, ztaux_ai, 'U', -1.0_wp, & 
     852            &                            ztauy_ai, 'V', -1.0_wp, ztaux_bi, 'U', -1.0_wp, ztauy_bi, 'V', -1.0_wp ) 
    853853         ! 
    854854         CALL iom_put( 'utau_oi' , ztaux_oi * aimsk00 ) 
     
    934934      IF( iom_use('yield11') .OR. iom_use('yield12') .OR. iom_use('yield22')) THEN 
    935935 
    936          CALL lbc_lnk_multi( 'icedyn_rhg_eap', zyield11, 'T', 1.0_wp, zyield22, 'T', 1.0_wp, zyield12, 'T', 1.0_wp ) 
     936         CALL lbc_lnk( 'icedyn_rhg_eap', zyield11, 'T', 1.0_wp, zyield22, 'T', 1.0_wp, zyield12, 'T', 1.0_wp ) 
    937937 
    938938         CALL iom_put( 'yield11', zyield11 * aimsk00 ) 
     
    951951         & iom_use('corstrx') .OR. iom_use('corstry') .OR. iom_use('intstrx') .OR. iom_use('intstry') ) THEN 
    952952         ! 
    953          CALL lbc_lnk_multi( 'icedyn_rhg_eap', zspgU, 'U', -1.0_wp, zspgV, 'V', -1.0_wp, & 
    954             &                                  zCorU, 'U', -1.0_wp, zCorV, 'V', -1.0_wp, & 
    955             &                                    zfU, 'U', -1.0_wp,   zfV, 'V', -1.0_wp ) 
     953         CALL lbc_lnk( 'icedyn_rhg_eap', zspgU, 'U', -1.0_wp, zspgV, 'V', -1.0_wp, & 
     954            &                            zCorU, 'U', -1.0_wp, zCorV, 'V', -1.0_wp, & 
     955            &                              zfU, 'U', -1.0_wp,   zfV, 'V', -1.0_wp ) 
    956956 
    957957         CALL iom_put( 'dssh_dx' , zspgU * aimsk00 )   ! Sea-surface tilt term in force balance (x) 
     
    985985         END_2D 
    986986 
    987          CALL lbc_lnk_multi( 'icedyn_rhg_eap', zdiag_xmtrp_ice, 'U', -1.0_wp, zdiag_ymtrp_ice, 'V', -1.0_wp, & 
    988             &                                  zdiag_xmtrp_snw, 'U', -1.0_wp, zdiag_ymtrp_snw, 'V', -1.0_wp, & 
    989             &                                  zdiag_xatrp    , 'U', -1.0_wp, zdiag_yatrp    , 'V', -1.0_wp ) 
     987         CALL lbc_lnk( 'icedyn_rhg_eap', zdiag_xmtrp_ice, 'U', -1.0_wp, zdiag_ymtrp_ice, 'V', -1.0_wp, & 
     988            &                            zdiag_xmtrp_snw, 'U', -1.0_wp, zdiag_ymtrp_snw, 'V', -1.0_wp, & 
     989            &                            zdiag_xatrp    , 'U', -1.0_wp, zdiag_yatrp    , 'V', -1.0_wp ) 
    990990 
    991991         CALL iom_put( 'xmtrpice' , zdiag_xmtrp_ice )   ! X-component of sea-ice mass transport (kg/s) 
  • NEMO/trunk/tests/ICE_RHEO/MY_SRC/icedyn_rhg_evp.F90

    r14021 r14433  
    320320 
    321321      END_2D 
    322       CALL lbc_lnk_multi( 'icedyn_rhg_evp', zmf, 'T', 1.0_wp, zdt_m, 'T', 1.0_wp ) 
     322      CALL lbc_lnk( 'icedyn_rhg_evp', zmf, 'T', 1.0_wp, zdt_m, 'T', 1.0_wp ) 
    323323      ! 
    324324      !                                  !== Landfast ice parameterization ==! 
     
    770770 
    771771      END_2D 
    772       CALL lbc_lnk_multi( 'icedyn_rhg_evp', pshear_i, 'T', 1._wp, pdivu_i, 'T', 1._wp, pdelta_i, 'T', 1._wp, zten_i, 'T', 1._wp, & 
    773          &                                  zs1     , 'T', 1._wp, zs2    , 'T', 1._wp, zs12    , 'F', 1._wp ) 
     772      CALL lbc_lnk( 'icedyn_rhg_evp', pshear_i, 'T', 1._wp, pdivu_i, 'T', 1._wp, pdelta_i, 'T', 1._wp, zten_i, 'T', 1._wp, & 
     773         &                            zs1     , 'T', 1._wp, zs2    , 'T', 1._wp, zs12    , 'F', 1._wp ) 
    774774       
    775775      ! --- Store the stress tensor for the next time step --- ! 
     
    786786         & iom_use('utau_bi') .OR. iom_use('vtau_bi') ) THEN 
    787787         ! 
    788          CALL lbc_lnk_multi( 'icedyn_rhg_evp', ztaux_oi, 'U', -1.0_wp, ztauy_oi, 'V', -1.0_wp, ztaux_ai, 'U', -1.0_wp, ztauy_ai, 'V', -1.0_wp, & 
    789             &                                  ztaux_bi, 'U', -1.0_wp, ztauy_bi, 'V', -1.0_wp ) 
     788         CALL lbc_lnk( 'icedyn_rhg_evp', ztaux_oi, 'U', -1.0_wp, ztauy_oi, 'V', -1.0_wp,   & 
     789            &                            ztaux_ai, 'U', -1.0_wp, ztauy_ai, 'V', -1.0_wp,   & 
     790            &                            ztaux_bi, 'U', -1.0_wp, ztauy_bi, 'V', -1.0_wp ) 
    790791         ! 
    791792         CALL iom_put( 'utau_oi' , ztaux_oi * zmsk00 ) 
     
    871872         & iom_use('corstrx') .OR. iom_use('corstry') .OR. iom_use('intstrx') .OR. iom_use('intstry') ) THEN 
    872873         ! 
    873          CALL lbc_lnk_multi( 'icedyn_rhg_evp', zspgU, 'U', -1.0_wp, zspgV, 'V', -1.0_wp, & 
    874             &                                  zCorU, 'U', -1.0_wp, zCorV, 'V', -1.0_wp, zfU, 'U', -1.0_wp, zfV, 'V', -1.0_wp ) 
     874         CALL lbc_lnk( 'icedyn_rhg_evp', zspgU, 'U', -1.0_wp, zspgV, 'V', -1.0_wp, & 
     875            &                            zCorU, 'U', -1.0_wp, zCorV, 'V', -1.0_wp, zfU, 'U', -1.0_wp, zfV, 'V', -1.0_wp ) 
    875876 
    876877         CALL iom_put( 'dssh_dx' , zspgU * zmsk00 )   ! Sea-surface tilt term in force balance (x) 
     
    904905         END_2D 
    905906 
    906          CALL lbc_lnk_multi( 'icedyn_rhg_evp', zdiag_xmtrp_ice, 'U', -1.0_wp, zdiag_ymtrp_ice, 'V', -1.0_wp, & 
    907             &                                  zdiag_xmtrp_snw, 'U', -1.0_wp, zdiag_ymtrp_snw, 'V', -1.0_wp, & 
    908             &                                  zdiag_xatrp    , 'U', -1.0_wp, zdiag_yatrp    , 'V', -1.0_wp ) 
     907         CALL lbc_lnk( 'icedyn_rhg_evp', zdiag_xmtrp_ice, 'U', -1.0_wp, zdiag_ymtrp_ice, 'V', -1.0_wp, & 
     908            &                            zdiag_xmtrp_snw, 'U', -1.0_wp, zdiag_ymtrp_snw, 'V', -1.0_wp, & 
     909            &                            zdiag_xatrp    , 'U', -1.0_wp, zdiag_yatrp    , 'V', -1.0_wp ) 
    909910 
    910911         CALL iom_put( 'xmtrpice' , zdiag_xmtrp_ice )   ! X-component of sea-ice mass transport (kg/s) 
  • NEMO/trunk/tests/ICE_RHEO/MY_SRC/usrdef_nam.F90

    r14021 r14433  
    4040CONTAINS 
    4141 
    42    SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     42   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype ) 
    4343      !!---------------------------------------------------------------------- 
    4444      !!                     ***  ROUTINE dom_nam  *** 
     
    5252      !! ** input   : - namusr_def namelist found in namelist_cfg 
    5353      !!---------------------------------------------------------------------- 
    54       CHARACTER(len=*)              , INTENT(out) ::   cd_cfg          ! configuration name 
    55       INTEGER                       , INTENT(out) ::   kk_cfg          ! configuration resolution 
    56       INTEGER                       , INTENT(out) ::   kpi, kpj, kpk   ! global domain sizes  
    57       INTEGER                       , INTENT(out) ::   kperio          ! lateral global domain b.c.  
     54      CHARACTER(len=*), INTENT(out) ::   cd_cfg               ! configuration name 
     55      INTEGER         , INTENT(out) ::   kk_cfg               ! configuration resolution 
     56      INTEGER         , INTENT(out) ::   kpi, kpj, kpk        ! global domain sizes 
     57      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity 
     58      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding 
     59      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F 
    5860      ! 
    5961      INTEGER ::   ios       ! Local integer 
     
    8183      zly = kpj*rn_dy*1.e-3 
    8284      ! 
    83       kperio = 0     ! closed periodicity for the zoom 
     85      ldIperio = .FALSE.   ;   ldJperio = .FALSE.   ! ICE_RHEO configuration : closed domain 
     86      ldNFold  = .FALSE.   ;   cdNFtype = '-' 
     87      ! 
    8488      !                             ! control print 
    8589      IF(lwp) THEN 
     
    98102         WRITE(numout,*) '         Coriolis:', ln_corio 
    99103         WRITE(numout,*) '   ' 
    100          WRITE(numout,*) '   Lateral boundary condition of the global domain' 
    101          WRITE(numout,*) '      ICE_RHEO closed basin                    jperio = ', kperio 
    102104      ENDIF 
    103105      ! 
  • NEMO/trunk/tests/ICE_RHEO/MY_SRC/usrdef_sbc.F90

    r14273 r14433  
    126126         windv(ji,jj) = Umax/sqrt(d*1000)*(d-2*mjg(jj)*res)/((d-2*mig(ji)*res)**2+(d-2*mjg(jj)*res)**2*Rwind**2)**(1/4)*Rwind*min(kt*30./21600,1.) 
    127127      END_2D 
    128       CALL lbc_lnk_multi( 'usrdef_sbc', windu, 'U', -1., windv, 'V', -1. ) 
     128      CALL lbc_lnk( 'usrdef_sbc', windu, 'U', -1., windv, 'V', -1. ) 
    129129 
    130130      wndm_ice(:,:) = 0._wp      !!gm brutal.... 
     
    156156            &          * ( 0.5 * (windv(ji,jj+1) + windv(ji,jj) ) - r_vfac * v_ice(ji,jj) ) 
    157157      END_2D 
    158       CALL lbc_lnk_multi( 'usrdef_sbc', utau_ice, 'U', -1., vtau_ice, 'V', -1. ) 
     158      CALL lbc_lnk( 'usrdef_sbc', utau_ice, 'U', -1., vtau_ice, 'V', -1. ) 
    159159      ! 
    160160   END SUBROUTINE usrdef_sbc_ice_tau 
  • NEMO/trunk/tests/ISOMIP/MY_SRC/usrdef_nam.F90

    r13286 r14433  
    4141CONTAINS 
    4242 
    43    SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     43   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype ) 
    4444      !!---------------------------------------------------------------------- 
    4545      !!                     ***  ROUTINE dom_nam  *** 
     
    5353      !! ** input   : - namusr_def namelist found in namelist_cfg 
    5454      !!---------------------------------------------------------------------- 
    55       CHARACTER(len=*)              , INTENT(out) ::   cd_cfg          ! configuration name 
    56       INTEGER                       , INTENT(out) ::   kk_cfg          ! configuration resolution 
    57       INTEGER                       , INTENT(out) ::   kpi, kpj, kpk   ! global domain sizes  
    58       INTEGER                       , INTENT(out) ::   kperio          ! lateral global domain b.c.  
     55      CHARACTER(len=*), INTENT(out) ::   cd_cfg               ! configuration name 
     56      INTEGER         , INTENT(out) ::   kk_cfg               ! configuration resolution 
     57      INTEGER         , INTENT(out) ::   kpi, kpj, kpk        ! global domain sizes 
     58      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity 
     59      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding 
     60      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F 
    5961      ! 
    6062      INTEGER ::   ios   ! Local integer 
     
    7779      ! 
    7880      !                             ! Set the lateral boundary condition of the global domain 
    79       kperio = 0                    ! ISOMIP configuration : close basin 
     81      ldIperio = .FALSE.   ;   ldJperio = .FALSE.   ! ISOMIP configuration : closed domain 
     82      ldNFold  = .FALSE.   ;   cdNFtype = '-' 
    8083      ! 
    8184      !                             ! control print 
     
    98101         WRITE(numout,*) '                                               jpkglo   = ', kpk 
    99102         WRITE(numout,*) '   ' 
    100          WRITE(numout,*) '   Lateral boundary condition of the global domain' 
    101          WRITE(numout,*) '      ISOMIP : closed basin                    jperio   = ', kperio 
    102103      ENDIF 
    103104      ! 
  • NEMO/trunk/tests/LOCK_EXCHANGE/MY_SRC/usrdef_nam.F90

    r13286 r14433  
    3737CONTAINS 
    3838 
    39    SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     39   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype ) 
    4040      !!---------------------------------------------------------------------- 
    4141      !!                     ***  ROUTINE dom_nam  *** 
     
    4949      !! ** input   : - namusr_def namelist found in namelist_cfg 
    5050      !!---------------------------------------------------------------------- 
    51       CHARACTER(len=*)              , INTENT(out) ::   cd_cfg          ! configuration name 
    52       INTEGER                       , INTENT(out) ::   kk_cfg          ! configuration resolution 
    53       INTEGER                       , INTENT(out) ::   kpi, kpj, kpk   ! global domain sizes  
    54       INTEGER                       , INTENT(out) ::   kperio          ! lateral global domain b.c.  
     51      CHARACTER(len=*), INTENT(out) ::   cd_cfg               ! configuration name 
     52      INTEGER         , INTENT(out) ::   kk_cfg               ! configuration resolution 
     53      INTEGER         , INTENT(out) ::   kpi, kpj, kpk        ! global domain sizes 
     54      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity 
     55      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding 
     56      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F 
    5557      ! 
    5658      INTEGER ::   ios   ! Local integer 
     
    7375      kpk = INT(  20.  / rn_dz ) + 1 
    7476      !                             ! Set the lateral boundary condition of the global domain 
    75       kperio = 0                    ! LOCK_EXCHANGE configuration : closed domain 
     77      ldIperio = .FALSE.   ;   ldJperio = .FALSE.   ! LOCK_EXCHANGE configuration : closed domain 
     78      ldNFold  = .FALSE.   ;   cdNFtype = '-' 
    7679      ! 
    7780      !                             ! control print 
     
    8891         WRITE(numout,*) '                                               jpkglo = ', kpk 
    8992         WRITE(numout,*) '   ' 
    90          WRITE(numout,*) '   Lateral boundary condition of the global domain' 
    91          WRITE(numout,*) '      closed                                   jperio = ', kperio 
    9293      ENDIF 
    9394      ! 
  • NEMO/trunk/tests/LOCK_EXCHANGE/MY_SRC/usrdef_zgr.F90

    r12377 r14433  
    8484      ! 
    8585      ! no ocean cavities : top ocean level is ONE, except over land 
    86       ! the ocean basin surrounded by land (1 grid-point) set through lbc_lnk call as jperio=0  
     86      ! the ocean basin surrounded by land (1+nn_hls grid-points) set through lbc_lnk call 
    8787      z2d(:,:) = 1._wp                    ! surface ocean is the 1st level 
    88       CALL lbc_lnk( 'usrdef_zgr', z2d, 'T', 1. )        ! closed basin since jperio = 0 (see userdef_nam.F90) 
     88      CALL lbc_lnk( 'usrdef_zgr', z2d, 'T', 1. )        ! closed basin, see userdef_nam.F90 
    8989      k_top(:,:) = NINT( z2d(:,:) ) 
    9090      ! 
  • NEMO/trunk/tests/OVERFLOW/MY_SRC/usrdef_nam.F90

    r13286 r14433  
    3838CONTAINS 
    3939 
    40    SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     40   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype ) 
    4141      !!---------------------------------------------------------------------- 
    4242      !!                     ***  ROUTINE dom_nam  *** 
     
    5050      !! ** input   : - namusr_def namelist found in namelist_cfg 
    5151      !!---------------------------------------------------------------------- 
    52       CHARACTER(len=*)              , INTENT(out) ::   cd_cfg          ! configuration name 
    53       INTEGER                       , INTENT(out) ::   kk_cfg          ! configuration resolution 
    54       INTEGER                       , INTENT(out) ::   kpi, kpj, kpk   ! global domain sizes  
    55       INTEGER                       , INTENT(out) ::   kperio          ! lateral global domain b.c.  
     52      CHARACTER(len=*), INTENT(out) ::   cd_cfg               ! configuration name 
     53      INTEGER         , INTENT(out) ::   kk_cfg               ! configuration resolution 
     54      INTEGER         , INTENT(out) ::   kpi, kpj, kpk        ! global domain sizes 
     55      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity 
     56      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding 
     57      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F 
    5658      ! 
    5759      INTEGER ::   ios   ! Local integer 
     
    8890      WRITE(numout,*) '                                               Nj0glo = ', kpj 
    8991      WRITE(numout,*) '                                               jpkglo = ', kpk 
     92      WRITE(numout,*) '   ' 
    9093      ! 
    9194      !                             ! Set the lateral boundary condition of the global domain 
    92       kperio = 0                    ! OVERFLOW configuration : close basin 
    93       ! 
    94       WRITE(numout,*) '   ' 
    95       WRITE(numout,*) '   Lateral boundary condition of the global domain' 
    96       WRITE(numout,*) '      OVERFLOW : closed basin                  jperio = ', kperio 
     95      ldIperio = .FALSE.   ;   ldJperio = .FALSE.   ! OVERFLOW configuration : closed domain 
     96      ldNFold  = .FALSE.   ;   cdNFtype = '-' 
    9797      ! 
    9898   END SUBROUTINE usr_def_nam 
  • NEMO/trunk/tests/OVERFLOW/MY_SRC/usrdef_zgr.F90

    r14053 r14433  
    110110      ! 
    111111      ! no ocean cavities : top ocean level is ONE, except over land 
    112       ! the ocean basin surrounded by land (1 grid-point) set through lbc_lnk call as jperio=0  
     112      ! the ocean basin surrounded by land (1+nn_hls grid-points) set through lbc_lnk call 
    113113      z2d(:,:) = 1._wp                    ! surface ocean is the 1st level 
    114       CALL lbc_lnk( 'usrdef_zgr', z2d, 'T', 1. )        ! closed basin since jperio = 0 (see userdef_nam.F90) 
     114      CALL lbc_lnk( 'usrdef_zgr', z2d, 'T', 1. )        ! closed basin, see userdef_nam.F90 
    115115      k_top(:,:) = NINT( z2d(:,:) ) 
    116116      ! 
  • NEMO/trunk/tests/STATION_ASF/MY_SRC/icesbc.F90

    r14072 r14433  
    9191         vtau_ice(ji,jj) = vtau_ice(ji,jj) * xcplmask(ji,jj,0) + zvtau_ice(ji,jj) * ( 1. - xcplmask(ji,jj,0) ) 
    9292         END_2D 
    93          CALL lbc_lnk_multi( 'icesbc', utau_ice, 'U', -1.0_wp, vtau_ice, 'V', -1.0_wp ) 
     93         CALL lbc_lnk( 'icesbc', utau_ice, 'U', -1.0_wp, vtau_ice, 'V', -1.0_wp ) 
    9494      ENDIF 
    9595      ! 
  • NEMO/trunk/tests/STATION_ASF/MY_SRC/nemogcm.F90

    r14239 r14433  
    243243      ! 
    244244      IF( ln_read_cfg ) THEN            ! Read sizes in domain configuration file 
    245          CALL domain_cfg ( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, jperio ) 
     245         CALL domain_cfg ( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, l_Iperio, l_Jperio, l_NFold, c_NFtype ) 
    246246      ELSE                              ! user-defined namelist 
    247          CALL usr_def_nam( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, jperio ) 
     247         CALL usr_def_nam( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, l_Iperio, l_Jperio, l_NFold, c_NFtype ) 
    248248      ENDIF 
    249249      ! 
  • NEMO/trunk/tests/STATION_ASF/MY_SRC/stpctl.F90

    r14318 r14433  
    113113      !                                   !==  done by all processes at every time step  ==! 
    114114      ! 
    115       llmsk(   1:Nis1,:) = .FALSE.                                              ! exclude halos from the checked region 
    116       llmsk(Nie1: jpi,:) = .FALSE. 
    117       llmsk(:,   1:Njs1) = .FALSE. 
    118       llmsk(:,Nje1: jpj) = .FALSE. 
     115      llmsk(     1:nn_hls,:) = .FALSE.                                          ! exclude halos from the checked region 
     116      llmsk(Nie0+1:  jpi,:) = .FALSE. 
     117      llmsk(:,     1:nn_hls) = .FALSE. 
     118      llmsk(:,Nje0+1:  jpj) = .FALSE. 
    119119      ! 
    120120      llmsk(Nis0:Nie0,Njs0:Nje0) = tmask(Nis0:Nie0,Njs0:Nje0,1) == 1._wp        ! test only the inner domain 
  • NEMO/trunk/tests/STATION_ASF/MY_SRC/usrdef_nam.F90

    r14072 r14433  
    3737CONTAINS 
    3838 
    39    SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     39   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype ) 
    4040      !!---------------------------------------------------------------------- 
    4141      !!                     ***  ROUTINE dom_nam  *** 
     
    4949      !! ** input   : - namusr_def namelist found in namelist_cfg 
    5050      !!---------------------------------------------------------------------- 
    51       CHARACTER(len=*), INTENT(out) ::   cd_cfg          ! configuration name 
    52       INTEGER         , INTENT(out) ::   kk_cfg          ! configuration resolution 
    53       INTEGER         , INTENT(out) ::   kpi, kpj, kpk   ! global domain sizes 
    54       INTEGER         , INTENT(out) ::   kperio          ! lateral global domain b.c. 
     51      CHARACTER(len=*), INTENT(out) ::   cd_cfg               ! configuration name 
     52      INTEGER         , INTENT(out) ::   kk_cfg               ! configuration resolution 
     53      INTEGER         , INTENT(out) ::   kpi, kpj, kpk        ! global domain sizes 
     54      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity 
     55      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding 
     56      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F 
    5557      ! 
    5658      INTEGER ::   ios   ! Local integer 
     
    7375      ! 
    7476      !                             ! Set the lateral boundary condition of the global domain 
    75       kperio =  7                   ! C1D configuration : 3x3 basin with cyclic Est-West and Norht-South condition 
     77      ldIperio = .TRUE.    ;   ldJperio = .true.   ! C1D configuration : 3x3 basin with cyclic Est-West and Norht-South condition 
     78      ldNFold  = .FALSE.   ;   cdNFtype = '-' 
    7679      ! 
    7780      !                             ! control print 
     
    8588         WRITE(numout,*) '      number of model levels                              kpk = ', kpk 
    8689         WRITE(numout,*) '   ' 
    87          WRITE(numout,*) '   Lateral b.c. of the domain set to       jperio = ', kperio 
    8890      ENDIF 
    8991      ! 
  • NEMO/trunk/tests/SWG/MY_SRC/usrdef_nam.F90

    r13752 r14433  
    5757CONTAINS 
    5858 
    59    SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     59   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype ) 
    6060      !!---------------------------------------------------------------------- 
    6161      !!                     ***  ROUTINE dom_nam  *** 
     
    6969      !! ** input   : - namusr_def namelist found in namelist_cfg 
    7070      !!---------------------------------------------------------------------- 
    71       CHARACTER(len=*), INTENT(out) ::   cd_cfg          ! configuration name 
    72       INTEGER         , INTENT(out) ::   kk_cfg          ! configuration resolution 
    73       INTEGER         , INTENT(out) ::   kpi, kpj, kpk   ! global domain sizes  
    74       INTEGER         , INTENT(out) ::   kperio          ! lateral global domain b.c.  
     71      CHARACTER(len=*), INTENT(out) ::   cd_cfg               ! configuration name 
     72      INTEGER         , INTENT(out) ::   kk_cfg               ! configuration resolution 
     73      INTEGER         , INTENT(out) ::   kpi, kpj, kpk        ! global domain sizes 
     74      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity 
     75      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding 
     76      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F 
    7577      ! 
    7678      INTEGER  ::   ios             ! Local integer 
     
    110112      kpk = jpkglo 
    111113      !                             ! Set the lateral boundary condition of the global domain 
    112       kperio = 0                    ! SWG configuration : closed domain 
     114      ldIperio = .FALSE.   ;   ldJperio = .FALSE.   ! SWG configuration : closed domain 
     115      ldNFold  = .FALSE.   ;   cdNFtype = '-' 
    113116      ! 
    114117# if defined key_bvp 
     
    131134         WRITE(numout,*) '      number of model levels                              jpkglo = ', kpk 
    132135         WRITE(numout,*) '   ' 
    133          WRITE(numout,*) '   Lateral b.c. of the global domain set to closed        jperio = ', kperio 
    134136      ENDIF 
    135137      ! 
  • NEMO/trunk/tests/SWG/MY_SRC/usrdef_sbc.F90

    r13752 r14433  
    104104      END DO 
    105105       
    106       CALL lbc_lnk_multi( 'usrdef_sbc', taum(:,:), 'T', 1. , wndm(:,:), 'T', 1. ) 
     106      CALL lbc_lnk( 'usrdef_sbc', taum(:,:), 'T', 1. , wndm(:,:), 'T', 1. ) 
    107107      ! 
    108108   END SUBROUTINE usrdef_sbc_oce 
  • NEMO/trunk/tests/SWG/MY_SRC/usrdef_zgr.F90

    r14204 r14433  
    190190      z2d(:,:) = REAL( jpkm1 , wp )          ! flat bottom 
    191191      ! 
    192       CALL lbc_lnk( 'usrdef_zgr', z2d, 'T', 1. )           ! set surrounding land to zero (here jperio=0 ==>> closed) 
    193       ! 
    194       !  
     192      CALL lbc_lnk( 'usrdef_zgr', z2d, 'T', 1. )           ! set surrounding land to zero (closed boundaries) 
     193      ! 
    195194      zylim0 =   10000._wp    ! +10km  
    196195      zylim1 = 2010000._wp    ! 2010km 
  • NEMO/trunk/tests/TSUNAMI/EXPREF/namelist_cfg

    r14297 r14433  
    2929   nn_fcase    =      0    !  Coriolis frequency(f) computation (0:f0, 1:Beta plan, 2:real) 
    3030   rn_ppgphi0  =    38.5   !  Reference latitude      [degrees] 
    31    nn_perio    =      7 
     31   ln_Iperio  =   .true.   ! i-periodicity 
     32   ln_Jperio  =   .true.   ! j-periodicity 
    3233/ 
    3334!----------------------------------------------------------------------- 
  • NEMO/trunk/tests/TSUNAMI/MY_SRC/usrdef_hgr.F90

    r14225 r14433  
    6464      ! 
    6565      INTEGER  ::   ji, jj     ! dummy loop indices 
    66       REAL(wp) ::   zphi0, zlam0, zbeta, zf0 
     66      INTEGER  ::   ii0, ij0   ! dummy loop indices 
     67      REAL(wp) ::   zbeta, zf0 
    6768      REAL(wp) ::   zti, ztj   ! local scalars 
    6869      !!------------------------------------------------------------------------------- 
     
    7778      ! Position coordinates (in kilometers) 
    7879      !                          ========== 
    79       zlam0 = -REAL(Ni0glo, wp) * rn_0xratio * rn_dx 
    80       zphi0 = -REAL(Nj0glo, wp) * rn_0yratio * rn_dy 
     80      ii0 = NINT( REAL(Ni0glo, wp) * rn_0xratio ) 
     81      ij0 = NINT( REAL(Nj0glo, wp) * rn_0yratio ) 
    8182 
    8283#if defined key_agrif 
    8384      ! ! let lower left longitude and latitude from parent 
    8485      IF (.NOT.Agrif_root()) THEN 
    85           zlam0 = (0.5_wp-(Agrif_parent(jpiglo)-1)/2)*Agrif_irhox()*rn_dx & 
    86              &+(Agrif_Ix()+nbghostcells-1)*Agrif_irhox()*rn_dx-(0.5_wp+nbghostcells)*rn_dx 
    87           zphi0 = (0.5_wp-(Agrif_parent(jpjglo)-1)/2)*Agrif_irhoy()*rn_dy & 
    88              &+(Agrif_Iy()+nbghostcells-1)*Agrif_irhoy()*rn_dy-(0.5_wp+nbghostcells)*rn_dy 
     86          to be coded... 
    8987      ENDIF  
    9088#endif 
    9189          
    9290      DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )          
    93          zti = REAL( mig0(ji), wp ) - 0.5_wp  ! start at i=0.5 in the global grid without halos 
    94          ztj = REAL( mjg0(jj), wp ) - 0.5_wp  ! start at j=0.5 in the global grid without halos 
     91         zti = REAL( mig0(ji)-ii0, wp )   ! =0 at i=ii0 in the global grid without halos 
     92         ztj = REAL( mjg0(jj)-ij0, wp )   ! =0 at i=ij0 in the global grid without halos 
    9593          
    96          plamt(ji,jj) = zlam0 + rn_dx *   zti 
    97          plamu(ji,jj) = zlam0 + rn_dx * ( zti + 0.5_wp )  
     94         plamt(ji,jj) = rn_dx *   zti 
     95         plamu(ji,jj) = rn_dx * ( zti + 0.5_wp )  
    9896         plamv(ji,jj) = plamt(ji,jj)  
    9997         plamf(ji,jj) = plamu(ji,jj)  
    10098          
    101          pphit(ji,jj) = zphi0 + rn_dy *   ztj 
    102          pphiv(ji,jj) = zphi0 + rn_dy * ( ztj + 0.5_wp )  
     99         pphit(ji,jj) = rn_dy *   ztj 
     100         pphiv(ji,jj) = rn_dy * ( ztj + 0.5_wp )  
    103101         pphiu(ji,jj) = pphit(ji,jj)  
    104102         pphif(ji,jj) = pphiv(ji,jj)  
  • NEMO/trunk/tests/TSUNAMI/MY_SRC/usrdef_nam.F90

    r14297 r14433  
    3737   INTEGER , PUBLIC ::   nn_fcase   =    1   ! F computation (0:f0, 1:Beta, 2:real) 
    3838   REAL(wp), PUBLIC ::   rn_ppgphi0 =   38.5 ! reference latitude for beta-plane  
    39    INTEGER , PUBLIC ::   nn_perio   =    0   ! periodicity of the channel (0=closed, 1=E-W) 
    4039 
    4140   !!---------------------------------------------------------------------- 
     
    4645CONTAINS 
    4746 
    48    SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     47   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype ) 
    4948      !!---------------------------------------------------------------------- 
    5049      !!                     ***  ROUTINE dom_nam  *** 
     
    5857      !! ** input   : - namusr_def namelist found in namelist_cfg 
    5958      !!---------------------------------------------------------------------- 
    60       CHARACTER(len=*)              , INTENT(out) ::   cd_cfg          ! configuration name 
    61       INTEGER                       , INTENT(out) ::   kk_cfg          ! configuration resolution 
    62       INTEGER                       , INTENT(out) ::   kpi, kpj, kpk   ! global domain sizes  
    63       INTEGER                       , INTENT(out) ::   kperio          ! lateral global domain b.c.  
     59      CHARACTER(len=*), INTENT(out) ::   cd_cfg               ! configuration name 
     60      INTEGER         , INTENT(out) ::   kk_cfg               ! configuration resolution 
     61      INTEGER         , INTENT(out) ::   kpi, kpj, kpk        ! global domain sizes 
     62      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity 
     63      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding 
     64      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F 
    6465      ! 
    6566      INTEGER ::   ios      ! Local integer 
     67      LOGICAL ::   ln_Iperio, ln_Jperio 
    6668      !! 
    6769      NAMELIST/namusr_def/  rn_domszx, rn_domszy, rn_domszz, rn_dx, rn_dy, rn_0xratio, rn_0yratio   & 
    68          &                 , nn_fcase, rn_ppgphi0, nn_perio 
     70         &                 , nn_fcase, rn_ppgphi0, ln_Iperio, ln_Jperio 
    6971      !!---------------------------------------------------------------------- 
    7072      ! 
     
    8587#endif 
    8688      ! 
    87       IF(lwm)   WRITE( numond, namusr_def ) 
    88       ! 
    8989      cd_cfg = 'TSUNAMI'             ! name & resolution (not used) 
    9090      kk_cfg = INT( rn_dx ) 
     
    9292      IF( Agrif_Root() ) THEN        ! Global Domain size:  TSUNAMI global domain is  1800 km x 1800 Km x 5000 m 
    9393         kpi = NINT( rn_domszx / rn_dx ) + 1 
    94          kpj = NINT( rn_domszy / rn_dy ) + 3 
     94         kpj = NINT( rn_domszy / rn_dy ) + 1 
    9595      ELSE                           ! Global Domain size: add nbghostcells + 1 "land" point on each side 
    9696         kpi  = nbcellsx + nbghostcells_x   + nbghostcells_x   + 2 
     
    9898      ENDIF 
    9999      kpk = 2 
    100       !                             ! Set the lateral boundary condition of the global domain 
    101       kperio = 1                    ! TSUNAMI configuration : closed basin 
    102       !                             ! control print 
     100      !                              ! Set the lateral boundary condition of the global domain 
     101      ! 
     102      ldIperio = ln_Iperio   ;   ldJperio = ln_Jperio 
     103      ldNFold  =  .FALSE.    ;   cdNFtype = '-' 
     104      ! 
     105      !                              ! control print 
    103106      IF(lwp) THEN 
    104107         WRITE(numout,*) '   ' 
     
    115118         WRITE(numout,*) '      F computation                     nn_fcase   = ',   nn_fcase 
    116119         WRITE(numout,*) '      Reference latitude                rn_ppgphi0 = ', rn_ppgphi0 
    117          WRITE(numout,*) '      Periodicity of the basin            nn_perio = ', nn_perio 
     120         WRITE(numout,*) '   ' 
    118121      ENDIF 
    119       !                             ! Set the lateral boundary condition of the global domain 
    120       kperio = nn_perio                    ! TSUNAMI configuration : closed basin 
    121122      ! 
    122123   END SUBROUTINE usr_def_nam 
  • NEMO/trunk/tests/TSUNAMI/MY_SRC/usrdef_sbc.F90

    r14225 r14433  
    33   !!                       ***  MODULE  usrdef_sbc  *** 
    44   !!  
    5    !!                      ===  CANAL configuration  === 
     5   !!                      ===  TSUNAMI configuration  === 
    66   !! 
    77   !! User defined :   surface forcing of a user configuration 
     
    4444      !!              condition, i.e. the momentum, heat and freshwater fluxes. 
    4545      !! 
    46       !! ** Method  :   all 0 fields, for CANAL case 
     46      !! ** Method  :   all 0 fields, for TSUNAMI case 
    4747      !!                CAUTION : never mask the surface stress field ! 
    4848      !! 
     
    5757      IF( kt == nit000 ) THEN 
    5858         ! 
    59          IF(lwp) WRITE(numout,*)' usr_sbc : EW_CANAL case: surface forcing' 
     59         IF(lwp) WRITE(numout,*)' usr_sbc : TSUNAMI case: surface forcing' 
    6060         IF(lwp) WRITE(numout,*)' ~~~~~~~~~~~   vtau = taum = wndm = qns = qsr = emp = sfx = 0' 
    6161         ! 
  • NEMO/trunk/tests/VORTEX/MY_SRC/usrdef_istate.F90

    r14133 r14433  
    123123      END_2D 
    124124      ! 
    125       CALL lbc_lnk_multi( 'usrdef_istate', pu, 'U', -1., pv, 'V', -1. ) 
     125      CALL lbc_lnk( 'usrdef_istate', pu, 'U', -1., pv, 'V', -1. ) 
    126126      !    
    127127   END SUBROUTINE usr_def_istate 
  • NEMO/trunk/tests/VORTEX/MY_SRC/usrdef_nam.F90

    r14086 r14433  
    4040CONTAINS 
    4141 
    42    SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     42   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype ) 
    4343      !!---------------------------------------------------------------------- 
    4444      !!                     ***  ROUTINE dom_nam  *** 
     
    5252      !! ** input   : - namusr_def namelist found in namelist_cfg 
    5353      !!---------------------------------------------------------------------- 
    54       CHARACTER(len=*)              , INTENT(out) ::   cd_cfg          ! configuration name 
    55       INTEGER                       , INTENT(out) ::   kk_cfg          ! configuration resolution 
    56       INTEGER                       , INTENT(out) ::   kpi, kpj, kpk   ! global domain sizes  
    57       INTEGER                       , INTENT(out) ::   kperio          ! lateral global domain b.c.  
     54      CHARACTER(len=*), INTENT(out) ::   cd_cfg               ! configuration name 
     55      INTEGER         , INTENT(out) ::   kk_cfg               ! configuration resolution 
     56      INTEGER         , INTENT(out) ::   kpi, kpj, kpk        ! global domain sizes 
     57      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity 
     58      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding 
     59      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F 
    5860      ! 
    5961      INTEGER ::   ios          ! Local integer 
     
    9698      zh  = (kpk-1)*rn_dz 
    9799      !                             ! Set the lateral boundary condition of the global domain 
    98       kperio = 0                    ! VORTEX configuration : closed basin 
     100      ldIperio = .FALSE.   ;   ldJperio = .FALSE.   ! VORTEX configuration : closed domain 
     101      ldNFold  = .FALSE.   ;   cdNFtype = '-' 
     102      ! 
    99103      !                             ! control print 
    100104      IF(lwp) THEN 
     
    115119         WRITE(numout,*) '      Reference latitude            rn_ppgphi0 = ', rn_ppgphi0 
    116120         WRITE(numout,*) '   ' 
    117          WRITE(numout,*) '   Lateral boundary condition of the global domain' 
    118          WRITE(numout,*) '      VORTEX : closed basin            jperio = ', kperio 
    119121      ENDIF 
    120122      ! 
  • NEMO/trunk/tests/VORTEX/MY_SRC/usrdef_zgr.F90

    r12740 r14433  
    190190      z2d(:,:) = REAL( jpkm1 , wp )          ! flat bottom 
    191191      ! 
    192       CALL lbc_lnk( 'usrdef_zgr', z2d, 'T', 1. )           ! set surrounding land to zero (here jperio=0 ==>> closed) 
     192      CALL lbc_lnk( 'usrdef_zgr', z2d, 'T', 1. )           ! set surrounding land to zero (closed boundaries) 
    193193      ! 
    194194      k_bot(:,:) = NINT( z2d(:,:) )          ! =jpkm1 over the ocean point, =0 elsewhere 
  • NEMO/trunk/tests/WAD/MY_SRC/usrdef_nam.F90

    r13286 r14433  
    3838CONTAINS 
    3939 
    40    SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     40   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype ) 
    4141      !!---------------------------------------------------------------------- 
    4242      !!                     ***  ROUTINE dom_nam  *** 
     
    5050      !! ** input   : - namusr_def namelist found in namelist_cfg 
    5151      !!---------------------------------------------------------------------- 
    52       CHARACTER(len=*)              , INTENT(out) ::   cd_cfg          ! configuration name 
    53       INTEGER                       , INTENT(out) ::   kk_cfg          ! configuration resolution 
    54       INTEGER                       , INTENT(out) ::   kpi, kpj, kpk   ! global domain sizes  
    55       INTEGER                       , INTENT(out) ::   kperio          ! lateral global domain b.c.  
     52      CHARACTER(len=*), INTENT(out) ::   cd_cfg               ! configuration name 
     53      INTEGER         , INTENT(out) ::   kk_cfg               ! configuration resolution 
     54      INTEGER         , INTENT(out) ::   kpi, kpj, kpk        ! global domain sizes 
     55      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity 
     56      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding 
     57      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F 
    5658      ! 
    5759      INTEGER ::   ios   ! Local integer 
     
    7577      kpk = INT(  10.  / rn_dz ) + 1 
    7678      !                             ! Set the lateral boundary condition of the global domain 
    77       kperio = 0                    ! WAD_TEST_CASES configuration : closed domain 
     79      ldIperio = .FALSE.   ;   ldJperio = .FALSE.    ! WAD_TEST_CASES configuration : closed domain 
     80      ldNFold  = .FALSE.   ;   cdNFtype = '-' 
    7881      IF( nn_wad_test == 8 ) THEN 
    79          kperio = 7         ! North-South cyclic test 
     82         ldIperio = .TRUE.   ;   ldJperio = .TRUE.   ! WAD_TEST_CASES configuration : bi-periodic 
    8083         kpi = kpi - 2      ! no closed boundary 
    8184         kpj = kpj - 2      ! no closed boundary 
     
    9598         WRITE(numout,*) '                                               jpkglo = ', kpk 
    9699         WRITE(numout,*) '   ' 
    97          WRITE(numout,*) '   Lateral boundary condition of the global domain' 
    98          WRITE(numout,*) '      closed                                   jperio = ', kperio 
    99100      ENDIF 
    100101      ! 
  • NEMO/trunk/tests/WAD/MY_SRC/usrdef_zgr.F90

    r13295 r14433  
    260260      ! 
    261261      ! no ocean cavities : top ocean level is ONE, except over land 
    262       ! the ocean basin surrounnded by land (1 grid-point) set through lbc_lnk call as jperio=0  
     262      ! the ocean basin surrounnded by land (1+nn_hls grid-points) set through lbc_lnk call 
    263263      z2d(:,:) = 1._wp                    ! surface ocean is the 1st level 
    264264      z2d(mi0(1):mi1(1),:) = 0._wp 
     
    267267      z2d(:,mj0(jpjglo):mj1(jpjglo)) = 0._wp 
    268268 
    269  
    270  
    271  
    272  
    273       CALL lbc_lnk( 'usrdef_zgr', z2d, 'T', 1. )        ! closed basin since jperio = 0 (see userdef_nam.F90) 
     269      CALL lbc_lnk( 'usrdef_zgr', z2d, 'T', 1. )        ! closed basin, see userdef_nam.F90 
    274270      k_top(:,:) = NINT( z2d(:,:) ) 
    275271      ! 
Note: See TracChangeset for help on using the changeset viewer.