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 14336 for NEMO/branches/2021 – NEMO

Changeset 14336 for NEMO/branches/2021


Ignore:
Timestamp:
2021-01-23T11:09:54+01:00 (3 years ago)
Author:
smasson
Message:

dev_r14312_MPI_Interface: replace jperio by l_Iperio, l_Jperio, l_NFold, c_NFtype, #2598

Location:
NEMO/branches/2021/dev_r14312_MPI_Interface
Files:
1 deleted
53 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r14312_MPI_Interface/cfgs/C1D_PAPA/MY_SRC/usrdef_nam.F90

    r12377 r14336  
    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 
     
    7476      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/branches/2021/dev_r14312_MPI_Interface/doc/NEMO_manual_state.txt

    r13461 r14336  
    1515chap_misc.tex: key{mpp\_mpi} key{nosignedzero} key{vectopt\_loop} np{iom\_get} np{jpjdta} np{jpjglo} np{nn\_bench} np{nn\_bit\_cmp} np{open\_ocean\_jstart}  
    1616chap_LDF.tex: hf{dynldf\_cNd} hf{ldfdyn\_substitute} hf{ldftra\_substitute} hf{traldf\_c1d} hf{traldf\_cNd} key{dynldf\_c1d} key{dynldf\_c2d} key{dynldf\_c3d} key{traldf\_c1d} key{traldf\_c2d} key{traldf\_c3d} key{traldf\_cNd} key{traldf\_eiv} mdl{ldfdyn\_c2d} mdl{ldfeiv} mdl{traadv\_eiv} np{ln\_dynldf\_bilap} np{ln\_sco} np{nn\_eos} np{rn\_aeih\_0} np{rn\_aeiv} np{rn\_aeiv\_0} np{rn\_ahm0} np{rn\_ahmb0} np{rn\_aht0} np{rn\_ahtb0} np{traldf\_grif} np{traldf\_grif\_iso} rou{ldf\_dyn\_c2d\_orca} rou{ldfslp\_init}  
    17 chap_LBC.tex: jp{jpreci} key{mpp\_mpi} np{jperio} np{jpiglo} np{jpindt} np{jpinft} np{jpjglo} np{jpjnob} np{nbdysegn} np{nn\_bdy\_jpk} np{nn\_msh} np{nn\_tra} rou{inimpp2}  
    18 chap_DOM.tex: key{mpp\_mpi} ngn{namzgr} ngn{namzgr\_sco} nlst{namzgr} nlst{namzgr_sco} np{jperio} np{jpiglo} np{jpjglo} np{jpkglo} np{ln\_sco} np{ln\_sigcrit} np{ln\_s\_SF12} np{ln\_s\_SH94} np{ln\_tsd\_ini} np{ln\_zco} np{ln\_zps} np{nn\_bathy} np{nn\_msh} np{ppa0} np{ppa1} np{ppacr} np{ppdzmin} np{pphmax} np{ppkth} np{ppsur} np{rn\_alpha} np{rn\_bb} np{rn\_e3zps\_min} np{rn\_e3zps\_rat} np{rn\_hc} np{rn\_rmax} np{rn\_sbot\_max} np{rn\_sbot\_min} np{rn\_theta} np{rn\_zb\_a} np{rn\_zb\_b} np{rn\_zs} rou{istate\_t\_s}  
     17chap_LBC.tex: jp{jpreci} key{mpp\_mpi} np{jpiglo} np{jpindt} np{jpinft} np{jpjglo} np{jpjnob} np{nbdysegn} np{nn\_bdy\_jpk} np{nn\_msh} np{nn\_tra} rou{inimpp2}  
     18chap_DOM.tex: key{mpp\_mpi} ngn{namzgr} ngn{namzgr\_sco} nlst{namzgr} nlst{namzgr_sco} np{jpiglo} np{jpjglo} np{jpkglo} np{ln\_sco} np{ln\_sigcrit} np{ln\_s\_SF12} np{ln\_s\_SH94} np{ln\_tsd\_ini} np{ln\_zco} np{ln\_zps} np{nn\_bathy} np{nn\_msh} np{ppa0} np{ppa1} np{ppacr} np{ppdzmin} np{pphmax} np{ppkth} np{ppsur} np{rn\_alpha} np{rn\_bb} np{rn\_e3zps\_min} np{rn\_e3zps\_rat} np{rn\_hc} np{rn\_rmax} np{rn\_sbot\_max} np{rn\_sbot\_min} np{rn\_theta} np{rn\_zb\_a} np{rn\_zb\_b} np{rn\_zs} rou{istate\_t\_s}  
    1919chap_conservation.tex: key{\_}  
    2020annex_iso.tex: key{trabbl} key{traldf\_eiv} np{ln\_traldf\_eiv} np{ln\_traldf\_gdia}  
  • NEMO/branches/2021/dev_r14312_MPI_Interface/doc/latex/NEMO/subfiles/chap_DOM.tex

    r14257 r14336  
    377377in which case \np{cn_cfg}{cn\_cfg} and \np{nn_cfg}{nn\_cfg} are set from these values accordingly). 
    378378 
    379 The global lateral boundary condition type is selected from 8 options using parameter \texttt{jperio}. 
     379The global lateral boundary condition type is selected from 8 options using parameters \texttt{l\_Iperio}, \texttt{l\_Jperio}, \texttt{l\_NFold} and \texttt{c\_NFtype}. 
    380380See \autoref{sec:LBC_jperio} for details on the available options and 
    381 the corresponding values for \texttt{jperio}. 
     381the corresponding values for \texttt{l\_Iperio}, \texttt{l\_Jperio}, \texttt{l\_NFold} and \texttt{c\_NFtype}. 
    382382 
    383383%% ================================================================================================= 
     
    394394 
    395395\begin{clines} 
    396 int    jpiglo, jpjglo, jpkglo     /* global domain sizes                                    */ 
    397 int    jperio                     /* lateral global domain b.c.                             */ 
    398 double glamt, glamu, glamv, glamf /* geographic longitude (t,u,v and f points respectively) */ 
    399 double gphit, gphiu, gphiv, gphif /* geographic latitude                                    */ 
    400 double e1t, e1u, e1v, e1f         /* horizontal scale factors                               */ 
    401 double e2t, e2u, e2v, e2f         /* horizontal scale factors                               */ 
     396integer   Ni0glo, NjOglo, jpkglo       /* global domain sizes (without MPI halos)                */ 
     397logical   l\_Iperio, l\_Jperio         /* lateral global domain b.c.: i- j-periodicity           */ 
     398logical   l\_NFold                     /* lateral global domain b.c.: North Pole folding         */ 
     399char(1)   c\_NFtype                    /*    type of North pole Folding: T or F point            */ 
     400real      glamt, glamu, glamv, glamf   /* geographic longitude (t,u,v and f points respectively) */ 
     401real      gphit, gphiu, gphiv, gphif   /* geographic latitude                                    */ 
     402real      e1t, e1u, e1v, e1f           /* horizontal scale factors                               */ 
     403real      e2t, e2u, e2v, e2f           /* horizontal scale factors                               */ 
    402404\end{clines} 
    403405 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/doc/latex/NEMO/subfiles/chap_LBC.tex

    r14257 r14336  
    159159 
    160160%% ================================================================================================= 
    161 \section{Model domain boundary condition (\forcode{jperio})} 
     161\section{Model domain boundary condition} 
    162162\label{sec:LBC_jperio} 
    163163 
     
    168168 
    169169%% ================================================================================================= 
    170 \subsection{Closed, cyclic (\forcode{jperio={0,1,2,7}})} 
     170\subsection{Closed, cyclic (\forcode{l\_Iperio,l\_jperio})} 
    171171\label{subsec:LBC_jperio012} 
    172172 
    173173The choice of closed or cyclic model domain boundary condition is made by 
    174 setting \forcode{jperio} to 0, 1, 2 or 7 in namelist \nam{cfg}{cfg}. 
     174setting \forcode{l\_Iperio,l\_jperio} to true or false in namelist \nam{cfg}{cfg}. 
    175175Each time such a boundary condition is needed, it is set by a call to routine \mdl{lbclnk}. 
    176176The computation of momentum and tracer trends proceeds from $i=2$ to $i=jpi-1$ and from $j=2$ to $j=jpj-1$, 
     
    181181\begin{description} 
    182182 
    183 \item [For closed boundary (\forcode{jperio=0})], solid walls are imposed at all model boundaries: 
     183\item [For closed boundary (\forcode{l\_Iperio = .false.,l\_jperio = .false.})], solid walls are imposed at all model boundaries: 
    184184  first and last rows and columns are set to zero. 
    185185 
    186 \item [For cyclic east-west boundary (\forcode{jperio=1})], first and last rows are set to zero (closed) whilst the first column is set to 
     186\item [For cyclic east-west boundary (\forcode{l\_Iperio = .true.,l\_jperio = .false.})], first and last rows are set to zero (closed) whilst the first column is set to 
    187187  the value of the last-but-one column and the last column to the value of the second one 
    188188  (\autoref{fig:LBC_jperio}-a). 
    189189  Whatever flows out of the eastern (western) end of the basin enters the western (eastern) end. 
    190190 
    191 \item [For cyclic north-south boundary (\forcode{jperio=2})], first and last columns are set to zero (closed) whilst the first row is set to 
     191\item [For cyclic north-south boundary (\forcode{l\_Iperio = .false.,l\_jperio = .true.})], first and last columns are set to zero (closed) whilst the first row is set to 
    192192  the value of the last-but-one row and the last row to the value of the second one 
    193193  (\autoref{fig:LBC_jperio}-a). 
    194194  Whatever flows out of the northern (southern) end of the basin enters the southern (northern) end. 
    195195 
    196 \item [Bi-cyclic east-west and north-south boundary (\forcode{jperio=7})] combines cases 1 and 2. 
     196\item [Bi-cyclic east-west and north-south boundary (\forcode{l\_Iperio = .true.,l\_jperio = .true.})] combines cases 1 and 2. 
    197197 
    198198\end{description} 
     
    207207 
    208208%% ================================================================================================= 
    209 \subsection{North-fold (\forcode{jperio={3,6}})} 
     209\subsection{North-fold (\forcode{l\_NFold = .true.})} 
    210210\label{subsec:LBC_north_fold} 
    211211 
     
    220220  \includegraphics[width=0.66\textwidth]{LBC_North_Fold_T} 
    221221  \caption[North fold boundary in ORCA 2\deg, 1/4\deg and 1/12\deg]{ 
    222     North fold boundary with a $T$-point pivot and cyclic east-west boundary condition ($jperio=4$), 
     222    North fold boundary with a $T$-point pivot and cyclic east-west boundary condition ($c\_NFtype='T'$), 
    223223    as used in ORCA 2\deg, 1/4\deg and 1/12\deg. 
    224224    Pink shaded area corresponds to the inner domain mask (see text).} 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/NST/agrif_user.F90

    r14229 r14336  
    6363! In case of East-West periodicity, prevent AGRIF interpolation at east and west boundaries 
    6464! The procnames will not be called at these boundaries 
    65       IF (jperio == 1) THEN 
     65      IF (l_Iperio) THEN 
    6666         CALL Agrif_Set_NearCommonBorderX(.TRUE.) 
    6767         CALL Agrif_Set_DistantCommonBorderX(.TRUE.) 
     
    872872      nbghostcells_y_n = nbghostcells 
    873873      ! 
    874       IF(   jperio == 1  )   nbghostcells_x   = 0 
     874      IF(    l_Iperio    )   nbghostcells_x   = 0 
    875875      IF( .NOT. lk_south )   nbghostcells_y_s = 0 
    876876      IF( .NOT. lk_north )   nbghostcells_y_n = 0 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/OCE/BDY/bdyini.F90

    r14314 r14336  
    166166      ! Check and write out namelist parameters 
    167167      ! ----------------------------------------- 
    168       IF( jperio /= 0 )   CALL ctl_stop( 'bdy_segs: Cyclic or symmetric,',   & 
    169          &                               ' and general open boundary condition are not compatible' ) 
    170  
     168       
    171169      IF(lwp) WRITE(numout,*) 'Number of open boundary sets : ', nb_bdy 
    172170 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/OCE/CRS/crsdom.F90

    r14314 r14336  
    3030   !!       Original.   May 2012.  (J. Simeon, C. Calone, G. Madec, C. Ethe) 
    3131   !!=================================================================== 
    32    USE dom_oce        ! ocean space and time domain and to get jperio 
     32   USE dom_oce        ! ocean space and time domain 
    3333   USE crs            ! domain for coarse grid 
    3434   ! 
     
    21172117      CASE ( 0 )  
    21182118 
    2119          SELECT CASE ( jperio ) 
    2120       
    2121   
    2122         CASE ( 0, 1, 3, 4 )    !   3, 4 : T-Pivot at North Fold 
    2123          
    2124             DO ji = 2, jpiglo_crsm1 
    2125                ijie = ( ji * nn_factx ) - nn_factx   !cc 
    2126                ijis = ijie - nn_factx + 1 
    2127                mis2_crs(ji) = ijis 
    2128                mie2_crs(ji) = ijie 
    2129             ENDDO 
    2130             IF ( jpiglo - 1 - mie2_crs(jpiglo_crsm1) <= nn_factx ) mie2_crs(jpiglo_crsm1) = jpiglo - 2   
    2131  
    2132             ! Handle first the northernmost bin 
    2133             IF ( nn_facty == 2 ) THEN   ;    ijjgloT = jpjglo - 1  
    2134             ELSE                        ;    ijjgloT = jpjglo 
    2135             ENDIF 
    2136  
    2137             DO jj = 2, jpjglo_crs 
    2138                 ijje = ijjgloT - nn_facty * ( jj - 3 ) 
    2139                 ijjs = ijje - nn_facty + 1                    
    2140                 mjs2_crs(jpjglo_crs-jj+2) = ijjs 
    2141                 mje2_crs(jpjglo_crs-jj+2) = ijje 
    2142             ENDDO 
    2143  
    2144          CASE ( 2 )  
    2145             WRITE(numout,*)  'crs_init, jperio=2 not supported'  
    2146          
    2147          CASE ( 5, 6 )    ! F-pivot at North Fold 
    2148  
    2149             DO ji = 2, jpiglo_crsm1 
    2150                ijie = ( ji * nn_factx ) - nn_factx  
    2151                ijis = ijie - nn_factx + 1 
    2152                mis2_crs(ji) = ijis 
    2153                mie2_crs(ji) = ijie 
    2154             ENDDO 
    2155             IF ( jpiglo - 1 - mie2_crs(jpiglo_crsm1) <= nn_factx ) mie_crs(jpiglo_crsm1)  = jpiglo - 2  
    2156  
    2157             ! Treat the northernmost bin separately. 
    2158             jj = 2 
    2159             ijje = jpj - nn_facty * ( jj - 2 ) 
    2160             IF ( nn_facty == 3 ) THEN   ;  ijjs = ijje - 1  
    2161             ELSE                        ;  ijjs = ijje - nn_facty + 1 
    2162             ENDIF 
    2163             mjs2_crs(jpj_crs-jj+1) = ijjs 
    2164             mje2_crs(jpj_crs-jj+1) = ijje 
    2165  
    2166             ! Now bin the rest, any remainder at the south is lumped in the southern bin 
    2167             DO jj = 3, jpjglo_crsm1 
    2168                 ijje = jpjglo - nn_facty * ( jj - 2 ) 
    2169                 ijjs = ijje - nn_facty + 1                   
    2170                 IF ( ijjs <= nn_facty )  ijjs = 2 
    2171                 mjs2_crs(jpj_crs-jj+1)   = ijjs 
    2172                 mje2_crs(jpj_crs-jj+1)   = ijje 
    2173             ENDDO 
    2174  
    2175          CASE DEFAULT 
    2176             WRITE(numout,*) 'crs_init. Only jperio = 0, 1, 3, 4, 5, 6 supported'  
    2177   
    2178          END SELECT 
     2119!!$         SELECT CASE ( jperio ) 
     2120!!$      
     2121!!$  
     2122!!$        CASE ( 0, 1, 3, 4 )    !   3, 4 : T-Pivot at North Fold 
     2123!!$         
     2124!!$            DO ji = 2, jpiglo_crsm1 
     2125!!$               ijie = ( ji * nn_factx ) - nn_factx   !cc 
     2126!!$               ijis = ijie - nn_factx + 1 
     2127!!$               mis2_crs(ji) = ijis 
     2128!!$               mie2_crs(ji) = ijie 
     2129!!$            ENDDO 
     2130!!$            IF ( jpiglo - 1 - mie2_crs(jpiglo_crsm1) <= nn_factx ) mie2_crs(jpiglo_crsm1) = jpiglo - 2   
     2131!!$ 
     2132!!$            ! Handle first the northernmost bin 
     2133!!$            IF ( nn_facty == 2 ) THEN   ;    ijjgloT = jpjglo - 1  
     2134!!$            ELSE                        ;    ijjgloT = jpjglo 
     2135!!$            ENDIF 
     2136!!$ 
     2137!!$            DO jj = 2, jpjglo_crs 
     2138!!$                ijje = ijjgloT - nn_facty * ( jj - 3 ) 
     2139!!$                ijjs = ijje - nn_facty + 1                    
     2140!!$                mjs2_crs(jpjglo_crs-jj+2) = ijjs 
     2141!!$                mje2_crs(jpjglo_crs-jj+2) = ijje 
     2142!!$            ENDDO 
     2143!!$ 
     2144!!$         CASE ( 2 )  
     2145!!$            WRITE(numout,*)  'crs_init, jperio=2 not supported'  
     2146!!$         
     2147!!$         CASE ( 5, 6 )    ! F-pivot at North Fold 
     2148!!$ 
     2149!!$            DO ji = 2, jpiglo_crsm1 
     2150!!$               ijie = ( ji * nn_factx ) - nn_factx  
     2151!!$               ijis = ijie - nn_factx + 1 
     2152!!$               mis2_crs(ji) = ijis 
     2153!!$               mie2_crs(ji) = ijie 
     2154!!$            ENDDO 
     2155!!$            IF ( jpiglo - 1 - mie2_crs(jpiglo_crsm1) <= nn_factx ) mie_crs(jpiglo_crsm1)  = jpiglo - 2  
     2156!!$ 
     2157!!$            ! Treat the northernmost bin separately. 
     2158!!$            jj = 2 
     2159!!$            ijje = jpj - nn_facty * ( jj - 2 ) 
     2160!!$            IF ( nn_facty == 3 ) THEN   ;  ijjs = ijje - 1  
     2161!!$            ELSE                        ;  ijjs = ijje - nn_facty + 1 
     2162!!$            ENDIF 
     2163!!$            mjs2_crs(jpj_crs-jj+1) = ijjs 
     2164!!$            mje2_crs(jpj_crs-jj+1) = ijje 
     2165!!$ 
     2166!!$            ! Now bin the rest, any remainder at the south is lumped in the southern bin 
     2167!!$            DO jj = 3, jpjglo_crsm1 
     2168!!$                ijje = jpjglo - nn_facty * ( jj - 2 ) 
     2169!!$                ijjs = ijje - nn_facty + 1                   
     2170!!$                IF ( ijjs <= nn_facty )  ijjs = 2 
     2171!!$                mjs2_crs(jpj_crs-jj+1)   = ijjs 
     2172!!$                mje2_crs(jpj_crs-jj+1)   = ijje 
     2173!!$            ENDDO 
     2174!!$ 
     2175!!$         CASE DEFAULT 
     2176!!$            WRITE(numout,*) 'crs_init. Only jperio = 0, 1, 3, 4, 5, 6 supported'  
     2177!!$  
     2178!!$         END SELECT 
    21792179 
    21802180      CASE (1 ) 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/OCE/DOM/dom_oce.F90

    r14314 r14336  
    6565   !! space domain parameters 
    6666   !!---------------------------------------------------------------------- 
    67    INTEGER, PUBLIC ::   jperio   !: Global domain lateral boundary type (between 0 and 7) 
    68    !                                !  = 0 closed                 ;   = 1 cyclic East-West 
    69    !                                !  = 2 cyclic North-South     ;   = 3 North fold T-point pivot 
    70    !                                !  = 4 cyclic East-West AND North fold T-point pivot 
    71    !                                !  = 5 North fold F-point pivot 
    72    !                                !  = 6 cyclic East-West AND North fold F-point pivot 
    73    !                                !  = 7 bi-cyclic East-West AND North-South 
    74    LOGICAL, PUBLIC ::   l_Iperio, l_Jperio   !   should we explicitely take care I/J periodicity 
    75    LOGICAL, PUBLIC ::   l_NFoldT, l_NFoldF 
     67   LOGICAL         , PUBLIC ::   l_Iperio, l_Jperio   ! i- j-periodicity 
     68   LOGICAL         , PUBLIC ::   l_NFold              ! North Pole folding 
     69   CHARACTER(len=3), PUBLIC ::   c_NFtype             ! type of North pole Folding: T or F point 
    7670 
    7771   ! Tiling namelist 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/OCE/DOM/domain.F90

    r14255 r14336  
    113113         WRITE(numout,*)     '              jpnj    : ', jpnj, '   nn_hls  : ', nn_hls 
    114114         WRITE(numout,*)     '              jpnij   : ', jpnij 
    115          WRITE(numout,*)     '      lateral boundary of the Global domain : jperio  = ', jperio 
    116          SELECT CASE ( jperio ) 
    117          CASE( 0 )   ;   WRITE(numout,*) '         (i.e. closed)' 
    118          CASE( 1 )   ;   WRITE(numout,*) '         (i.e. cyclic east-west)' 
    119          CASE( 2 )   ;   WRITE(numout,*) '         (i.e. cyclic north-south)' 
    120          CASE( 3 )   ;   WRITE(numout,*) '         (i.e. north fold with T-point pivot)' 
    121          CASE( 4 )   ;   WRITE(numout,*) '         (i.e. cyclic east-west and north fold with T-point pivot)' 
    122          CASE( 5 )   ;   WRITE(numout,*) '         (i.e. north fold with F-point pivot)' 
    123          CASE( 6 )   ;   WRITE(numout,*) '         (i.e. cyclic east-west and north fold with F-point pivot)' 
    124          CASE( 7 )   ;   WRITE(numout,*) '         (i.e. cyclic east-west and north-south)' 
    125          CASE DEFAULT 
    126             CALL ctl_stop( 'dom_init:   jperio is out of range' ) 
    127          END SELECT 
     115         WRITE(numout,*)     '      lateral boundary of the Global domain:' 
     116         WRITE(numout,*)     '              cyclic east-west             :', l_Iperio 
     117         WRITE(numout,*)     '              cyclic north-south           :', l_Jperio 
     118         WRITE(numout,*)     '              North Pole folding           :', l_NFold 
     119         WRITE(numout,*)     '                 type of North pole Folding:', c_NFtype 
    128120         WRITE(numout,*)     '      Ocean model configuration used:' 
    129          WRITE(numout,*)     '         cn_cfg = ', TRIM( cn_cfg ), '   nn_cfg = ', nn_cfg 
     121         WRITE(numout,*)     '              cn_cfg = ', TRIM( cn_cfg ), '   nn_cfg = ', nn_cfg 
    130122      ENDIF 
    131123 
     
    622614 
    623615 
    624    SUBROUTINE domain_cfg( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     616   SUBROUTINE domain_cfg( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype ) 
    625617      !!---------------------------------------------------------------------- 
    626618      !!                     ***  ROUTINE domain_cfg  *** 
     
    630622      !! ** Method  :   read the cn_domcfg NetCDF file 
    631623      !!---------------------------------------------------------------------- 
    632       CHARACTER(len=*)              , INTENT(out) ::   cd_cfg          ! configuration name 
    633       INTEGER                       , INTENT(out) ::   kk_cfg          ! configuration resolution 
    634       INTEGER                       , INTENT(out) ::   kpi, kpj, kpk   ! global domain sizes 
    635       INTEGER                       , INTENT(out) ::   kperio          ! lateral global domain b.c. 
    636       ! 
    637       INTEGER ::   inum   ! local integer 
     624      CHARACTER(len=*), INTENT(out) ::   cd_cfg               ! configuration name 
     625      INTEGER         , INTENT(out) ::   kk_cfg               ! configuration resolution 
     626      INTEGER         , INTENT(out) ::   kpi, kpj, kpk        ! global domain sizes 
     627      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity 
     628      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding 
     629      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F 
     630      ! 
     631      INTEGER ::   inum, iperio                   ! local integer 
    638632      REAL(wp) ::   zorca_res                     ! local scalars 
    639       REAL(wp) ::   zperio                        !   -      - 
     633      REAL(wp) ::   zperio, z01                   !   -      - 
    640634      INTEGER, DIMENSION(4) ::   idvar, idimsz    ! size   of dimensions 
    641635      !!---------------------------------------------------------------------- 
     
    678672      kpj = idimsz(2) 
    679673      kpk = idimsz(3) 
    680       CALL iom_get( inum, 'jperio', zperio )   ;   kperio = NINT( zperio ) 
     674      ! 
     675      IF( iom_varid( inum, 'jperio', ldstop = .FALSE. ) > 0 ) THEN                   ! keep compatibility with old version... 
     676         CALL iom_get( inum, 'jperio', zperio )   ;   iperio = NINT( zperio ) 
     677         ldIperio = iperio == 1 .OR. iperio == 4 .OR. iperio == 6 .OR. iperio == 7   ! i-periodicity 
     678         ldJperio = iperio == 2 .OR. iperio == 7                                     ! j-periodicity 
     679         ldNFold  = iperio >= 3 .OR. iperio <= 6                                     ! North pole folding 
     680         IF(     iperio == 3 .OR. iperio == 4 ) THEN   ;   cdNFtype = 'T'            !    folding at T point 
     681         ELSEIF( iperio == 5 .OR. iperio == 6 ) THEN   ;   cdNFtype = 'F'            !    folding at F point 
     682         ELSE                                          ;   cdNFtype = '-'   
     683         ENDIF 
     684      ELSE    
     685         z01 = 0._wp   ;   IF( iom_varid( inum, 'Iperio', ldstop = .FALSE. ) > 0 )   CALL iom_get( inum, 'Iperio', z01 ) 
     686         ldIperio = NINT(z01) == 1               ! i-periodicity 
     687         z01 = 0._wp   ;   IF( iom_varid( inum, 'Jperio', ldstop = .FALSE. ) > 0 )   CALL iom_get( inum, 'Jperio', z01 ) 
     688         ldJperio = NINT(z01) == 1               ! j-periodicity 
     689         cdNFtype = '-'                          ! default definition 
     690         z01 = 0._wp   ;   IF( iom_varid( inum, 'NFoldT', ldstop = .FALSE. ) > 0 )   CALL iom_get( inum, 'NFoldT', z01 ) 
     691         IF( NINT(z01) == 1 )   cdNFtype = 'T'   ! folding at T point 
     692         z01 = 0._wp   ;   IF( iom_varid( inum, 'NFoldF', ldstop = .FALSE. ) > 0 )   CALL iom_get( inum, 'NFoldF', z01 ) 
     693         IF( NINT(z01) == 1 )   cdNFtype = 'F'   ! folding at T point 
     694         ldNFold = cdNFtype /= '-'               ! North pole folding    
     695      ENDIF 
    681696      CALL iom_close( inum ) 
    682697      ! 
     
    686701         WRITE(numout,*) '      Nj0glo = ', kpj 
    687702         WRITE(numout,*) '      jpkglo = ', kpk 
    688          WRITE(numout,*) '      type of global domain lateral boundary   jperio = ', kperio 
    689703      ENDIF 
    690704      ! 
     
    733747      ! 
    734748      !                                   ! lateral boundary of the global domain 
    735       CALL iom_rstput( 0, 0, inum, 'jperio', REAL( jperio, wp), ktype = jp_i4 ) 
     749      CALL iom_rstput( 0, 0, inum, 'Iperio', REAL( COUNT( (/l_Iperio/) ), wp), ktype = jp_i1 ) 
     750      CALL iom_rstput( 0, 0, inum, 'Jperio', REAL( COUNT( (/l_Jperio/) ), wp), ktype = jp_i1 ) 
     751      CALL iom_rstput( 0, 0, inum, 'NFoldT', REAL( COUNT( (/c_NFtype == 'T'/) ), wp), ktype = jp_i1 ) 
     752      CALL iom_rstput( 0, 0, inum, 'NFoldF', REAL( COUNT( (/c_NFtype == 'F'/) ), wp), ktype = jp_i1 ) 
    736753      ! 
    737754      !                                   ! type of vertical coordinate 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/OCE/DOM/domwri.F90

    r13295 r14336  
    7575      CALL iom_open( TRIM(clnam), inum, ldwrt = .TRUE. ) 
    7676      !                                                         ! domain characteristics 
    77       CALL iom_rstput( 0, 0, inum, 'jperio', REAL( jperio, wp), ktype = jp_i4 ) 
     77      CALL iom_rstput( 0, 0, inum, 'Iperio', REAL( COUNT( (/l_Iperio/) ), wp), ktype = jp_i1 ) 
     78      CALL iom_rstput( 0, 0, inum, 'Jperio', REAL( COUNT( (/l_Jperio/) ), wp), ktype = jp_i1 ) 
     79      CALL iom_rstput( 0, 0, inum, 'NFoldT', REAL( COUNT( (/c_NFtype == 'T'/) ), wp), ktype = jp_i1 ) 
     80      CALL iom_rstput( 0, 0, inum, 'NFoldF', REAL( COUNT( (/c_NFtype == 'F'/) ), wp), ktype = jp_i1 ) 
    7881      !                                                         ! type of vertical coordinate 
    7982      IF( ln_zco    ) THEN   ;   izco = 1   ;   ELSE   ;   izco = 0   ;   ENDIF 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/OCE/DOM/domzgr.F90

    r13295 r14336  
    115115      ! 
    116116      zmsk(:,:) = 1._wp                                       ! default: no closed boundaries 
    117       IF( jperio == 0 .OR. jperio == 2 .OR. jperio == 3 .OR. jperio == 5 ) THEN   ! E-W closed 
     117      IF( .NOT. l_Iperio ) THEN                                    ! E-W closed: 
    118118         zmsk(  mi0(     1+nn_hls):mi1(     1+nn_hls),:) = 0._wp   ! first column of inner global domain at 0 
    119119         zmsk(  mi0(jpiglo-nn_hls):mi1(jpiglo-nn_hls),:) = 0._wp   ! last  column of inner global domain at 0  
    120120      ENDIF 
    121       IF( .NOT. ( jperio == 2 .OR. jperio == 7 ) ) THEN                           ! S closed 
     121      IF( .NOT. l_Jperio ) THEN                                    ! S closed: 
    122122         zmsk(:,mj0(     1+nn_hls):mj1(     1+nn_hls)  ) = 0._wp   ! first   line of inner global domain at 0 
    123123      ENDIF 
    124       IF( jperio == 0 .OR. jperio == 1 ) THEN                                     ! N closed 
     124      IF( .NOT. ( l_Jperio .OR. l_NFold ) ) THEN                   ! N closed: 
    125125         zmsk(:,mj0(jpjglo-nn_hls):mj1(jpjglo-nn_hls)  ) = 0._wp   ! last    line of inner global domain at 0 
    126126      ENDIF 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/OCE/LBC/lbc_nfd_ext_generic.h90

    r14314 r14336  
    4343      DO jf = 1, ipf                      ! Loop on the number of arrays to be treated 
    4444         ! 
    45          IF( l_NFoldT ) THEN                   ! *  North fold  T-point pivot 
     45         IF( c_NFtype == 'T' ) THEN            ! *  North fold  T-point pivot 
    4646            ! 
    4747            SELECT CASE ( NAT_IN(jf)  ) 
     
    9494            END SELECT 
    9595            ! 
    96          ENDIF   ! l_NFoldT 
     96         ENDIF   ! c_NFtype == 'T' 
    9797         ! 
    98          IF( l_NFoldF ) THEN                   ! *  North fold  F-point pivot 
     98         IF( c_NFtype == 'F' ) THEN            ! *  North fold  F-point pivot 
    9999            ! 
    100100            SELECT CASE ( NAT_IN(jf)  ) 
     
    139139            END SELECT 
    140140            ! 
    141          ENDIF   ! l_NFoldF 
     141         ENDIF   ! c_NFtype == 'F' 
    142142         ! 
    143143      END DO 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/OCE/LBC/lbc_nfd_generic.h90

    r14314 r14336  
    9494      DO jf = 1, ipf                      ! Loop on the number of arrays to be treated 
    9595         ! 
    96          IF( l_NFoldT ) THEN                   ! *  North fold  T-point pivot 
     96         IF( c_NFtype == 'T' ) THEN            ! *  North fold  T-point pivot 
    9797            ! 
    9898            SELECT CASE ( NAT_IN(jf)  ) 
     
    261261            END SELECT   ! NAT_IN(jf) 
    262262            ! 
    263          ENDIF   ! l_NFoldT 
     263         ENDIF   ! c_NFtype == 'T' 
    264264         ! 
    265          IF( l_NFoldF ) THEN                   ! *  North fold  F-point pivot 
     265         IF( c_NFtype == 'F' ) THEN            ! *  North fold  F-point pivot 
    266266            ! 
    267267            SELECT CASE ( NAT_IN(jf)  ) 
     
    453453            END SELECT   ! NAT_IN(jf) 
    454454            ! 
    455          ENDIF   ! l_NFoldF 
     455         ENDIF   ! c_NFtype == 'F' 
    456456         ! 
    457457      END DO   ! ipf 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/OCE/LBC/lbc_nfd_nogather_generic.h90

    r14314 r14336  
    109109      DO jf = 1, ipf                      ! Loop over the number of arrays to be processed 
    110110         ! 
    111          IF( l_NFoldT ) THEN                 ! *  North fold  T-point pivot 
     111         IF( c_NFtype == 'T' ) THEN          ! *  North fold  T-point pivot 
    112112            ! 
    113113            SELECT CASE ( NAT_IN(jf) ) 
     
    305305            END SELECT 
    306306            ! 
    307          ENDIF   ! l_NFoldT 
     307         ENDIF   ! c_NFtype == 'T' 
    308308         ! 
    309          IF( l_NFoldF ) THEN                  ! *  North fold  F-point pivot 
     309         IF( c_NFtype == 'F' ) THEN           ! *  North fold  F-point pivot 
    310310            ! 
    311311            SELECT CASE ( NAT_IN(jf) ) 
     
    429429            END SELECT 
    430430            ! 
    431          ENDIF   ! l_NFoldF 
     431         ENDIF   ! c_NFtype == 'F' 
    432432         ! 
    433433      END DO            ! End jf loop 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/OCE/LBC/mpp_nfd_generic.h90

    r14314 r14336  
    118118         ! 
    119119         ! However, some other points are duplicated in the north pole folding: 
    120          !  - jperio=[34], grid=T : half of the last line (jpiglo/2+2:jpiglo-nn_hls) 
    121          !  - jperio=[34], grid=U : half of the last line (jpiglo/2+1:jpiglo-nn_hls) 
    122          !  - jperio=[34], grid=V : all the last line nn_hls+1 and (nn_hls+2:jpiglo-nn_hls) 
    123          !  - jperio=[34], grid=F : all the last line (nn_hls+1:jpiglo-nn_hls) 
    124          !  - jperio=[56], grid=T : 2 points of the last line (jpiglo/2+1 and jpglo-nn_hls) 
    125          !  - jperio=[56], grid=U : no points are duplicated 
    126          !  - jperio=[56], grid=V : half of the last line (jpiglo/2+1:jpiglo-nn_hls) 
    127          !  - jperio=[56], grid=F : half of the last line (jpiglo/2+1:jpiglo-nn_hls-1) 
     120         !  - c_NFtype='T', grid=T : half of the last line (jpiglo/2+2:jpiglo-nn_hls) 
     121         !  - c_NFtype='T', grid=U : half of the last line (jpiglo/2+1:jpiglo-nn_hls) 
     122         !  - c_NFtype='T', grid=V : all the last line nn_hls+1 and (nn_hls+2:jpiglo-nn_hls) 
     123         !  - c_NFtype='T', grid=F : all the last line (nn_hls+1:jpiglo-nn_hls) 
     124         !  - c_NFtype='F', grid=T : 2 points of the last line (jpiglo/2+1 and jpglo-nn_hls) 
     125         !  - c_NFtype='F', grid=U : no points are duplicated 
     126         !  - c_NFtype='F', grid=V : half of the last line (jpiglo/2+1:jpiglo-nn_hls) 
     127         !  - c_NFtype='F', grid=F : half of the last line (jpiglo/2+1:jpiglo-nn_hls-1) 
    128128         ! The order of the calculations may differ for these duplicated points (as, for example jj+1 becomes jj-1) 
    129129         ! This explain why these duplicated points may have different values even if they are at the exact same location. 
     
    141141         IF( ll_add_line ) THEN 
    142142            DO jf = 1, ipf                      ! Loop over the number of arrays to be processed 
    143                ipj_s(jf) = nn_hls + COUNT( (/ l_NFoldT .OR. NAT_IN(jf) == 'V' .OR. NAT_IN(jf) == 'F' /) )  
     143               ipj_s(jf) = nn_hls + COUNT( (/ c_NFtype == 'T' .OR. NAT_IN(jf) == 'V' .OR. NAT_IN(jf) == 'F' /) )  
    144144            END DO 
    145145         ELSE 
     
    155155         DO jf = 1, ipf                      ! Loop over the number of arrays to be processed 
    156156            ! 
    157             IF( l_NFoldT ) THEN          ! *  North fold  T-point pivot 
     157            IF( c_NFtype == 'T' ) THEN          ! *  North fold  T-point pivot 
    158158               SELECT CASE ( NAT_IN(jf) ) 
    159159               CASE ( 'T', 'W', 'U' )   ;   i012 = 1   ! T-, U-, W-point 
     
    161161               END SELECT 
    162162            ENDIF 
    163             IF( l_NFoldF ) THEN          ! *  North fold  F-point pivot 
     163            IF( c_NFtype == 'F' ) THEN          ! *  North fold  F-point pivot 
    164164               SELECT CASE ( NAT_IN(jf) ) 
    165165               CASE ( 'T', 'W', 'U' )   ;   i012 = 0   ! T-, U-, W-point 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/OCE/LBC/mppini.F90

    r14327 r14336  
    113113      !! ** Method  :   Global domain is distributed in smaller local domains. 
    114114      !!      Periodic condition is a function of the local domain position 
    115       !!      (global boundary or neighbouring domain) and of the global 
    116       !!      periodic 
    117       !!      Type :         jperio global periodic condition 
     115      !!      (global boundary or neighbouring domain) and of the global periodic 
    118116      !! 
    119117      !! ** Action : - set domain parameters 
     
    137135      LOGICAL ::   llbest, llauto 
    138136      LOGICAL ::   llwrtlay 
    139       LOGICAL ::   llmpi_Iperio, llmpi_Jperio, llmpiNfold 
     137      LOGICAL ::   llmpi_Iperio, llmpi_Jperio, llmpiNFold 
    140138      LOGICAL ::   ln_listonly 
    141139      LOGICAL, ALLOCATABLE, DIMENSION(:,:  ) ::   llisOce  ! is not land-domain only? 
     
    494492      !                          ! Prepare mpp north fold 
    495493      ! 
    496       llmpiNfold =          jpni  > 1 .AND. ( l_NFoldT .OR. l_NFoldF )   ! is the North fold done with an MPI communication? 
    497       l_IdoNFold = ijn(narea) == jpnj .AND. ( l_NFoldT .OR. l_NFoldF )   ! is this process doing North fold? 
    498       ! 
    499       IF( llmpiNfold ) THEN 
     494      llmpiNFold =          jpni  > 1 .AND. l_NFold   ! is the North fold done with an MPI communication? 
     495      l_IdoNFold = ijn(narea) == jpnj .AND. l_NFold   ! is this process doing North fold? 
     496      ! 
     497      IF( llmpiNFold ) THEN 
    500498         CALL mpp_ini_north 
    501499         IF (lwp) THEN 
     
    596594        CALL ctl_stop( 'STOP', ctmp1, ctmp2 ) 
    597595      ENDIF 
    598       IF( jperio == 3 .OR. jperio == 4 .OR. jperio == 5 .OR. jperio == 6 ) THEN 
     596      IF( l_NFold ) THEN 
    599597         ! minimize the size of the last row to compensate for the north pole folding coast 
    600          IF( jperio == 3 .OR. jperio == 4 )   ijpjmin = 2+3*khls   ! V and F folding must be outside of southern halos 
    601          IF( jperio == 5 .OR. jperio == 6 )   ijpjmin = 1+3*khls   ! V and F folding must be outside of southern halos 
    602          irm = knbj - irestj                                       ! total number of lines to be removed 
    603          klcj(:,knbj) = MAX( ijpjmin, kjmax-irm )                  ! we must have jpj >= ijpjmin in the last row 
    604          irm = irm - ( kjmax - klcj(1,knbj) )                      ! remaining number of lines to remove 
     598         IF( c_NFtype == 'T' )   ijpjmin = 2+3*khls   ! V and F folding must be outside of southern halos 
     599         IF( c_NFtype == 'F' )   ijpjmin = 1+3*khls   ! V and F folding must be outside of southern halos 
     600         irm = knbj - irestj                          ! total number of lines to be removed 
     601         klcj(:,knbj) = MAX( ijpjmin, kjmax-irm )     ! we must have jpj >= ijpjmin in the last row 
     602         irm = irm - ( kjmax - klcj(1,knbj) )         ! remaining number of lines to remove 
    605603         irestj = knbj - 1 - irm 
    606604         klcj(:, irestj+1:knbj-1) = kjmax-1 
     
    690688      iszimin = 4*nn_hls          ! minimum size of the MPI subdomain so halos are always adressing neighbor inner domain 
    691689      iszjmin = 4*nn_hls 
    692       IF( jperio == 3 .OR. jperio == 4 )   iszjmin = MAX(iszjmin, 2+3*nn_hls)   ! V and F folding must be outside of southern halos 
    693       IF( jperio == 5 .OR. jperio == 6 )   iszjmin = MAX(iszjmin, 1+3*nn_hls)   ! V and F folding must be outside of southern halos 
     690      IF( c_NFtype == 'T' )   iszjmin = MAX(iszjmin, 2+3*nn_hls)   ! V and F folding must be outside of southern halos 
     691      IF( c_NFtype == 'F' )   iszjmin = MAX(iszjmin, 1+3*nn_hls)   ! V and F folding must be outside of southern halos 
    694692      ! 
    695693      ! get the list of knbi that gives a smaller jpimax than knbi-1 
     
    953951            ! 
    954952            IF( iarea == 1    ) THEN                                   ! the first line was not read 
    955                IF( jperio == 2 .OR. jperio == 7 ) THEN                 !   north-south periodocity 
     953               IF( l_Jperio ) THEN                                     !   north-south periodocity 
    956954                  CALL readbot_strip( Nj0glo, 1, lloce(2:inx-1, 1) )   !   read the last line -> first line of lloce 
    957955               ELSE 
     
    960958            ENDIF 
    961959            IF( iarea == inbj ) THEN                                   ! the last line was not read 
    962                IF( jperio == 2 .OR. jperio == 7 ) THEN                 !   north-south periodocity 
     960               IF( l_Jperio ) THEN                                     !   north-south periodocity 
    963961                  CALL readbot_strip( 1, 1, lloce(2:inx-1,iny) )       !      read the first line -> last line of lloce 
    964                ELSEIF( jperio == 3 .OR. jperio == 4 ) THEN             !   north-pole folding T-pivot, T-point 
     962               ELSEIF( c_NFtype == 'T' ) THEN                          !   north-pole folding T-pivot, T-point 
    965963                  lloce(2,iny) = lloce(2,iny-2)                        !      here we have 1 halo (even if nn_hls>1) 
    966964                  DO ji = 3,inx-1 
     
    970968                     lloce(ji,iny-1) = lloce(inx-ji+2,iny-1) 
    971969                  END DO 
    972                ELSEIF( jperio == 5 .OR. jperio == 6 ) THEN             !   north-pole folding F-pivot, T-point, 1 halo 
     970               ELSEIF( c_NFtype == 'F' ) THEN                          !   north-pole folding F-pivot, T-point, 1 halo 
    973971                  lloce(inx/2+1,iny-1) = lloce(inx/2,iny-1)            !      here we have 1 halo (even if nn_hls>1) 
    974972                  lloce(inx  -1,iny-1) = lloce(2    ,iny-1) 
     
    981979            ENDIF 
    982980            !                                                          ! first and last column were not read 
    983             IF( jperio == 1 .OR. jperio == 4 .OR. jperio == 6 .OR. jperio == 7 ) THEN 
     981            IF( l_Iperio ) THEN 
    984982               lloce(1,:) = lloce(inx-1,:)   ;   lloce(inx,:) = lloce(2,:)   ! east-west periodocity 
    985983            ELSE 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/OCE/USR/README.rst

    r14239 r14336  
    111111   /* configuration name, configuration resolution                 */ 
    112112   int    ORCA, ORCA_index 
    113    /* global domain sizes                                          */ 
    114    int    jpiglo, jpjglo, jpkglo 
    115113   /* lateral global domain b.c.                                   */ 
    116    int    jperio 
     114   int    Iperio, Jperio, NFoldT, NFoldF 
    117115   /* flags for z-coord, z-coord with partial steps and s-coord    */ 
    118116   int    ln_zco, ln_zps, ln_sco 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/OCE/USR/usrdef_nam.F90

    r14072 r14336  
    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 
     
    8284      kpk = jpkglo 
    8385      !                             ! Set the lateral boundary condition of the global domain 
    84       kperio = 0                    ! GYRE configuration : closed domain 
     86      ldIperio = .FALSE.   ;   ldJperio = .FALSE.   ! GYRE configuration : closed domain 
     87      ldNFold  = .FALSE.   ;   cdNFtype = '-' 
    8588      ! 
    8689      !                             ! control print 
     
    102105         WRITE(numout,*) '      number of model levels                           jpkglo = ', kpk 
    103106         WRITE(numout,*) '   ' 
    104          WRITE(numout,*) '   Lateral b.c. of the global domain set to closed     jperio = ', kperio 
    105107      ENDIF 
    106108      ! 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/OCE/nemogcm.F90

    r14314 r14336  
    378378      ! 
    379379      IF( ln_read_cfg ) THEN            ! Read sizes in domain configuration file 
    380          CALL domain_cfg ( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, jperio ) 
     380         CALL domain_cfg ( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, l_Iperio, l_Jperio, l_NFold, c_NFtype ) 
    381381      ELSE                              ! user-defined namelist 
    382          CALL usr_def_nam( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, jperio ) 
    383       ENDIF 
    384       l_Iperio = jperio == 1 .OR. jperio == 4 .OR. jperio == 6 .OR. jperio == 7   ! i-periodicity? 
    385       l_Jperio = jperio == 2 .OR. jperio == 7                                     ! j-periodicity ? 
    386       l_NFoldT = jperio == 3 .OR. jperio == 4                                !  
    387       l_NFoldF = jperio == 5 .OR. jperio == 6                               !  
     382         CALL usr_def_nam( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, l_Iperio, l_Jperio, l_NFold, c_NFtype ) 
     383      ENDIF 
    388384      ! 
    389385      IF(lwm)   WRITE( numond, namcfg ) 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/OFF/nemogcm.F90

    r14331 r14336  
    309309      ! 
    310310      IF( ln_read_cfg ) THEN              ! Read sizes in domain configuration file 
    311          CALL domain_cfg ( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, jperio ) 
     311         CALL domain_cfg ( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, l_Iperio, l_Jperio, l_NFold, c_NFtype ) 
    312312      ELSE                                ! user-defined namelist 
    313          CALL usr_def_nam( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, jperio ) 
    314       ENDIF 
    315       l_Iperio = jperio == 1 .OR. jperio == 4 .OR. jperio == 6 .OR. jperio == 7   ! i-periodicity? 
    316       l_Jperio = jperio == 2 .OR. jperio == 7                                     ! j-periodicity ? 
    317       l_NFoldT = jperio == 3 .OR. jperio == 4                                     !  
    318       l_NFoldF = jperio == 5 .OR. jperio == 6                                     !  
     313         CALL usr_def_nam( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, l_Iperio, l_Jperio, l_NFold, c_NFtype ) 
     314      ENDIF 
    319315      ! 
    320316      IF(lwm)   WRITE( numond, namcfg ) 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/SAO/nemogcm.F90

    r14239 r14336  
    207207      ! 
    208208      IF( ln_read_cfg ) THEN            ! Read sizes in domain configuration file 
    209          CALL domain_cfg ( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, jperio ) 
     209         CALL domain_cfg ( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, l_Iperio, l_Jperio, l_NFold, c_NFtype ) 
    210210      ELSE                              ! user-defined namelist 
    211          CALL usr_def_nam( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, jperio ) 
     211         CALL usr_def_nam( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, l_Iperio, l_Jperio, l_NFold, c_NFtype ) 
    212212      ENDIF 
    213213      ! 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/SAS/nemogcm.F90

    r14331 r14336  
    340340      ! 
    341341      IF( ln_read_cfg ) THEN            ! Read sizes in domain configuration file 
    342          CALL domain_cfg ( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, jperio ) 
     342         CALL domain_cfg ( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, l_Iperio, l_Jperio, l_NFold, c_NFtype ) 
    343343      ELSE                              ! user-defined namelist 
    344          CALL usr_def_nam( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, jperio ) 
    345       ENDIF 
    346       l_Iperio = jperio == 1 .OR. jperio == 4 .OR. jperio == 6 .OR. jperio == 7   ! i-periodicity? 
    347       l_Jperio = jperio == 2 .OR. jperio == 7                                     ! j-periodicity ? 
    348       l_NFoldT = jperio == 3 .OR. jperio == 4                                     !  
    349       l_NFoldF = jperio == 5 .OR. jperio == 6                                     !  
     344         CALL usr_def_nam( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, l_Iperio, l_Jperio, l_NFold, c_NFtype ) 
     345      ENDIF 
    350346      ! 
    351347      IF(lwm)   WRITE( numond, namcfg ) 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/SWE/nemogcm.F90

    r14239 r14336  
    261261      ! 
    262262      IF( ln_read_cfg ) THEN            ! Read sizes in domain configuration file 
    263          CALL domain_cfg ( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, jperio ) 
     263         CALL domain_cfg ( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, l_Iperio, l_Jperio, l_NFold, c_NFtype ) 
    264264      ELSE                              ! user-defined namelist 
    265          CALL usr_def_nam( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, jperio ) 
     265         CALL usr_def_nam( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, l_Iperio, l_Jperio, l_NFold, c_NFtype ) 
    266266      ENDIF 
    267267      ! 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/tests/BENCH/EXPREF/namelist_cfg_orca025_like

    r14229 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/BENCH/EXPREF/namelist_cfg_orca12_like

    r14229 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/BENCH/EXPREF/namelist_cfg_orca1_like

    r14229 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/BENCH/MY_SRC/usrdef_nam.F90

    r13286 r14336  
    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 
    5757      LOGICAL          ::   ln_nnogather, 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 
     62      NAMELIST/namusr_def/ nn_isize, nn_jsize, nn_ksize, ln_Iperio, ln_Jperio, ln_NFold, cn_NFtype 
    6063      NAMELIST/nammpp/ jpni, jpnj, nn_hls, ln_nnogather, ln_listonly 
    6164      !!----------------------------------------------------------------------      
     
    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/branches/2021/dev_r14312_MPI_Interface/tests/BENCH/MY_SRC/usrdef_zgr.F90

    r13286 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/C1D_ASICS/MY_SRC/usrdef_nam.F90

    r14021 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/CANAL/EXPREF/namelist_cfg

    r14229 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/CANAL/MY_SRC/usrdef_nam.F90

    r13472 r14336  
    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) 
     52   LOGICAL , PUBLIC ::   ln_Iperio  =.false. ! i-periodicity 
     53   LOGICAL , PUBLIC ::   ln_Jperio  =.false. ! j-periodicity 
    5354 
    5455   !!---------------------------------------------------------------------- 
     
    5960CONTAINS 
    6061 
    61    SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     62   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype ) 
    6263      !!---------------------------------------------------------------------- 
    6364      !!                     ***  ROUTINE dom_nam  *** 
     
    7172      !! ** input   : - namusr_def namelist found in namelist_cfg 
    7273      !!---------------------------------------------------------------------- 
    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.  
     74      CHARACTER(len=*), INTENT(out) ::   cd_cfg               ! configuration name 
     75      INTEGER         , INTENT(out) ::   kk_cfg               ! configuration resolution 
     76      INTEGER         , INTENT(out) ::   kpi, kpj, kpk        ! global domain sizes 
     77      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity 
     78      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding 
     79      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F 
    7780      ! 
    7881      INTEGER ::   ios      ! Local integer 
     
    8285         &                 , nn_fcase, rn_ppgphi0, rn_u10, rn_windszx, rn_windszy & !!, rn_uofac   & 
    8386         &                 , rn_vtxmax, rn_uzonal, rn_ujetszx, rn_ujetszy  & 
    84          &                 , nn_botcase, nn_initcase, ln_sshnoise, rn_lambda, nn_perio 
     87         &                 , nn_botcase, nn_initcase, ln_sshnoise, rn_lambda, ln_Iperio, ln_Jperio 
    8588      !!---------------------------------------------------------------------- 
    8689      ! 
     
    117120      ! 
    118121      zh  = (kpk-1)*rn_dz 
    119       !                             ! Set the lateral boundary condition of the global domain 
    120       kperio = 1                    ! EW_CANAL configuration : closed basin 
    121122      !                             ! control print 
    122123      IF(lwp) THEN 
     
    149150         WRITE(numout,*) '      add random noise on initial ssh   ln_sshnoise= ', ln_sshnoise 
    150151         WRITE(numout,*) '      Gaussian lambda parameter          rn_lambda = ', rn_lambda 
    151          WRITE(numout,*) '      Periodicity of the basin            nn_perio = ', nn_perio 
     152         WRITE(numout,*) '      i and j Periodicity     ln_Iperio, ln_Jperio = ', ln_Iperio, ln_Jperio 
     153         WRITE(numout,*) '   ' 
    152154      ENDIF 
    153155      !                             ! Set the lateral boundary condition of the global domain 
    154       kperio = nn_perio                    ! EW_CANAL configuration : closed basin 
     156      ldIperio = ln_Iperio   ;   ldJperio = ln_Jperio   ! CANAL configuration 
     157      ldNFold  =  .FALSE.    ;   cdNFtype = '-' 
    155158      ! 
    156159   END SUBROUTINE usr_def_nam 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/tests/CANAL/MY_SRC/usrdef_zgr.F90

    r13472 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/DOME/MY_SRC/usrdef_nam.F90

    r14254 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/DOME/MY_SRC/usrdef_zgr.F90

    r14261 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/ICB/MY_SRC/usrdef_nam.F90

    r13899 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/ICE_ADV1D/MY_SRC/usrdef_nam.F90

    r13286 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/ICE_ADV2D/MY_SRC/usrdef_nam.F90

    r13286 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/ICE_AGRIF/MY_SRC/usrdef_nam.F90

    r14223 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/ICE_RHEO/MY_SRC/usrdef_nam.F90

    r14021 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/ISOMIP/MY_SRC/usrdef_nam.F90

    r13286 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/LOCK_EXCHANGE/MY_SRC/usrdef_nam.F90

    r13286 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/LOCK_EXCHANGE/MY_SRC/usrdef_zgr.F90

    r12377 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/OVERFLOW/MY_SRC/usrdef_nam.F90

    r13286 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/OVERFLOW/MY_SRC/usrdef_zgr.F90

    r14053 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/STATION_ASF/MY_SRC/nemogcm.F90

    r14239 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/STATION_ASF/MY_SRC/usrdef_nam.F90

    r14072 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/SWG/MY_SRC/usrdef_nam.F90

    r13752 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/SWG/MY_SRC/usrdef_zgr.F90

    r14204 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/TSUNAMI/MY_SRC/usrdef_nam.F90

    r14297 r14336  
    4646CONTAINS 
    4747 
    48    SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, kperio ) 
     48   SUBROUTINE usr_def_nam( cd_cfg, kk_cfg, kpi, kpj, kpk, ldIperio, ldJperio, ldNFold, cdNFtype ) 
    4949      !!---------------------------------------------------------------------- 
    5050      !!                     ***  ROUTINE dom_nam  *** 
     
    5858      !! ** input   : - namusr_def namelist found in namelist_cfg 
    5959      !!---------------------------------------------------------------------- 
    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.  
     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      LOGICAL         , INTENT(out) ::   ldIperio, ldJperio   ! i- and j- periodicity 
     64      LOGICAL         , INTENT(out) ::   ldNFold              ! North pole folding 
     65      CHARACTER(len=1), INTENT(out) ::   cdNFtype             ! Folding type: T or F 
    6466      ! 
    6567      INTEGER ::   ios      ! Local integer 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/tests/VORTEX/MY_SRC/usrdef_nam.F90

    r14086 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/VORTEX/MY_SRC/usrdef_zgr.F90

    r12740 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/WAD/MY_SRC/usrdef_nam.F90

    r13286 r14336  
    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/branches/2021/dev_r14312_MPI_Interface/tests/WAD/MY_SRC/usrdef_zgr.F90

    r13295 r14336  
    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.