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

Changeset 7299


Ignore:
Timestamp:
2016-11-22T12:19:58+01:00 (7 years ago)
Author:
lovato
Message:

Merge with CMCC changes from dev_r6522_SIMPLIF_3 - ticket #1729 & #1783

Location:
branches/2016/dev_CMCC_2016
Files:
1 deleted
65 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_CMCC_2016/DOC/Namelists/nam_tide

    r6997 r7299  
    11!----------------------------------------------------------------------- 
    2 &nam_tide      !   tide parameters                                      ("key_tide") 
     2&nam_tide      !   tide parameters 
    33!----------------------------------------------------------------------- 
    4    ln_tide_pot = .true.    !  use tidal potential forcing 
    5    ln_tide_ramp= .false.   ! 
    6    rdttideramp =    0.     ! 
    7    clname(1)   = 'DUMMY'   !  name of constituent - all tidal components must be set in namelist_cfg 
     4   ln_tide       = .true.   !  Activate tide module 
     5   ln_tide_pot   = .true.   !  use tidal potential forcing 
     6   ln_tide_ramp  = .false.  ! 
     7   rdttideramp   =    0.    ! 
     8   clname(1)     = 'DUMMY'  !  name of constituent - all tidal components must be set in namelist_cfg 
    89/ 
  • branches/2016/dev_CMCC_2016/DOC/Namelists/nambdy

    r6140 r7299  
    11!----------------------------------------------------------------------- 
    2 &nambdy        !  unstructured open boundaries                          ("key_bdy") 
     2&nambdy        !  unstructured open boundaries 
    33!----------------------------------------------------------------------- 
     4    ln_bdy         = .true.               !  Activate BDY module 
    45    nb_bdy         = 0                    !  number of open boundary sets 
    56    ln_coords_file = .true.               !  =T : read bdy coordinates from file 
  • branches/2016/dev_CMCC_2016/DOC/Namelists/nambdy_dta

    r6997 r7299  
    11!----------------------------------------------------------------------- 
    2 &nambdy_dta    !  open boundaries - external data                       ("key_bdy") 
     2&nambdy_dta    !  open boundaries - external data 
    33!----------------------------------------------------------------------- 
    44!              !  file name      ! frequency (hours) ! variable  ! time interp.!  clim   ! 'yearly'/ ! weights  ! rotation ! land/sea mask ! 
  • branches/2016/dev_CMCC_2016/DOC/TexFiles/Chapters/Chap_CFG.tex

    r6997 r7299  
    299299In particular, the AMM uses $S$-coordinates in the vertical rather than 
    300300$z$-coordinates and is forced with tidal lateral boundary conditions 
    301 using a flather boundary condition from the BDY module (key\_bdy). 
     301using a flather boundary condition from the BDY module. 
    302302The AMM configuration  uses the GLS (key\_zdfgls) turbulence scheme, the 
    303303VVL non-linear free surface(key\_vvl) and time-splitting 
     
    306306In addition to the tidal boundary condition the model may also take 
    307307open boundary conditions from a North Atlantic model. Boundaries may be 
    308 completely ommited by removing the BDY key (key\_bdy). 
     308completely omitted by setting \np{ln\_bdy} to false. 
    309309Sample surface fluxes, river forcing and a sample initial restart file 
    310310are included to test a realistic model run. The Baltic boundary is 
  • branches/2016/dev_CMCC_2016/DOC/TexFiles/Chapters/Chap_DYN.tex

    r6997 r7299  
    12091209into account when computing the surface pressure gradient. 
    12101210 
    1211 (2) When \np{ln\_tide\_pot}~=~true and \key{tide} is defined (see \S\ref{SBC_tide}),  
     1211(2) When \np{ln\_tide\_pot}~=~true and \np{ln\_tide}~=~true (see \S\ref{SBC_tide}),  
    12121212the tidal potential is taken into account when computing the surface pressure gradient. 
    12131213 
  • branches/2016/dev_CMCC_2016/DOC/TexFiles/Chapters/Chap_LBC.tex

    r6997 r7299  
    350350% Unstructured open boundaries BDY  
    351351% ==================================================================== 
    352 \section{Unstructured Open Boundary Conditions (\key{bdy}) (BDY)} 
     352\section{Unstructured Open Boundary Conditions (BDY)} 
    353353\label{LBC_bdy} 
    354354 
     
    368368Options are defined through the \ngn{nambdy} \ngn{nambdy\_index}  
    369369\ngn{nambdy\_dta} \ngn{nambdy\_dta2} namelist variables. 
    370 The BDY module is an alternative implementation of open boundary 
     370The BDY module is the core implementation of open boundary 
    371371conditions for regional configurations. It implements the Flow 
    372372Relaxation Scheme algorithm for temperature, salinity, velocities and 
     
    376376an isobath or other irregular contour.  
    377377 
    378 The BDY module was modelled on the OBC module and shares many features 
    379 and a similar coding structure \citep{Chanut2005}. 
    380  
    381 The BDY module is completely rewritten at NEMO 3.4 and there is a new 
    382 set of namelists. Boundary data files used with earlier versions of 
    383 NEMO may need to be re-ordered to work with this version. See the 
     378The BDY module was modelled on the OBC module (see NEMO 3.4) and shares many 
     379features and a similar coding structure \citep{Chanut2005}. 
     380 
     381Boundary data files used with earlier versions of NEMO may need 
     382to be re-ordered to work with this version. See the 
    384383section on the Input Boundary Data Files for details. 
    385384 
     
    388387\label{BDY_namelist} 
    389388 
     389The BDY module is activated by setting \np{ln\_bdy} to true. 
    390390It is possible to define more than one boundary ``set'' and apply 
    391391different boundary conditions to each set. The number of boundary 
  • branches/2016/dev_CMCC_2016/DOC/TexFiles/Chapters/Chap_SBC.tex

    r6997 r7299  
    776776 
    777777A module is available to compute the tidal potential and use it in the momentum equation. 
    778 This option is activated when \key{tide} is defined. 
     778This option is activated when \np{ln\_tide} is set to true in \ngn{nam\_tide}. 
    779779 
    780780Some parameters are available in namelist \ngn{nam\_tide}: 
  • branches/2016/dev_CMCC_2016/NEMOGCM/CONFIG/AMM12/EXP00/namelist_cfg

    r6489 r7299  
    189189/ 
    190190!----------------------------------------------------------------------- 
    191 &nam_tide      !   tide parameters (#ifdef key_tide) 
    192 !----------------------------------------------------------------------- 
     191&nam_tide      !   tide parameters 
     192!----------------------------------------------------------------------- 
     193   ln_tide     = .true. 
    193194   clname(1)     =   'Q1'   !  name of constituent 
    194195   clname(2)     =   'O1' 
     
    208209/ 
    209210!----------------------------------------------------------------------- 
    210 &nambdy        !  unstructured open boundaries                          ("key_bdy") 
     211&nambdy        !  unstructured open boundaries 
     212    ln_bdy         = .true. 
    211213    nb_bdy         =  1 
    212214    cn_dyn2d       = 'flather' 
     
    216218/ 
    217219!----------------------------------------------------------------------- 
    218 &nambdy_dta      !  open boundaries - external data           ("key_bdy") 
     220&nambdy_dta      !  open boundaries - external data 
    219221!----------------------------------------------------------------------- 
    220222!          !  file name  ! frequency (hours) ! variable  ! time interp. !  clim  ! 'yearly'/ ! weights  ! rotation ! land/sea mask ! 
  • branches/2016/dev_CMCC_2016/NEMOGCM/CONFIG/AMM12/cpp_AMM12.fcm

    r6140 r7299  
    1  bld::tool::fppkeys  key_bdy key_tide key_zdfgls key_diainstant key_mpp_mpi key_iomput 
     1 bld::tool::fppkeys key_zdfgls key_diainstant key_mpp_mpi key_iomput 
  • branches/2016/dev_CMCC_2016/NEMOGCM/CONFIG/C1D_PAPA/EXP00/namelist_cfg

    r6489 r7299  
    174174/ 
    175175!----------------------------------------------------------------------- 
    176 &nam_tide      !    tide parameters (#ifdef key_tide) 
    177 !----------------------------------------------------------------------- 
    178 / 
    179 !----------------------------------------------------------------------- 
    180 &nambdy        !  unstructured open boundaries                          ("key_bdy") 
    181 !----------------------------------------------------------------------- 
    182 / 
    183 !----------------------------------------------------------------------- 
    184 &nambdy_dta      !  open boundaries - external data           ("key_bdy") 
     176&nam_tide      !    tide parameters 
     177!----------------------------------------------------------------------- 
     178/ 
     179!----------------------------------------------------------------------- 
     180&nambdy        !  unstructured open boundaries                           
     181!----------------------------------------------------------------------- 
     182/ 
     183!----------------------------------------------------------------------- 
     184&nambdy_dta      !  open boundaries - external data            
    185185!----------------------------------------------------------------------- 
    186186/ 
  • branches/2016/dev_CMCC_2016/NEMOGCM/CONFIG/GYRE/EXP00/namelist_cfg

    r6489 r7299  
    154154/ 
    155155!----------------------------------------------------------------------- 
    156 &nam_tide      !    tide parameters (#ifdef key_tide) 
    157 !----------------------------------------------------------------------- 
    158 / 
    159 !----------------------------------------------------------------------- 
    160 &nambdy        !  unstructured open boundaries                          ("key_bdy") 
    161 !----------------------------------------------------------------------- 
    162 / 
    163 !----------------------------------------------------------------------- 
    164 &nambdy_dta      !  open boundaries - external data           ("key_bdy") 
     156&nam_tide      !    tide parameters 
     157!----------------------------------------------------------------------- 
     158/ 
     159!----------------------------------------------------------------------- 
     160&nambdy        !  unstructured open boundaries                           
     161!----------------------------------------------------------------------- 
     162/ 
     163!----------------------------------------------------------------------- 
     164&nambdy_dta      !  open boundaries - external data            
    165165!----------------------------------------------------------------------- 
    166166/ 
  • branches/2016/dev_CMCC_2016/NEMOGCM/CONFIG/GYRE_BFM/EXP00/namelist_cfg

    r6489 r7299  
    159159/ 
    160160!----------------------------------------------------------------------- 
    161 &nam_tide      !    tide parameters (#ifdef key_tide) 
    162 !----------------------------------------------------------------------- 
    163 / 
    164 !----------------------------------------------------------------------- 
    165 &nambdy        !  unstructured open boundaries                          ("key_bdy") 
    166 !----------------------------------------------------------------------- 
    167 / 
    168 !----------------------------------------------------------------------- 
    169 &nambdy_dta      !  open boundaries - external data           ("key_bdy") 
     161&nam_tide      !    tide parameters 
     162!----------------------------------------------------------------------- 
     163/ 
     164!----------------------------------------------------------------------- 
     165&nambdy        !  unstructured open boundaries                           
     166!----------------------------------------------------------------------- 
     167/ 
     168!----------------------------------------------------------------------- 
     169&nambdy_dta      !  open boundaries - external data            
    170170!----------------------------------------------------------------------- 
    171171/ 
  • branches/2016/dev_CMCC_2016/NEMOGCM/CONFIG/GYRE_XIOS/EXP00/namelist_cfg

    r6489 r7299  
    152152/ 
    153153!----------------------------------------------------------------------- 
    154 &nam_tide      !    tide parameters (#ifdef key_tide) 
    155 !----------------------------------------------------------------------- 
    156 / 
    157 !----------------------------------------------------------------------- 
    158 &nambdy        !  unstructured open boundaries                          ("key_bdy") 
    159 !----------------------------------------------------------------------- 
    160 / 
    161 !----------------------------------------------------------------------- 
    162 &nambdy_dta      !  open boundaries - external data           ("key_bdy") 
     154&nam_tide      !    tide parameters 
     155!----------------------------------------------------------------------- 
     156/ 
     157!----------------------------------------------------------------------- 
     158&nambdy        !  unstructured open boundaries                           
     159!----------------------------------------------------------------------- 
     160/ 
     161!----------------------------------------------------------------------- 
     162&nambdy_dta      !  open boundaries - external data            
    163163!----------------------------------------------------------------------- 
    164164/ 
  • branches/2016/dev_CMCC_2016/NEMOGCM/CONFIG/ORCA2_LIM_CFC_C14b/EXP00/1_namelist_cfg

    r6140 r7299  
    305305!!   namlbc        lateral momentum boundary condition 
    306306!!   namagrif      agrif nested grid ( read by child model only )       ("key_agrif")  
    307 !!   nambdy        Unstructured open boundaries                         ("key_bdy") 
    308 !!   namtide       Tidal forcing at open boundaries                     ("key_bdy_tides") 
     307!!   nambdy        Unstructured open boundaries 
     308!!   namtide       Tidal forcing at open boundaries 
    309309!!====================================================================== 
    310310! 
     
    324324/ 
    325325!----------------------------------------------------------------------- 
    326 &nambdy        !  unstructured open boundaries                          ("key_bdy") 
    327 !----------------------------------------------------------------------- 
     326&nambdy        !  unstructured open boundaries 
     327!----------------------------------------------------------------------- 
     328    ln_bdy         = .false.              !  Use unstructured open boundaries 
    328329    nb_bdy = 1                            !  number of open boundary sets        
    329330    ln_coords_file = .true.               !  =T : read bdy coordinates from file 
     
    351352/ 
    352353!----------------------------------------------------------------------- 
    353 &nambdy_dta      !  open boundaries - external data           ("key_bdy") 
     354&nambdy_dta      !  open boundaries - external data 
    354355!----------------------------------------------------------------------- 
    355356!              !   file name    ! frequency (hours) !  variable  ! time interpol. !  clim   ! 'yearly'/ ! weights  ! rotation ! 
  • branches/2016/dev_CMCC_2016/NEMOGCM/CONFIG/ORCA2_LIM_CFC_C14b/EXP00/namelist_cfg

    r6489 r7299  
    138138/ 
    139139!----------------------------------------------------------------------- 
    140 &nam_tide      !   tide parameters (#ifdef key_tide) 
    141 !----------------------------------------------------------------------- 
    142 / 
    143 !----------------------------------------------------------------------- 
    144 &nambdy        !  unstructured open boundaries                          ("key_bdy") 
    145 !----------------------------------------------------------------------- 
    146 / 
    147 !----------------------------------------------------------------------- 
    148 &nambdy_dta      !  open boundaries - external data           ("key_bdy") 
     140&nam_tide      !   tide parameters 
     141!----------------------------------------------------------------------- 
     142/ 
     143!----------------------------------------------------------------------- 
     144&nambdy        !  unstructured open boundaries                           
     145!----------------------------------------------------------------------- 
     146/ 
     147!----------------------------------------------------------------------- 
     148&nambdy_dta      !  open boundaries - external data            
    149149!----------------------------------------------------------------------- 
    150150/ 
  • branches/2016/dev_CMCC_2016/NEMOGCM/CONFIG/SHARED/namelist_ref

    r6497 r7299  
    589589!!   namagrif      agrif nested grid ( read by child model only )       ("key_agrif") 
    590590!!   nam_tide      Tidal forcing  
    591 !!   nambdy        Unstructured open boundaries                         ("key_bdy") 
    592 !!   nambdy_dta    Unstructured open boundaries - external data         ("key_bdy") 
    593 !!   nambdy_tide   tidal forcing at open boundaries                     ("key_bdy_tides") 
     591!!   nambdy        Unstructured open boundaries                          
     592!!   nambdy_dta    Unstructured open boundaries - external data          
     593!!   nambdy_tide   tidal forcing at open boundaries                      
    594594!!====================================================================== 
    595595! 
     
    611611/ 
    612612!----------------------------------------------------------------------- 
    613 &nam_tide      !   tide parameters                                      ("key_tide") 
    614 !----------------------------------------------------------------------- 
     613&nam_tide      !   tide parameters 
     614!----------------------------------------------------------------------- 
     615   ln_tide     = .false. 
    615616   ln_tide_pot = .true.    !  use tidal potential forcing 
    616617   ln_tide_ramp= .false.   ! 
     
    619620/ 
    620621!----------------------------------------------------------------------- 
    621 &nambdy        !  unstructured open boundaries                          ("key_bdy") 
    622 !----------------------------------------------------------------------- 
     622&nambdy        !  unstructured open boundaries                           
     623!----------------------------------------------------------------------- 
     624    ln_bdy         = .false.              !  Use unstructured open boundaries 
    623625    nb_bdy         = 0                    !  number of open boundary sets 
    624626    ln_coords_file = .true.               !  =T : read bdy coordinates from file 
     
    653655/ 
    654656!----------------------------------------------------------------------- 
    655 &nambdy_dta    !  open boundaries - external data                       ("key_bdy") 
     657&nambdy_dta    !  open boundaries - external data                        
    656658!----------------------------------------------------------------------- 
    657659!              !  file name      ! frequency (hours) ! variable  ! time interp.!  clim   ! 'yearly'/ ! weights  ! rotation ! land/sea mask ! 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/LIM_SRC_3/limcons.F90

    r6416 r7299  
    286286      REAL(wp), PARAMETER             :: zconv = 1.e-9 ! convert W to GW and kg to Mt 
    287287 
    288 #if ! defined key_bdy 
    289288      ! heat flux 
    290289      zhfx  = glob_sum( ( hfx_in - hfx_out - diag_heat - diag_trp_ei - diag_trp_es - SUM( qevap_ice * a_i_b, dim=3 ) )  & 
     
    304303      IF( ABS( zsfx ) > zs_sill ) WRITE(numout,*) 'violation sfx    [psu*Mt/day]   (',cd_routine,')  = ',(zsfx) 
    305304      IF( ABS( zhfx ) > zh_sill ) WRITE(numout,*) 'violation hfx    [GW]           (',cd_routine,')  = ',(zhfx) 
    306 #endif 
    307305 
    308306   END SUBROUTINE lim_cons_final 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/LIM_SRC_3/limrhg.F90

    r6416 r7299  
    4141   USE agrif_lim2_interp 
    4242#endif 
    43 #if defined key_bdy 
     43   USE bdy_oce   , ONLY: ln_bdy 
    4444   USE bdyice_lim 
    45 #endif 
    4645 
    4746   IMPLICIT NONE 
     
    460459            CALL agrif_rhg_lim2( jter, nn_nevp, 'U' ) 
    461460#endif 
    462 #if defined key_bdy 
    463          CALL bdy_ice_lim_dyn( 'U' ) 
    464 #endif          
     461         IF( ln_bdy ) CALL bdy_ice_lim_dyn( 'U' ) 
    465462 
    466463            DO jj = k_j1+1, k_jpj-1 
     
    486483            CALL agrif_rhg_lim2( jter, nn_nevp, 'V' ) 
    487484#endif 
    488 #if defined key_bdy 
    489          CALL bdy_ice_lim_dyn( 'V' ) 
    490 #endif          
     485         IF( ln_bdy ) CALL bdy_ice_lim_dyn( 'V' ) 
    491486 
    492487         ELSE  
     
    513508            CALL agrif_rhg_lim2( jter, nn_nevp, 'V' ) 
    514509#endif 
    515 #if defined key_bdy 
    516          CALL bdy_ice_lim_dyn( 'V' ) 
    517 #endif          
     510         IF( ln_bdy ) CALL bdy_ice_lim_dyn( 'V' ) 
    518511 
    519512            DO jj = k_j1+1, k_jpj-1 
     
    538531            CALL agrif_rhg_lim2( jter, nn_nevp, 'U' ) 
    539532#endif 
    540 #if defined key_bdy 
    541          CALL bdy_ice_lim_dyn( 'U' ) 
    542 #endif          
     533         IF( ln_bdy ) CALL bdy_ice_lim_dyn( 'U' ) 
    543534 
    544535         ENDIF 
     
    577568      CALL agrif_rhg_lim2( nn_nevp , nn_nevp, 'V' ) 
    578569#endif 
    579 #if defined key_bdy 
    580       CALL bdy_ice_lim_dyn( 'U' ) 
    581       CALL bdy_ice_lim_dyn( 'V' ) 
    582 #endif          
     570      IF( ln_bdy ) THEN 
     571         CALL bdy_ice_lim_dyn( 'U' ) ; CALL bdy_ice_lim_dyn( 'V' ) 
     572      ENDIF 
    583573 
    584574      DO jj = k_j1+1, k_jpj-1  
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/LIM_SRC_3/limsbc.F90

    r6416 r7299  
    3636   USE limctl         !  
    3737   USE limcons        !  
     38   USE bdy_oce  , ONLY: ln_bdy 
    3839   ! 
    3940   USE in_out_manager ! I/O manager 
     
    221222 
    222223      ! conservation test 
    223       IF( ln_limdiahsb )   CALL lim_cons_final( 'limsbc' ) 
     224      IF( ln_limdiahsb .AND. .NOT. ln_bdy)   CALL lim_cons_final( 'limsbc' ) 
    224225 
    225226      ! control prints 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/NST_SRC/agrif_user.F90

    r6140 r7299  
    6161   USE nemogcm 
    6262   USE tradmp 
    63    USE bdy_par 
     63   USE bdy_oce   , ONLY: ln_bdy 
    6464 
    6565   IMPLICIT NONE 
     
    7878   ln_tradmp = .FALSE. 
    7979   ! no open boundary on fine grids 
    80    lk_bdy = .FALSE. 
     80   ln_bdy = .FALSE. 
    8181 
    8282 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/BDY/bdy_oce.F90

    r6140 r7299  
    1010   !!            3.6  !  2014-01  (C. Rousset) add ice boundary conditions for lim3 
    1111   !!---------------------------------------------------------------------- 
    12 #if defined key_bdy  
    13    !!---------------------------------------------------------------------- 
    14    !!   'key_bdy'                      Unstructured Open Boundary Condition 
    15    !!---------------------------------------------------------------------- 
    1612   USE par_oce         ! ocean parameters 
    17    USE bdy_par         ! Unstructured boundary parameters 
    1813   USE lib_mpp         ! distributed memory computing 
    1914 
    2015   IMPLICIT NONE 
    2116   PUBLIC 
     17 
     18   INTEGER, PUBLIC, PARAMETER ::   jp_bdy  = 10       !: Maximum number of bdy sets 
     19   INTEGER, PUBLIC, PARAMETER ::   jpbgrd  = 3        !: Number of horizontal grid types used  (T, U, V) 
    2220 
    2321   TYPE, PUBLIC ::   OBC_INDEX    !: Indices and weights which define the open boundary 
     
    8280   !! Namelist variables 
    8381   !!---------------------------------------------------------------------- 
     82   LOGICAL, PUBLIC            ::   ln_bdy                   !: Unstructured Ocean Boundary Condition 
     83 
    8484   CHARACTER(len=80), DIMENSION(jp_bdy) ::   cn_coords_file !: Name of bdy coordinates file 
    8585   CHARACTER(len=80)                    ::   cn_mask_file   !: Name of bdy mask file 
     
    166166   END FUNCTION bdy_oce_alloc 
    167167 
    168 #else 
    169    !!---------------------------------------------------------------------- 
    170    !!   Dummy module                NO Unstructured Open Boundary Condition 
    171    !!---------------------------------------------------------------------- 
    172    LOGICAL ::   ln_tides = .false.  !: =T apply tidal harmonic forcing along open boundaries 
    173 #endif 
    174  
    175168   !!====================================================================== 
    176169END MODULE bdy_oce 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/BDY/bdydta.F90

    r6140 r7299  
    1212   !!            3.4  !  2011     (D. Storkey) rewrite in preparation for OBC-BDY merge 
    1313   !!            3.6  !  2012-01  (C. Rousset) add ice boundary conditions for lim3 
    14    !!---------------------------------------------------------------------- 
    15 #if defined key_bdy 
    16    !!---------------------------------------------------------------------- 
    17    !!   'key_bdy'                     Open Boundary Conditions 
    1814   !!---------------------------------------------------------------------- 
    1915   !!    bdy_dta        : read external data along open boundaries from file 
     
    3632#endif 
    3733   USE sbcapr 
     34   USE sbctide         ! Tidal forcing or not 
    3835 
    3936   IMPLICIT NONE 
     
    381378      END DO  ! ib_bdy 
    382379 
    383 #if defined key_tide 
    384       IF (ln_dynspg_ts) THEN      ! Fill temporary arrays with slow-varying bdy data                            
    385          DO ib_bdy = 1, nb_bdy    ! Tidal component added in ts loop 
    386             IF ( nn_dyn2d_dta(ib_bdy) .ge. 2 ) THEN 
    387                nblen => idx_bdy(ib_bdy)%nblen 
    388                nblenrim => idx_bdy(ib_bdy)%nblenrim 
    389                IF( cn_dyn2d(ib_bdy) == 'frs' ) THEN; ilen1(:)=nblen(:) ; ELSE ; ilen1(:)=nblenrim(:) ; ENDIF  
    390                IF ( dta_bdy(ib_bdy)%ll_ssh ) dta_bdy_s(ib_bdy)%ssh(1:ilen1(1)) = dta_bdy(ib_bdy)%ssh(1:ilen1(1)) 
    391                IF ( dta_bdy(ib_bdy)%ll_u2d ) dta_bdy_s(ib_bdy)%u2d(1:ilen1(2)) = dta_bdy(ib_bdy)%u2d(1:ilen1(2)) 
    392                IF ( dta_bdy(ib_bdy)%ll_v2d ) dta_bdy_s(ib_bdy)%v2d(1:ilen1(3)) = dta_bdy(ib_bdy)%v2d(1:ilen1(3)) 
    393             ENDIF 
    394          END DO 
    395       ELSE ! Add tides if not split-explicit free surface else this is done in ts loop 
    396          ! 
    397          CALL bdy_dta_tides( kt=kt, time_offset=time_offset ) 
     380      IF ( ln_tide ) THEN 
     381         IF (ln_dynspg_ts) THEN      ! Fill temporary arrays with slow-varying bdy data                            
     382            DO ib_bdy = 1, nb_bdy    ! Tidal component added in ts loop 
     383               IF ( nn_dyn2d_dta(ib_bdy) .ge. 2 ) THEN 
     384                  nblen => idx_bdy(ib_bdy)%nblen 
     385                  nblenrim => idx_bdy(ib_bdy)%nblenrim 
     386                  IF( cn_dyn2d(ib_bdy) == 'frs' ) THEN; ilen1(:)=nblen(:) ; ELSE ; ilen1(:)=nblenrim(:) ; ENDIF  
     387                  IF ( dta_bdy(ib_bdy)%ll_ssh ) dta_bdy_s(ib_bdy)%ssh(1:ilen1(1)) = dta_bdy(ib_bdy)%ssh(1:ilen1(1)) 
     388                  IF ( dta_bdy(ib_bdy)%ll_u2d ) dta_bdy_s(ib_bdy)%u2d(1:ilen1(2)) = dta_bdy(ib_bdy)%u2d(1:ilen1(2)) 
     389                  IF ( dta_bdy(ib_bdy)%ll_v2d ) dta_bdy_s(ib_bdy)%v2d(1:ilen1(3)) = dta_bdy(ib_bdy)%v2d(1:ilen1(3)) 
     390               ENDIF 
     391            END DO 
     392         ELSE ! Add tides if not split-explicit free surface else this is done in ts loop 
     393            ! 
     394            CALL bdy_dta_tides( kt=kt, time_offset=time_offset ) 
     395         ENDIF 
    398396      ENDIF 
    399 #endif 
    400397 
    401398      IF ( ln_apr_obc ) THEN 
     
    899896   END SUBROUTINE bdy_dta_init 
    900897 
    901 #else 
    902    !!---------------------------------------------------------------------- 
    903    !!   Dummy module                   NO Open Boundary Conditions 
    904    !!---------------------------------------------------------------------- 
    905 CONTAINS 
    906    SUBROUTINE bdy_dta( kt, jit, time_offset ) ! Empty routine 
    907       INTEGER, INTENT( in )           ::   kt     
    908       INTEGER, INTENT( in ), OPTIONAL ::   jit    
    909       INTEGER, INTENT( in ), OPTIONAL ::   time_offset 
    910       WRITE(*,*) 'bdy_dta: You should not have seen this print! error?', kt 
    911    END SUBROUTINE bdy_dta 
    912    SUBROUTINE bdy_dta_init()                  ! Empty routine 
    913       WRITE(*,*) 'bdy_dta_init: You should not have seen this print! error?' 
    914    END SUBROUTINE bdy_dta_init 
    915 #endif 
    916  
    917898   !!============================================================================== 
    918899END MODULE bdydta 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/BDY/bdydyn.F90

    r6140 r7299  
    1111   !!            3.3  !  2010-09  (D.Storkey) add ice boundary conditions 
    1212   !!            3.4  !  2011     (D. Storkey) rewrite in preparation for OBC-BDY merge 
    13    !!---------------------------------------------------------------------- 
    14 #if defined key_bdy  
    15    !!---------------------------------------------------------------------- 
    16    !!   'key_bdy' :                    Unstructured Open Boundary Condition 
    1713   !!---------------------------------------------------------------------- 
    1814   !!   bdy_dyn        : split velocities into barotropic and baroclinic parts 
     
    137133   END SUBROUTINE bdy_dyn 
    138134 
    139 #else 
    140    !!---------------------------------------------------------------------- 
    141    !!   Dummy module                   NO Unstruct Open Boundary Conditions 
    142    !!---------------------------------------------------------------------- 
    143 CONTAINS 
    144    SUBROUTINE bdy_dyn( kt )      ! Empty routine 
    145       WRITE(*,*) 'bdy_dyn: You should not have seen this print! error?', kt 
    146    END SUBROUTINE bdy_dyn 
    147 #endif 
    148  
    149135   !!====================================================================== 
    150136END MODULE bdydyn 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/BDY/bdydyn2d.F90

    r5930 r7299  
    77   !!            3.5  !  2012     (S. Mocavero, I. Epicoco) Optimization of BDY communications 
    88   !!            3.5  !  2013-07  (J. Chanut) Compliant with time splitting changes 
    9    !!---------------------------------------------------------------------- 
    10 #if defined key_bdy  
    11    !!---------------------------------------------------------------------- 
    12    !!   'key_bdy' :                    Unstructured Open Boundary Condition 
    139   !!---------------------------------------------------------------------- 
    1410   !!   bdy_dyn2d          : Apply open boundary conditions to barotropic variables. 
     
    310306   END SUBROUTINE bdy_ssh 
    311307 
    312 #else 
    313    !!---------------------------------------------------------------------- 
    314    !!   Dummy module                   NO Unstruct Open Boundary Conditions 
    315    !!---------------------------------------------------------------------- 
    316 CONTAINS 
    317    SUBROUTINE bdy_dyn2d( kt )      ! Empty routine 
    318       INTEGER, intent(in) :: kt 
    319       WRITE(*,*) 'bdy_dyn2d: You should not have seen this print! error?', kt 
    320    END SUBROUTINE bdy_dyn2d 
    321  
    322 #endif 
    323  
    324308   !!====================================================================== 
    325309END MODULE bdydyn2d 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/BDY/bdydyn3d.F90

    r6140 r7299  
    66   !! History :  3.4  !  2011     (D. Storkey) new module as part of BDY rewrite  
    77   !!            3.5  !  2012     (S. Mocavero, I. Epicoco) Optimization of BDY communications 
    8    !!---------------------------------------------------------------------- 
    9 #if defined key_bdy  
    10    !!---------------------------------------------------------------------- 
    11    !!   'key_bdy' :                    Unstructured Open Boundary Condition 
    128   !!---------------------------------------------------------------------- 
    139   !!   bdy_dyn3d        : apply open boundary conditions to baroclinic velocities 
     
    296292   END SUBROUTINE bdy_dyn3d_dmp 
    297293 
    298 #else 
    299    !!---------------------------------------------------------------------- 
    300    !!   Dummy module                   NO Unstruct Open Boundary Conditions 
    301    !!---------------------------------------------------------------------- 
    302 CONTAINS 
    303    SUBROUTINE bdy_dyn3d( kt )      ! Empty routine 
    304       WRITE(*,*) 'bdy_dyn3d: You should not have seen this print! error?', kt 
    305    END SUBROUTINE bdy_dyn3d 
    306    SUBROUTINE bdy_dyn3d_dmp( kt )      ! Empty routine 
    307       WRITE(*,*) 'bdy_dyn3d_dmp: You should not have seen this print! error?', kt 
    308    END SUBROUTINE bdy_dyn3d_dmp 
    309 #endif 
    310  
    311294   !!====================================================================== 
    312295END MODULE bdydyn3d 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/BDY/bdyice_lim.F90

    r5836 r7299  
    88   !!              -   !  2012-01 (C. Rousset)  add lim3 and remove useless jk loop  
    99   !!---------------------------------------------------------------------- 
    10 #if defined   key_bdy   &&  ( defined key_lim2 || defined key_lim3 ) 
    11    !!---------------------------------------------------------------------- 
    12    !!   'key_bdy'            and                 Unstructured Open Boundary Conditions 
     10#if defined key_lim2 || defined key_lim3 
     11   !!---------------------------------------------------------------------- 
    1312   !!   'key_lim2'                                                 LIM-2 sea ice model 
    1413   !!   'key_lim3'                                                 LIM-3 sea ice model 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/BDY/bdyini.F90

    r6140 r7299  
    1313   !!            3.4  !  2012     (J. Chanut) straight open boundary case update 
    1414   !!            3.5  !  2012     (S. Mocavero, I. Epicoco) optimization of BDY communications 
    15    !!---------------------------------------------------------------------- 
    16 #if defined key_bdy 
    17    !!---------------------------------------------------------------------- 
    18    !!   'key_bdy'                     Unstructured Open Boundary Conditions 
     15   !!            3.7  !  2016     (T. Lovato) Remove bdy macro, call here init for dta and tides 
    1916   !!---------------------------------------------------------------------- 
    2017   !!   bdy_init      : Initialization of unstructured open boundaries 
     
    2320   USE dom_oce        ! ocean space and time domain 
    2421   USE bdy_oce        ! unstructured open boundary conditions 
    25    USE sbctide  , ONLY: lk_tide ! Tidal forcing or not 
     22   USE bdydta         ! open boundary cond. setting   (bdy_dta_init routine) 
     23   USE bdytides       ! open boundary cond. setting   (bdytide_init routine) 
     24   USE sbctide        ! Tidal forcing or not 
    2625   USE phycst   , ONLY: rday 
    2726   ! 
     
    5352   !!---------------------------------------------------------------------- 
    5453CONTAINS 
    55     
     54 
    5655   SUBROUTINE bdy_init 
    5756      !!---------------------------------------------------------------------- 
    5857      !!                 ***  ROUTINE bdy_init  *** 
     58      !! 
     59      !! ** Purpose :   Initialization of the dynamics and tracer fields with 
     60      !!              unstructured open boundaries. 
     61      !! 
     62      !! ** Method  :   Read initialization arrays (mask, indices) to identify 
     63      !!              an unstructured open boundary 
     64      !! 
     65      !! ** Input   :  bdy_init.nc, input file for unstructured open boundaries 
     66      !!---------------------------------------------------------------------- 
     67      NAMELIST/nambdy/ ln_bdy, nb_bdy, ln_coords_file, cn_coords_file,         & 
     68         &             ln_mask_file, cn_mask_file, cn_dyn2d, nn_dyn2d_dta,     & 
     69         &             cn_dyn3d, nn_dyn3d_dta, cn_tra, nn_tra_dta,             & 
     70         &             ln_tra_dmp, ln_dyn3d_dmp, rn_time_dmp, rn_time_dmp_out, & 
     71         &             cn_ice_lim, nn_ice_lim_dta,                             & 
     72         &             rn_ice_tem, rn_ice_sal, rn_ice_age,                     & 
     73         &             ln_vol, nn_volctl, nn_rimwidth 
     74         ! 
     75      INTEGER  ::   ios                 ! Local integer output status for namelist read 
     76      !!---------------------------------------------------------------------- 
     77      ! 
     78      IF( nn_timing == 1 )   CALL timing_start('bdy_init') 
     79 
     80      ! ------------------------ 
     81      ! Read namelist parameters 
     82      ! ------------------------ 
     83      REWIND( numnam_ref )              ! Namelist nambdy in reference namelist :Unstructured open boundaries 
     84      READ  ( numnam_ref, nambdy, IOSTAT = ios, ERR = 901) 
     85901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nambdy in reference namelist', lwp ) 
     86      ! 
     87      REWIND( numnam_cfg )              ! Namelist nambdy in configuration namelist :Unstructured open boundaries 
     88      READ  ( numnam_cfg, nambdy, IOSTAT = ios, ERR = 902 ) 
     89902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nambdy in configuration namelist', lwp ) 
     90      IF(lwm) WRITE ( numond, nambdy ) 
     91 
     92      ! ----------------------------------------- 
     93      ! unstructured open boundaries use control 
     94      ! ----------------------------------------- 
     95      IF ( ln_bdy ) THEN 
     96         IF(lwp) WRITE(numout,*) 
     97         IF(lwp) WRITE(numout,*) 'bdy_init : initialization of open boundaries' 
     98         IF(lwp) WRITE(numout,*) '~~~~~~~~' 
     99         ! 
     100         ! Open boundaries definition (arrays and masks) 
     101         CALL bdy_segs 
     102         ! 
     103         ! Open boundaries initialisation of external data arrays 
     104         CALL bdy_dta_init 
     105         ! 
     106         ! Open boundaries initialisation of tidal harmonic forcing 
     107         IF( ln_tide ) CALL bdytide_init 
     108         ! 
     109      ELSE 
     110         IF(lwp) WRITE(numout,*) 
     111         IF(lwp) WRITE(numout,*) 'bdy_init : open boundaries not used (ln_bdy = F)' 
     112         IF(lwp) WRITE(numout,*) '~~~~~~~~' 
     113         ! 
     114      ENDIF 
     115      ! 
     116      IF( nn_timing == 1 )   CALL timing_stop('bdy_init') 
     117      ! 
     118   END SUBROUTINE bdy_init 
     119    
     120   SUBROUTINE bdy_segs 
     121      !!---------------------------------------------------------------------- 
     122      !!                 ***  ROUTINE bdy_init  *** 
    59123      !!          
    60       !! ** Purpose :   Initialization of the dynamics and tracer fields with  
    61       !!              unstructured open boundaries. 
     124      !! ** Purpose :   Definition of unstructured open boundaries. 
    62125      !! 
    63126      !! ** Method  :   Read initialization arrays (mask, indices) to identify  
     
    90153      REAL(wp), POINTER, DIMENSION(:,:)       ::   zfmask  ! temporary fmask array excluding coastal boundary condition (shlat) 
    91154      !! 
    92       CHARACTER(LEN=80),DIMENSION(jpbgrd)  ::   clfile     ! Namelist variables 
    93155      CHARACTER(LEN=1)                     ::   ctypebdy   !     -        -  
    94156      INTEGER                              ::   nbdyind, nbdybeg, nbdyend 
    95157      !! 
    96       NAMELIST/nambdy/ nb_bdy, ln_coords_file, cn_coords_file,                 & 
    97          &             ln_mask_file, cn_mask_file, cn_dyn2d, nn_dyn2d_dta,     & 
    98          &             cn_dyn3d, nn_dyn3d_dta, cn_tra, nn_tra_dta,             &   
    99          &             ln_tra_dmp, ln_dyn3d_dmp, rn_time_dmp, rn_time_dmp_out, & 
    100          &             cn_ice_lim, nn_ice_lim_dta,                           & 
    101          &             rn_ice_tem, rn_ice_sal, rn_ice_age,                 & 
    102          &             ln_vol, nn_volctl, nn_rimwidth 
    103          ! 
    104158      NAMELIST/nambdy_index/ ctypebdy, nbdyind, nbdybeg, nbdyend 
    105159      INTEGER  ::   ios                 ! Local integer output status for namelist read 
    106160      !!---------------------------------------------------------------------- 
    107161      ! 
    108       IF( nn_timing == 1 )   CALL timing_start('bdy_init') 
    109       ! 
    110       IF(lwp) WRITE(numout,*) 
    111       IF(lwp) WRITE(numout,*) 'bdy_init : initialization of open boundaries' 
    112       IF(lwp) WRITE(numout,*) '~~~~~~~~' 
    113       ! 
    114       IF( jperio /= 0 )   CALL ctl_stop( 'Cyclic or symmetric,',   & 
    115          &                               ' and general open boundary condition are not compatible' ) 
    116  
     162      IF( nn_timing == 1 )   CALL timing_start('bdy_segs') 
     163      ! 
    117164      cgrid = (/'t','u','v'/) 
    118        
    119       ! ------------------------ 
    120       ! Read namelist parameters 
    121       ! ------------------------ 
    122       REWIND( numnam_ref )              ! Namelist nambdy in reference namelist :Unstructured open boundaries   
    123       READ  ( numnam_ref, nambdy, IOSTAT = ios, ERR = 901) 
    124 901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nambdy in reference namelist', lwp ) 
    125       ! 
    126       REWIND( numnam_cfg )              ! Namelist nambdy in configuration namelist :Unstructured open boundaries 
    127       READ  ( numnam_cfg, nambdy, IOSTAT = ios, ERR = 902 ) 
    128 902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nambdy in configuration namelist', lwp ) 
    129       IF(lwm) WRITE ( numond, nambdy ) 
    130165 
    131166      ! ----------------------------------------- 
    132167      ! Check and write out namelist parameters 
    133168      ! ----------------------------------------- 
    134       !                                   ! control prints 
    135       IF(lwp) WRITE(numout,*) '   nambdy' 
     169      IF( jperio /= 0 )   CALL ctl_stop( 'bdy_segs: Cyclic or symmetric,',   & 
     170         &                               ' and general open boundary condition are not compatible' ) 
    136171 
    137172      IF( nb_bdy == 0 ) THEN  
     
    189224              CASE DEFAULT   ;   CALL ctl_stop( 'nn_dyn2d_dta must be between 0 and 3' ) 
    190225           END SELECT 
    191            IF (( nn_dyn2d_dta(ib_bdy) .ge. 2 ).AND.(.NOT.lk_tide)) THEN 
    192              CALL ctl_stop( 'You must activate key_tide to add tidal forcing at open boundaries' ) 
     226           IF (( nn_dyn2d_dta(ib_bdy) .ge. 2 ).AND.(.NOT.ln_tide)) THEN 
     227             CALL ctl_stop( 'You must activate with ln_tide to add tidal forcing at open boundaries' ) 
    193228           ENDIF 
    194229        ENDIF 
     
    839874               IF(lwp) THEN         ! Since all procs read global data only need to do this check on one proc... 
    840875                  IF( nbrdta(ib,igrd,ib_bdy) < nbrdta(ibm1,igrd,ib_bdy) ) THEN 
    841                      CALL ctl_stop('bdy_init : ERROR : boundary data in file must be defined ', & 
     876                     CALL ctl_stop('bdy_segs : ERROR : boundary data in file must be defined ', & 
    842877                          &        ' in order of distance from edge nbr A utility for re-ordering ', & 
    843878                          &        ' boundary coordinates and data files exists in the TOOLS/OBC directory') 
     
    13001335      CALL wrk_dealloc(jpi,jpj,   zfmask )  
    13011336      ! 
    1302       IF( nn_timing == 1 )   CALL timing_stop('bdy_init') 
    1303       ! 
    1304    END SUBROUTINE bdy_init 
    1305  
     1337      IF( nn_timing == 1 )   CALL timing_stop('bdy_segs') 
     1338      ! 
     1339   END SUBROUTINE bdy_segs 
    13061340 
    13071341   SUBROUTINE bdy_ctl_seg 
     
    17131747   END SUBROUTINE bdy_ctl_corn 
    17141748 
    1715 #else 
    1716    !!--------------------------------------------------------------------------------- 
    1717    !!   Dummy module                                   NO open boundaries 
    1718    !!--------------------------------------------------------------------------------- 
    1719 CONTAINS 
    1720    SUBROUTINE bdy_init      ! Dummy routine 
    1721    END SUBROUTINE bdy_init 
    1722 #endif 
    1723  
    17241749   !!================================================================================= 
    17251750END MODULE bdyini 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/BDY/bdylib.F90

    r6140 r7299  
    55   !!====================================================================== 
    66   !! History :  3.6  !  2013     (D. Storkey) original code 
     7   !!            4.0  !  2014     (T. Lovato) Generalize OBC structure 
    78   !!---------------------------------------------------------------------- 
    8 #if defined key_bdy  
    9    !!---------------------------------------------------------------------- 
    10    !!   'key_bdy' :                    Unstructured Open Boundary Condition 
    119   !!---------------------------------------------------------------------- 
    1210   !!   bdy_orlanski_2d 
     
    2523   PRIVATE 
    2624 
    27    PUBLIC   bdy_orlanski_2d     ! routine called where? 
    28    PUBLIC   bdy_orlanski_3d     ! routine called where? 
     25   PUBLIC   bdy_frs, bdy_spe, bdy_nmn, bdy_orl 
     26   PUBLIC   bdy_orlanski_2d 
     27   PUBLIC   bdy_orlanski_3d 
    2928 
    3029   !!---------------------------------------------------------------------- 
    31    !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     30   !! NEMO/OPA 4.0 , NEMO Consortium (2016) 
    3231   !! $Id$  
    3332   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    3433   !!---------------------------------------------------------------------- 
    3534CONTAINS 
     35 
     36   SUBROUTINE bdy_frs( idx, pta, dta ) 
     37      !!---------------------------------------------------------------------- 
     38      !!                 ***  SUBROUTINE bdy_frs  *** 
     39      !! 
     40      !! ** Purpose : Apply the Flow Relaxation Scheme for tracers at open boundaries. 
     41      !! 
     42      !! Reference : Engedahl H., 1995, Tellus, 365-382. 
     43      !!---------------------------------------------------------------------- 
     44      TYPE(OBC_INDEX),                     INTENT(in) ::   idx  ! OBC indices 
     45      REAL(wp), DIMENSION(:,:),            INTENT(in) ::   dta  ! OBC external data 
     46      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   pta  ! tracer trend 
     47      !! 
     48      REAL(wp) ::   zwgt           ! boundary weight 
     49      INTEGER  ::   ib, ik, igrd   ! dummy loop indices 
     50      INTEGER  ::   ii, ij         ! 2D addresses 
     51      !!---------------------------------------------------------------------- 
     52      ! 
     53      IF( nn_timing == 1 ) CALL timing_start('bdy_frs') 
     54      !  
     55      igrd = 1                       ! Everything is at T-points here 
     56      DO ib = 1, idx%nblen(igrd) 
     57         DO ik = 1, jpkm1 
     58            ii = idx%nbi(ib,igrd)  
     59            ij = idx%nbj(ib,igrd) 
     60            zwgt = idx%nbw(ib,igrd) 
     61            pta(ii,ij,ik) = ( pta(ii,ij,ik) + zwgt * (dta(ib,ik) - pta(ii,ij,ik) ) ) * tmask(ii,ij,ik) 
     62         END DO 
     63      END DO 
     64      ! 
     65      IF( nn_timing == 1 ) CALL timing_stop('bdy_frs') 
     66      ! 
     67   END SUBROUTINE bdy_frs 
     68 
     69   SUBROUTINE bdy_spe( idx, pta, dta ) 
     70      !!---------------------------------------------------------------------- 
     71      !!                 ***  SUBROUTINE bdy_spe  *** 
     72      !! 
     73      !! ** Purpose : Apply a specified value for tracers at open boundaries. 
     74      !! 
     75      !!---------------------------------------------------------------------- 
     76      TYPE(OBC_INDEX),                     INTENT(in) ::   idx  ! OBC indices 
     77      REAL(wp), DIMENSION(:,:),            INTENT(in) ::   dta  ! OBC external data 
     78      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   pta  ! tracer trend 
     79      !! 
     80      REAL(wp) ::   zwgt           ! boundary weight 
     81      INTEGER  ::   ib, ik, igrd   ! dummy loop indices 
     82      INTEGER  ::   ii, ij         ! 2D addresses 
     83      !!---------------------------------------------------------------------- 
     84      ! 
     85      IF( nn_timing == 1 ) CALL timing_start('bdy_spe') 
     86      ! 
     87      igrd = 1                       ! Everything is at T-points here 
     88      DO ib = 1, idx%nblenrim(igrd) 
     89         ii = idx%nbi(ib,igrd) 
     90         ij = idx%nbj(ib,igrd) 
     91         DO ik = 1, jpkm1 
     92            pta(ii,ij,ik) = dta(ib,ik) * tmask(ii,ij,ik) 
     93         END DO 
     94      END DO 
     95      ! 
     96      IF( nn_timing == 1 ) CALL timing_stop('bdy_spe') 
     97      ! 
     98   END SUBROUTINE bdy_spe 
     99 
     100   SUBROUTINE bdy_nmn( idx, pta ) 
     101      !!---------------------------------------------------------------------- 
     102      !!                 ***  SUBROUTINE bdy_nmn  *** 
     103      !! 
     104      !! ** Purpose : Duplicate the value for tracers at open boundaries. 
     105      !! 
     106      !!---------------------------------------------------------------------- 
     107      TYPE(OBC_INDEX),                     INTENT(in) ::   idx  ! OBC indices 
     108      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   pta  ! tracer trend 
     109      !! 
     110      REAL(wp) ::   zwgt           ! boundary weight 
     111      INTEGER  ::   ib, ik, igrd   ! dummy loop indices 
     112      INTEGER  ::   ii, ij, zcoef, zcoef1, zcoef2, ip, jp   ! 2D addresses 
     113      !!---------------------------------------------------------------------- 
     114      ! 
     115      IF( nn_timing == 1 ) CALL timing_start('bdy_nmn') 
     116      ! 
     117      igrd = 1                       ! Everything is at T-points here 
     118      DO ib = 1, idx%nblenrim(igrd) 
     119         ii = idx%nbi(ib,igrd) 
     120         ij = idx%nbj(ib,igrd) 
     121         DO ik = 1, jpkm1 
     122            ! search the sense of the gradient 
     123            zcoef1 = bdytmask(ii-1,ij  ) +  bdytmask(ii+1,ij  ) 
     124            zcoef2 = bdytmask(ii  ,ij-1) +  bdytmask(ii  ,ij+1) 
     125            IF ( zcoef1+zcoef2 == 0) THEN 
     126               ! corner 
     127               zcoef = tmask(ii-1,ij,ik) + tmask(ii+1,ij,ik) +  tmask(ii,ij-1,ik) +  tmask(ii,ij+1,ik) 
     128               pta(ii,ij,ik) = pta(ii-1,ij  ,ik) * tmask(ii-1,ij  ,ik) + & 
     129                 &             pta(ii+1,ij  ,ik) * tmask(ii+1,ij  ,ik) + & 
     130                 &             pta(ii  ,ij-1,ik) * tmask(ii  ,ij-1,ik) + & 
     131                 &             pta(ii  ,ij+1,ik) * tmask(ii  ,ij+1,ik) 
     132               pta(ii,ij,ik) = ( pta(ii,ij,ik) / MAX( 1, zcoef) ) * tmask(ii,ij,ik) 
     133            ELSE 
     134               ip = bdytmask(ii+1,ij  ) - bdytmask(ii-1,ij  ) 
     135               jp = bdytmask(ii  ,ij+1) - bdytmask(ii  ,ij-1) 
     136               pta(ii,ij,ik) = pta(ii+ip,ij+jp,ik) * tmask(ii+ip,ij+jp,ik) 
     137            ENDIF 
     138         END DO 
     139      END DO 
     140      ! 
     141      IF( nn_timing == 1 ) CALL timing_stop('bdy_nmn') 
     142      ! 
     143   END SUBROUTINE bdy_nmn 
     144 
     145   SUBROUTINE bdy_orl( idx, ptb, pta, dta, ll_npo ) 
     146      !!---------------------------------------------------------------------- 
     147      !!                 ***  SUBROUTINE bdy_orl  *** 
     148      !! 
     149      !! ** Purpose : Apply Orlanski radiation for tracers at open boundaries. 
     150      !!              This is a wrapper routine for bdy_orlanski_3d below 
     151      !! 
     152      !!---------------------------------------------------------------------- 
     153      TYPE(OBC_INDEX),                     INTENT(in) ::   idx  ! OBC indices 
     154      REAL(wp), DIMENSION(:,:),            INTENT(in) ::   dta  ! OBC external data 
     155      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   ptb  ! before tracer field 
     156      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   pta  ! tracer trend 
     157      LOGICAL,                             INTENT(in) ::   ll_npo  ! switch for NPO version 
     158      !! 
     159      INTEGER  ::   igrd                                    ! grid index 
     160      !!---------------------------------------------------------------------- 
     161      ! 
     162      IF( nn_timing == 1 ) CALL timing_start('bdy_orl') 
     163      ! 
     164      igrd = 1                       ! Everything is at T-points here 
     165      ! 
     166      CALL bdy_orlanski_3d( idx, igrd, ptb(:,:,:), pta(:,:,:), dta, ll_npo ) 
     167      ! 
     168      IF( nn_timing == 1 ) CALL timing_stop('bdy_orl') 
     169      ! 
     170   END SUBROUTINE bdy_orl 
    36171 
    37172   SUBROUTINE bdy_orlanski_2d( idx, igrd, phib, phia, phi_ext, ll_npo ) 
     
    355490   END SUBROUTINE bdy_orlanski_3d 
    356491 
    357  
    358 #else 
    359    !!---------------------------------------------------------------------- 
    360    !!   Dummy module                   NO Unstruct Open Boundary Conditions 
    361    !!---------------------------------------------------------------------- 
    362 CONTAINS 
    363    SUBROUTINE bdy_orlanski_2d( idx, igrd, phib, phia, phi_ext  )      ! Empty routine 
    364       WRITE(*,*) 'bdy_orlanski_2d: You should not have seen this print! error?', kt 
    365    END SUBROUTINE bdy_orlanski_2d 
    366    SUBROUTINE bdy_orlanski_3d( idx, igrd, phib, phia, phi_ext  )      ! Empty routine 
    367       WRITE(*,*) 'bdy_orlanski_3d: You should not have seen this print! error?', kt 
    368    END SUBROUTINE bdy_orlanski_3d 
    369 #endif 
    370  
    371492   !!====================================================================== 
    372493END MODULE bdylib 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/BDY/bdytides.F90

    r6140 r7299  
    1111   !!            3.5  !  2013-07  (J. Chanut) Compliant with time splitting changes 
    1212   !!---------------------------------------------------------------------- 
    13 #if defined key_bdy 
    14    !!---------------------------------------------------------------------- 
    15    !!   'key_bdy'     Open Boundary Condition 
    16    !!---------------------------------------------------------------------- 
    1713   !!   bdytide_init  : read of namelist and initialisation of tidal harmonics data 
    1814   !!   tide_update   : calculation of tidal forcing at each timestep 
     
    2117   USE dom_oce        ! ocean space and time domain 
    2218   USE phycst         ! physical constants 
    23    USE bdy_par        ! Unstructured boundary parameters 
    2419   USE bdy_oce        ! ocean open boundary conditions 
    2520   USE tideini        !  
     
    598593  END SUBROUTINE tide_init_velocities 
    599594 
    600 #else 
    601    !!---------------------------------------------------------------------- 
    602    !!   Dummy module         NO Unstruct Open Boundary Conditions for tides 
    603    !!---------------------------------------------------------------------- 
    604 CONTAINS 
    605    SUBROUTINE bdytide_init             ! Empty routine 
    606       WRITE(*,*) 'bdytide_init: You should not have seen this print! error?' 
    607    END SUBROUTINE bdytide_init 
    608    SUBROUTINE bdytide_update( kt, jit )   ! Empty routine 
    609       WRITE(*,*) 'bdytide_update: You should not have seen this print! error?', kt, jit 
    610    END SUBROUTINE bdytide_update 
    611    SUBROUTINE bdy_dta_tides( kt, kit, time_offset )     ! Empty routine 
    612       INTEGER, INTENT( in )            ::   kt          ! Dummy argument empty routine       
    613       INTEGER, INTENT( in ),OPTIONAL   ::   kit         ! Dummy argument empty routine 
    614       INTEGER, INTENT( in ),OPTIONAL   ::   time_offset ! Dummy argument empty routine 
    615       WRITE(*,*) 'bdy_dta_tides: You should not have seen this print! error?', kt, jit 
    616    END SUBROUTINE bdy_dta_tides 
    617 #endif 
    618  
    619595   !!====================================================================== 
    620596END MODULE bdytides 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/BDY/bdytra.F90

    r6140 r7299  
    88   !!            3.4  !  2011     (D. Storkey) rewrite in preparation for OBC-BDY merge 
    99   !!            3.5  !  2012     (S. Mocavero, I. Epicoco) Optimization of BDY communications 
     10   !!            4.0  !  2016     (T. Lovato) Generalize OBC structure 
    1011   !!---------------------------------------------------------------------- 
    11 #if defined key_bdy 
    12    !!---------------------------------------------------------------------- 
    13    !!   'key_bdy'                     Unstructured Open Boundary Conditions 
    14    !!---------------------------------------------------------------------- 
    15    !!   bdy_tra            : Apply open boundary conditions to T and S 
    16    !!   bdy_tra_frs        : Apply Flow Relaxation Scheme 
     12   !!   bdy_tra       : Apply open boundary conditions & damping to T and S 
    1713   !!---------------------------------------------------------------------- 
    1814   USE oce            ! ocean dynamics and tracers variables 
     
    2016   USE bdy_oce        ! ocean open boundary conditions 
    2117   USE bdylib         ! for orlanski library routines 
    22    USE bdydta   , ONLY:   bf   !  
    2318   ! 
    2419   USE in_out_manager ! I/O manager 
     
    2924   PRIVATE 
    3025 
     26   ! Local structure to rearrange tracers data 
     27   TYPE, PUBLIC ::   ztrabdy 
     28      REAL(wp), POINTER, DIMENSION(:,:) ::  tra 
     29   END TYPE 
     30 
    3131   PUBLIC   bdy_tra      ! called in tranxt.F90  
    3232   PUBLIC   bdy_tra_dmp  ! called in step.F90  
    3333 
    3434   !!---------------------------------------------------------------------- 
    35    !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     35   !! NEMO/OPA 4.0, NEMO Consortium (2016) 
    3636   !! $Id$  
    3737   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     
    4848      INTEGER, INTENT(in) ::   kt   ! Main time step counter 
    4949      ! 
    50       INTEGER ::   ib_bdy   ! Loop index 
     50      INTEGER                        :: ib_bdy, jn   ! Loop indeces 
     51      TYPE(ztrabdy), DIMENSION(jpts) :: zdta         ! Temporary data structure 
    5152      !!---------------------------------------------------------------------- 
    5253 
    5354      DO ib_bdy=1, nb_bdy 
    5455         ! 
    55          SELECT CASE( cn_tra(ib_bdy) ) 
    56          CASE('none'        )   ;   CYCLE 
    57          CASE('frs'         )   ;   CALL bdy_tra_frs     ( idx_bdy(ib_bdy), dta_bdy(ib_bdy), kt ) 
    58          CASE('specified'   )   ;   CALL bdy_tra_spe     ( idx_bdy(ib_bdy), dta_bdy(ib_bdy), kt ) 
    59          CASE('neumann'     )   ;   CALL bdy_tra_nmn     ( idx_bdy(ib_bdy), dta_bdy(ib_bdy), kt ) 
    60          CASE('orlanski'    )   ;   CALL bdy_tra_orlanski( idx_bdy(ib_bdy), dta_bdy(ib_bdy), ll_npo=.false. ) 
    61          CASE('orlanski_npo')   ;   CALL bdy_tra_orlanski( idx_bdy(ib_bdy), dta_bdy(ib_bdy), ll_npo=.true. ) 
    62          CASE('runoff'      )   ;   CALL bdy_tra_rnf     ( idx_bdy(ib_bdy), dta_bdy(ib_bdy), kt ) 
    63          CASE DEFAULT           ;   CALL ctl_stop( 'bdy_tra : unrecognised option for open boundaries for T and S' ) 
    64          END SELECT 
    65          ! Boundary points should be updated 
    66          CALL lbc_bdy_lnk( tsa(:,:,:,jp_tem), 'T', 1., ib_bdy ) 
    67          CALL lbc_bdy_lnk( tsa(:,:,:,jp_sal), 'T', 1., ib_bdy ) 
     56         zdta(1)%tra => dta_bdy(ib_bdy)%tem 
     57         zdta(2)%tra => dta_bdy(ib_bdy)%sal 
     58         ! 
     59         DO jn = 1, jpts 
     60            ! 
     61            SELECT CASE( TRIM(cn_tra(ib_bdy)) ) 
     62            CASE('none'        )   ;   CYCLE 
     63            CASE('frs'         )   ;   CALL bdy_frs ( idx_bdy(ib_bdy),                tsa(:,:,:,jn), zdta(jn)%tra ) 
     64            CASE('specified'   )   ;   CALL bdy_spe ( idx_bdy(ib_bdy),                tsa(:,:,:,jn), zdta(jn)%tra ) 
     65            CASE('neumann'     )   ;   CALL bdy_nmn ( idx_bdy(ib_bdy),                tsa(:,:,:,jn)               ) 
     66            CASE('orlanski'    )   ;   CALL bdy_orl ( idx_bdy(ib_bdy), tsb(:,:,:,jn), tsa(:,:,:,jn), zdta(jn)%tra, ll_npo=.false. ) 
     67            CASE('orlanski_npo')   ;   CALL bdy_orl ( idx_bdy(ib_bdy), tsb(:,:,:,jn), tsa(:,:,:,jn), zdta(jn)%tra, ll_npo=.true. ) 
     68            CASE('runoff'      )   ;   CALL bdy_rnf ( idx_bdy(ib_bdy),                tsa(:,:,:,jn),               jn ) 
     69            CASE DEFAULT           ;   CALL ctl_stop( 'bdy_tra : unrecognised option for open boundaries for T and S' ) 
     70            END SELECT 
     71            ! Boundary points should be updated 
     72            CALL lbc_bdy_lnk( tsa(:,:,:,jn), 'T', 1., ib_bdy ) 
     73            !  
     74         END DO 
    6875      END DO 
    6976      ! 
    7077   END SUBROUTINE bdy_tra 
    7178 
    72  
    73    SUBROUTINE bdy_tra_frs( idx, dta, kt ) 
     79   SUBROUTINE bdy_rnf( idx, pta, jpa ) 
    7480      !!---------------------------------------------------------------------- 
    75       !!                 ***  SUBROUTINE bdy_tra_frs  *** 
     81      !!                 ***  SUBROUTINE bdy_rnf  *** 
    7682      !!                     
    77       !! ** Purpose : Apply the Flow Relaxation Scheme for tracers at open boundaries. 
    78       !!  
    79       !! Reference : Engedahl H., 1995, Tellus, 365-382. 
    80       !!---------------------------------------------------------------------- 
    81       INTEGER,         INTENT(in) ::   kt    ! 
    82       TYPE(OBC_INDEX), INTENT(in) ::   idx   ! OBC indices 
    83       TYPE(OBC_DATA),  INTENT(in) ::   dta   ! OBC external data 
    84       ! 
    85       REAL(wp) ::   zwgt           ! boundary weight 
    86       INTEGER  ::   ib, ik, igrd   ! dummy loop indices 
    87       INTEGER  ::   ii, ij         ! 2D addresses 
    88       !!---------------------------------------------------------------------- 
    89       ! 
    90       IF( nn_timing == 1 )   CALL timing_start('bdy_tra_frs') 
    91       ! 
    92       igrd = 1                       ! Everything is at T-points here 
    93       DO ib = 1, idx%nblen(igrd) 
    94          DO ik = 1, jpkm1 
    95             ii = idx%nbi(ib,igrd) 
    96             ij = idx%nbj(ib,igrd) 
    97             zwgt = idx%nbw(ib,igrd) 
    98             tsa(ii,ij,ik,jp_tem) = ( tsa(ii,ij,ik,jp_tem) + zwgt * ( dta%tem(ib,ik) - tsa(ii,ij,ik,jp_tem) ) ) * tmask(ii,ij,ik)          
    99             tsa(ii,ij,ik,jp_sal) = ( tsa(ii,ij,ik,jp_sal) + zwgt * ( dta%sal(ib,ik) - tsa(ii,ij,ik,jp_sal) ) ) * tmask(ii,ij,ik) 
    100          END DO 
    101       END DO  
    102       ! 
    103       IF( kt .eq. nit000 )   CLOSE( unit = 102 ) 
    104       ! 
    105       IF( nn_timing == 1 )   CALL timing_stop('bdy_tra_frs') 
    106       ! 
    107    END SUBROUTINE bdy_tra_frs 
    108  
    109  
    110    SUBROUTINE bdy_tra_spe( idx, dta, kt ) 
    111       !!---------------------------------------------------------------------- 
    112       !!                 ***  SUBROUTINE bdy_tra_frs  *** 
    113       !!                     
    114       !! ** Purpose : Apply a specified value for tracers at open boundaries. 
     83      !! ** Purpose : Specialized routine to apply TRA runoff values at OBs: 
     84      !!                  - duplicate the neighbour value for the temperature 
     85      !!                  - specified to 0.1 PSU for the salinity 
    11586      !!  
    11687      !!---------------------------------------------------------------------- 
    117       INTEGER,         INTENT(in) ::   kt    ! 
    118       TYPE(OBC_INDEX), INTENT(in) ::   idx   ! OBC indices 
    119       TYPE(OBC_DATA),  INTENT(in) ::   dta   ! OBC external data 
    120       ! 
    121       REAL(wp) ::   zwgt           ! boundary weight 
    122       INTEGER  ::   ib, ik, igrd   ! dummy loop indices 
    123       INTEGER  ::   ii, ij         ! 2D addresses 
    124       !!---------------------------------------------------------------------- 
    125       ! 
    126       IF( nn_timing == 1 ) CALL timing_start('bdy_tra_spe') 
    127       ! 
    128       igrd = 1                       ! Everything is at T-points here 
    129       DO ib = 1, idx%nblenrim(igrd) 
    130          ii = idx%nbi(ib,igrd) 
    131          ij = idx%nbj(ib,igrd) 
    132          DO ik = 1, jpkm1 
    133             tsa(ii,ij,ik,jp_tem) = dta%tem(ib,ik) * tmask(ii,ij,ik) 
    134             tsa(ii,ij,ik,jp_sal) = dta%sal(ib,ik) * tmask(ii,ij,ik) 
    135          END DO 
    136       END DO 
    137       ! 
    138       IF( kt == nit000 )   CLOSE( unit = 102 ) 
    139       ! 
    140       IF( nn_timing == 1 )   CALL timing_stop('bdy_tra_spe') 
    141       ! 
    142    END SUBROUTINE bdy_tra_spe 
    143  
    144  
    145    SUBROUTINE bdy_tra_nmn( idx, dta, kt ) 
    146       !!---------------------------------------------------------------------- 
    147       !!                 ***  SUBROUTINE bdy_tra_nmn  *** 
    148       !!                     
    149       !! ** Purpose : Duplicate the value for tracers at open boundaries. 
    150       !!  
    151       !!---------------------------------------------------------------------- 
    152       INTEGER,         INTENT(in) ::   kt    !  
    153       TYPE(OBC_INDEX), INTENT(in) ::   idx   ! OBC indices 
    154       TYPE(OBC_DATA) , INTENT(in) ::   dta   ! OBC external data 
    155       ! 
    156       REAL(wp) ::   zwgt           ! boundary weight 
    157       INTEGER  ::   ib, ik, igrd   ! dummy loop indices 
    158       INTEGER  ::   ii, ij,zcoef, zcoef1,zcoef2, ip, jp   ! 2D addresses 
    159       !!---------------------------------------------------------------------- 
    160       ! 
    161       IF( nn_timing == 1 )   CALL timing_start('bdy_tra_nmn') 
    162       ! 
    163       igrd = 1                       ! Everything is at T-points here 
    164       DO ib = 1, idx%nblenrim(igrd) 
    165          ii = idx%nbi(ib,igrd) 
    166          ij = idx%nbj(ib,igrd) 
    167          DO ik = 1, jpkm1 
    168             ! search the sense of the gradient 
    169             zcoef1 = bdytmask(ii-1,ij  ) +  bdytmask(ii+1,ij  ) 
    170             zcoef2 = bdytmask(ii  ,ij-1) +  bdytmask(ii  ,ij+1) 
    171             IF ( zcoef1+zcoef2 == 0) THEN 
    172                ! corner 
    173                zcoef = tmask(ii-1,ij,ik) + tmask(ii+1,ij,ik) +  tmask(ii,ij-1,ik) +  tmask(ii,ij+1,ik) 
    174                tsa(ii,ij,ik,jp_tem) = tsa(ii-1,ij  ,ik,jp_tem) * tmask(ii-1,ij  ,ik) + & 
    175                  &                    tsa(ii+1,ij  ,ik,jp_tem) * tmask(ii+1,ij  ,ik) + & 
    176                  &                    tsa(ii  ,ij-1,ik,jp_tem) * tmask(ii  ,ij-1,ik) + & 
    177                  &                    tsa(ii  ,ij+1,ik,jp_tem) * tmask(ii  ,ij+1,ik) 
    178                tsa(ii,ij,ik,jp_tem) = ( tsa(ii,ij,ik,jp_tem) / MAX( 1, zcoef) ) * tmask(ii,ij,ik) 
    179                tsa(ii,ij,ik,jp_sal) = tsa(ii-1,ij  ,ik,jp_sal) * tmask(ii-1,ij  ,ik) + & 
    180                  &                    tsa(ii+1,ij  ,ik,jp_sal) * tmask(ii+1,ij  ,ik) + & 
    181                  &                    tsa(ii  ,ij-1,ik,jp_sal) * tmask(ii  ,ij-1,ik) + & 
    182                  &                    tsa(ii  ,ij+1,ik,jp_sal) * tmask(ii  ,ij+1,ik) 
    183                tsa(ii,ij,ik,jp_sal) = ( tsa(ii,ij,ik,jp_sal) / MAX( 1, zcoef) ) * tmask(ii,ij,ik) 
    184             ELSE 
    185                ip = bdytmask(ii+1,ij  ) - bdytmask(ii-1,ij  ) 
    186                jp = bdytmask(ii  ,ij+1) - bdytmask(ii  ,ij-1) 
    187                tsa(ii,ij,ik,jp_tem) = tsa(ii+ip,ij+jp,ik,jp_tem) * tmask(ii+ip,ij+jp,ik) 
    188                tsa(ii,ij,ik,jp_sal) = tsa(ii+ip,ij+jp,ik,jp_sal) * tmask(ii+ip,ij+jp,ik) 
    189             ENDIF 
    190          END DO 
    191       END DO 
    192       ! 
    193       IF( kt == nit000 )   CLOSE( unit = 102 ) 
    194       ! 
    195       IF( nn_timing == 1 )   CALL timing_stop('bdy_tra_nmn') 
    196       ! 
    197    END SUBROUTINE bdy_tra_nmn 
    198   
    199  
    200    SUBROUTINE bdy_tra_orlanski( idx, dta, ll_npo ) 
    201       !!---------------------------------------------------------------------- 
    202       !!                 ***  SUBROUTINE bdy_tra_orlanski  *** 
    203       !!              
    204       !!              - Apply Orlanski radiation to temperature and salinity.  
    205       !!              - Wrapper routine for bdy_orlanski_3d 
    206       !!  
    207       !! 
    208       !! References:  Marchesiello, McWilliams and Shchepetkin, Ocean Modelling vol. 3 (2001)     
    209       !!---------------------------------------------------------------------- 
    210       TYPE(OBC_INDEX), INTENT(in) ::   idx     ! OBC indices 
    211       TYPE(OBC_DATA) , INTENT(in) ::   dta     ! OBC external data 
    212       LOGICAL        , INTENT(in) ::   ll_npo  ! switch for NPO version 
    213       ! 
    214       INTEGER  ::   igrd                                    ! grid index 
    215       !!---------------------------------------------------------------------- 
    216       ! 
    217       IF( nn_timing == 1 ) CALL timing_start('bdy_tra_orlanski') 
    218       ! 
    219       igrd = 1      ! Orlanski bc on temperature;  
    220       !             
    221       CALL bdy_orlanski_3d( idx, igrd, tsb(:,:,:,jp_tem), tsa(:,:,:,jp_tem), dta%tem, ll_npo ) 
    222  
    223       igrd = 1      ! Orlanski bc on salinity; 
    224       !   
    225       CALL bdy_orlanski_3d( idx, igrd, tsb(:,:,:,jp_sal), tsa(:,:,:,jp_sal), dta%sal, ll_npo ) 
    226       ! 
    227       IF( nn_timing == 1 )   CALL timing_stop('bdy_tra_orlanski') 
    228       ! 
    229    END SUBROUTINE bdy_tra_orlanski 
    230  
    231  
    232    SUBROUTINE bdy_tra_rnf( idx, dta, kt ) 
    233       !!---------------------------------------------------------------------- 
    234       !!                 ***  SUBROUTINE bdy_tra_rnf  *** 
    235       !!                     
    236       !! ** Purpose : Apply the runoff values for tracers at open boundaries: 
    237       !!                  - specified to 0.1 PSU for the salinity 
    238       !!                  - duplicate the value for the temperature 
    239       !!  
    240       !!---------------------------------------------------------------------- 
    241       INTEGER        , INTENT(in) ::   kt    !  
    242       TYPE(OBC_INDEX), INTENT(in) ::   idx   ! OBC indices 
    243       TYPE(OBC_DATA) , INTENT(in) ::   dta   ! OBC external data 
     88      TYPE(OBC_INDEX),                     INTENT(in) ::   idx  ! OBC indices 
     89      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   pta  ! tracer trend 
     90      INTEGER,                             INTENT(in) ::   jpa  ! TRA index 
    24491      ! 
    24592      REAL(wp) ::   zwgt           ! boundary weight 
     
    24895      !!---------------------------------------------------------------------- 
    24996      ! 
    250       IF( nn_timing == 1 )   CALL timing_start('bdy_tra_rnf') 
     97      IF( nn_timing == 1 )   CALL timing_start('bdy_rnf') 
    25198      ! 
    25299      igrd = 1                       ! Everything is at T-points here 
     
    257104            ip = bdytmask(ii+1,ij  ) - bdytmask(ii-1,ij  ) 
    258105            jp = bdytmask(ii  ,ij+1) - bdytmask(ii  ,ij-1) 
    259             tsa(ii,ij,ik,jp_tem) = tsa(ii+ip,ij+jp,ik,jp_tem) * tmask(ii,ij,ik) 
    260             tsa(ii,ij,ik,jp_sal) =                        0.1 * tmask(ii,ij,ik) 
     106            if (jpa == jp_tem) pta(ii,ij,ik) = pta(ii+ip,ij+jp,ik) * tmask(ii,ij,ik) 
     107            if (jpa == jp_sal) pta(ii,ij,ik) =                 0.1 * tmask(ii,ij,ik) 
    261108         END DO 
    262109      END DO 
    263110      ! 
    264       IF( kt == nit000 )   CLOSE( unit = 102 ) 
     111      IF( nn_timing == 1 )   CALL timing_stop('bdy_rnf') 
    265112      ! 
    266       IF( nn_timing == 1 )   CALL timing_stop('bdy_tra_rnf') 
    267       ! 
    268    END SUBROUTINE bdy_tra_rnf 
    269  
     113   END SUBROUTINE bdy_rnf 
    270114 
    271115   SUBROUTINE bdy_tra_dmp( kt ) 
     
    308152   END SUBROUTINE bdy_tra_dmp 
    309153  
    310 #else 
    311    !!---------------------------------------------------------------------- 
    312    !!   Dummy module                   NO Unstruct Open Boundary Conditions 
    313    !!---------------------------------------------------------------------- 
    314 CONTAINS 
    315    SUBROUTINE bdy_tra(kt)      ! Empty routine 
    316       WRITE(*,*) 'bdy_tra: You should not have seen this print! error?', kt 
    317    END SUBROUTINE bdy_tra 
    318  
    319    SUBROUTINE bdy_tra_dmp(kt)      ! Empty routine 
    320       WRITE(*,*) 'bdy_tra_dmp: You should not have seen this print! error?', kt 
    321    END SUBROUTINE bdy_tra_dmp 
    322 #endif 
    323  
    324154   !!====================================================================== 
    325155END MODULE bdytra 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/BDY/bdyvol.F90

    r6140 r7299  
    99   !!            3.0  !  2008-04  (NEMO team)  add in the reference version 
    1010   !!            3.4  !  2011     (D. Storkey) rewrite in preparation for OBC-BDY merge 
    11    !!---------------------------------------------------------------------- 
    12 #if defined key_bdy 
    13    !!---------------------------------------------------------------------- 
    14    !!   'key_bdy'                     unstructured open boundary conditions 
    1511   !!---------------------------------------------------------------------- 
    1612   USE oce            ! ocean dynamics and tracers  
     
    175171   END SUBROUTINE bdy_vol 
    176172 
    177 #else 
    178    !!---------------------------------------------------------------------- 
    179    !!   Dummy module                   NO Unstruct Open Boundary Conditions 
    180    !!---------------------------------------------------------------------- 
    181 CONTAINS 
    182    SUBROUTINE bdy_vol( kt )        ! Empty routine 
    183       WRITE(*,*) 'bdy_vol: You should not have seen this print! error?', kt 
    184    END SUBROUTINE bdy_vol 
    185 #endif 
    186  
    187173   !!====================================================================== 
    188174END MODULE bdyvol 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/DIA/diaharm.F90

    r6140 r7299  
    66   !! History :  3.1  !  2007  (O. Le Galloudec, J. Chanut)  Original code 
    77   !!---------------------------------------------------------------------- 
    8 #if defined key_diaharm && defined key_tide 
     8#if defined key_diaharm 
    99   !!---------------------------------------------------------------------- 
    1010   !!   'key_diaharm' 
    11    !!   'key_tide' 
    1211   !!---------------------------------------------------------------------- 
    1312   USE oce             ! ocean dynamics and tracers variables 
     
    1615   USE daymod 
    1716   USE tide_mod 
     17   USE sbctide         ! Tidal forcing or not 
    1818   ! 
    1919   USE in_out_manager  ! I/O units 
     
    8282         WRITE(numout,*) '~~~~~~~ ' 
    8383      ENDIF 
     84      ! 
     85      IF( .NOT. ln_tide )   CALL ctl_stop( 'dia_harm_init : ln_tide must be true for harmonic analysis') 
    8486      ! 
    8587      CALL tide_init_Wave 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/DIA/diahsb.F90

    r7298 r7299  
    2323   USE trabbc          ! bottom boundary condition  
    2424   USE trabbc          ! bottom boundary condition 
    25    USE bdy_par         ! (for lk_bdy) 
    2625   USE restart         ! ocean restart 
     26   USE bdy_oce   , ONLY: ln_bdy 
    2727   ! 
    2828   USE iom             ! I/O manager 
     
    395395      surf_tot  = glob_sum( surf(:,:) )                                       ! total ocean surface area 
    396396 
    397       IF( lk_bdy ) CALL ctl_warn( 'dia_hsb does not take open boundary fluxes into account' )          
     397      IF( ln_bdy ) CALL ctl_warn( 'dia_hsb does not take open boundary fluxes into account' )          
    398398      ! 
    399399      ! ---------------------------------- ! 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/DOM/dommsk.F90

    r6140 r7299  
    8888      !!      are defined with the proper value at lateral domain boundaries. 
    8989      !! 
    90       !!      In case of open boundaries (lk_bdy=T): 
     90      !!      In case of open boundaries (ln_bdy=T): 
    9191      !!        - tmask is set to 1 on the points to be computed bay the open 
    9292      !!          boundaries routines. 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/DYN/dynnxt.F90

    r6140 r7299  
    3232   USE dynspg_ts      ! surface pressure gradient: split-explicit scheme 
    3333   USE domvvl         ! variable volume 
    34    USE bdy_oce        ! ocean open boundary conditions 
     34   USE bdy_oce   , ONLY: ln_bdy 
    3535   USE bdydta         ! ocean open boundary conditions 
    3636   USE bdydyn         ! ocean open boundary conditions 
     
    7777      !!              * Apply lateral boundary conditions on after velocity  
    7878      !!             at the local domain boundaries through lbc_lnk call, 
    79       !!             at the one-way open boundaries (lk_bdy=T), 
     79      !!             at the one-way open boundaries (ln_bdy=T), 
    8080      !!             at the AGRIF zoom   boundaries (lk_agrif=T) 
    8181      !! 
     
    147147      CALL lbc_lnk( va, 'V', -1. )  
    148148      ! 
    149 # if defined key_bdy 
    150149      !                                !* BDY open boundaries 
    151       IF( lk_bdy .AND. ln_dynspg_exp )   CALL bdy_dyn( kt ) 
    152       IF( lk_bdy .AND. ln_dynspg_ts  )   CALL bdy_dyn( kt, dyn3d_only=.true. ) 
     150      IF( ln_bdy .AND. ln_dynspg_exp )   CALL bdy_dyn( kt ) 
     151      IF( ln_bdy .AND. ln_dynspg_ts  )   CALL bdy_dyn( kt, dyn3d_only=.true. ) 
    153152 
    154153!!$   Do we need a call to bdy_vol here?? 
    155       ! 
    156 # endif 
    157154      ! 
    158155      IF( l_trddyn ) THEN             ! prepare the atf trend computation + some diagnostics 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg.F90

    r6981 r7299  
    8888      ! 
    8989      IF(      ln_apr_dyn                                                &   ! atmos. pressure 
    90          .OR.  ( .NOT.ln_dynspg_ts .AND. (ln_tide_pot .AND. lk_tide) )   &   ! tide potential (no time slitting) 
     90         .OR.  ( .NOT.ln_dynspg_ts .AND. (ln_tide_pot .AND. ln_tide) )   &   ! tide potential (no time slitting) 
    9191         .OR.  nn_ice_embd == 2  ) THEN                                      ! embedded sea-ice 
    9292         ! 
     
    111111         ! 
    112112         !                                    !==  tide potential forcing term  ==! 
    113          IF( .NOT.ln_dynspg_ts .AND. ( ln_tide_pot .AND. lk_tide )  ) THEN   ! N.B. added directly at sub-time-step in ts-case 
     113         IF( .NOT.ln_dynspg_ts .AND. ( ln_tide_pot .AND. ln_tide )  ) THEN   ! N.B. added directly at sub-time-step in ts-case 
    114114            ! 
    115115            CALL upd_tide( kt )                      ! update tide potential 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg_ts.F90

    r6152 r7299  
    3333   USE dynvor          ! vorticity term 
    3434   USE wet_dry         ! wetting/drying flux limter 
    35    USE bdy_par         ! for lk_bdy 
     35   USE bdy_oce   , ONLY: ln_bdy 
    3636   USE bdytides        ! open boundary condition data 
    3737   USE bdydyn2d        ! open boundary conditions on barotropic variables 
     
    607607         !                                                !  ------------------ 
    608608         ! Update only tidal forcing at open boundaries 
    609 #if defined key_tide 
    610          IF( lk_bdy      .AND. lk_tide )   CALL bdy_dta_tides( kt, kit=jn, time_offset= noffset+1 ) 
    611          IF( ln_tide_pot .AND. lk_tide )   CALL upd_tide     ( kt, kit=jn, time_offset= noffset   ) 
    612 #endif 
     609         IF( ln_bdy      .AND. ln_tide )   CALL bdy_dta_tides( kt, kit=jn, time_offset= noffset+1 ) 
     610         IF( ln_tide_pot .AND. ln_tide )   CALL upd_tide     ( kt, kit=jn, time_offset= noffset   ) 
    613611         ! 
    614612         ! Set extrapolation coefficients for predictor step: 
     
    705703         CALL lbc_lnk( ssha_e, 'T',  1._wp ) 
    706704 
    707 #if defined key_bdy 
    708705         ! Duplicate sea level across open boundaries (this is only cosmetic if linssh=T) 
    709          IF( lk_bdy )   CALL bdy_ssh( ssha_e ) 
    710 #endif 
     706         IF( ln_bdy )   CALL bdy_ssh( ssha_e ) 
     707 
    711708#if defined key_agrif 
    712709         IF( .NOT.Agrif_Root() )   CALL agrif_ssh_ts( jn ) 
     
    861858         ! 
    862859         ! Add tidal astronomical forcing if defined 
    863          IF ( lk_tide.AND.ln_tide_pot ) THEN 
     860         IF ( ln_tide.AND.ln_tide_pot ) THEN 
    864861            DO jj = 2, jpjm1 
    865862               DO ji = fs_2, fs_jpim1   ! vector opt. 
     
    967964         CALL lbc_lnk_multi( ua_e, 'U', -1._wp, va_e , 'V', -1._wp ) 
    968965         ! 
    969 #if defined key_bdy   
    970966         !                                                 ! open boundaries 
    971          IF( lk_bdy )   CALL bdy_dyn2d( jn, ua_e, va_e, un_e, vn_e, hur_e, hvr_e, ssha_e ) 
    972 #endif 
     967         IF( ln_bdy )   CALL bdy_dyn2d( jn, ua_e, va_e, un_e, vn_e, hur_e, hvr_e, ssha_e ) 
     968 
    973969#if defined key_agrif                                                            
    974970         IF( .NOT.Agrif_Root() )  CALL agrif_dyn_ts( jn )  ! Agrif 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/DYN/sshwzv.F90

    r6152 r7299  
    2222   USE divhor         ! horizontal divergence 
    2323   USE phycst         ! physical constants 
    24    USE bdy_oce        !  
    25    USE bdy_par        ! 
     24   USE bdy_oce   , ONLY: ln_bdy, bdytmask 
    2625   USE bdydyn2d       ! bdy_ssh routine 
    2726#if defined key_agrif 
     
    116115         CALL agrif_ssh( kt ) 
    117116# endif 
    118 # if defined key_bdy 
    119          IF( lk_bdy ) THEN 
     117         IF( ln_bdy ) THEN 
    120118            CALL lbc_lnk( ssha, 'T', 1. )    ! Not sure that's necessary 
    121119            CALL bdy_ssh( ssha )             ! Duplicate sea level across open boundaries 
    122120         ENDIF 
    123 # endif 
    124121      ENDIF 
    125122 
     
    211208      ENDIF 
    212209 
    213 #if defined key_bdy 
    214       IF( lk_bdy ) THEN 
     210      IF( ln_bdy ) THEN 
    215211         DO jk = 1, jpkm1 
    216212            wn(:,:,jk) = wn(:,:,jk) * bdytmask(:,:) 
    217213         END DO 
    218214      ENDIF 
    219 #endif 
    220215      ! 
    221216      IF( nn_timing == 1 )  CALL timing_stop('wzv') 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/SBC/fldread.F90

    r6140 r7299  
    666666      !!                using a general mapping (for open boundaries) 
    667667      !!---------------------------------------------------------------------- 
    668 #if defined key_bdy 
    669       USE bdy_oce, ONLY:  dta_global, dta_global2         ! workspace to read in global data arrays 
    670 #endif  
     668      USE bdy_oce, ONLY: ln_bdy, dta_global, dta_global2         ! workspace to read in global data arrays 
     669 
    671670      INTEGER                   , INTENT(in ) ::   num     ! stream number 
    672671      CHARACTER(LEN=*)          , INTENT(in ) ::   clvar   ! variable name 
     
    692691      ilendta = iom_file(num)%dimsz(1,idvar) 
    693692 
    694 #if defined key_bdy 
    695       ipj = iom_file(num)%dimsz(2,idvar) 
    696       IF( map%ll_unstruc) THEN   ! unstructured open boundary data file 
    697          dta_read => dta_global 
    698       ELSE                       ! structured open boundary data file 
    699          dta_read => dta_global2 
    700       ENDIF 
    701 #endif 
     693      IF ( ln_bdy ) THEN 
     694         ipj = iom_file(num)%dimsz(2,idvar) 
     695         IF( map%ll_unstruc) THEN   ! unstructured open boundary data file 
     696            dta_read => dta_global 
     697         ELSE                       ! structured open boundary data file 
     698            dta_read => dta_global2 
     699         ENDIF 
     700      ENDIF 
    702701 
    703702      IF(lwp) WRITE(numout,*) 'Dim size for ',        TRIM(clvar),' is ', ilendta 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim.F90

    r6416 r7299  
    6262   USE timing          ! Timing 
    6363 
    64 #if defined key_bdy  
    65    USE bdyice_lim       ! unstructured open boundary data  (bdy_ice_lim routine) 
    66 #endif 
     64   USE bdy_oce   , ONLY: ln_bdy 
     65   USE bdyice_lim      ! unstructured open boundary data  (bdy_ice_lim routine) 
    6766 
    6867   IMPLICIT NONE 
     
    166165            IF( nn_monocat /= 2 ) CALL lim_itd_me ! Mechanical redistribution ! (ridging/rafting) 
    167166            ! 
    168 #if defined key_bdy 
    169             CALL bdy_ice_lim( kt )                ! bdy ice thermo  
    170             IF( ln_icectl )       CALL lim_prt( kt, iiceprt, jiceprt, 1, ' - ice thermo bdy - ' ) 
    171 #endif 
     167            IF( ln_bdy )  CALL bdy_ice_lim( kt )                ! bdy ice thermo  
     168            IF( ln_bdy .AND. ln_icectl )  CALL lim_prt( kt, iiceprt, jiceprt, 1, ' - ice thermo bdy - ' ) 
    172169            ! 
    173170            CALL lim_update1( kt )                ! Corrections 
     
    380377      r1_nlay_s = 1._wp / REAL( nlay_s, wp ) 
    381378      ! 
    382 #if defined key_bdy 
    383       IF( lwp .AND. ln_limdiahsb )  CALL ctl_warn('online conservation check activated but it does not work with BDY') 
    384 #endif 
     379      IF( lwp .AND. ln_bdy .AND. ln_limdiahsb )  & 
     380      &   CALL ctl_warn('online conservation check activated but it does not work with BDY') 
    385381      ! 
    386382   END SUBROUTINE ice_run 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim_2.F90

    r6140 r7299  
    5454# endif 
    5555 
    56 #if defined key_bdy  
     56   USE bdy_oce   , ONLY: ln_bdy 
    5757   USE bdyice_lim       ! unstructured open boundary data  (bdy_ice_lim routine) 
    58 #endif 
    5958 
    6059   IMPLICIT NONE 
     
    230229                           CALL lim_trp_2      ( kt )      ! Ice transport   ( Advection/diffusion ) 
    231230           IF( ln_limdmp ) CALL lim_dmp_2      ( kt )      ! Ice damping  
    232 #if defined key_bdy 
    233                            CALL bdy_ice_lim( kt ) ! bdy ice thermo 
    234 #endif 
     231           IF( ln_bdy    ) CALL bdy_ice_lim( kt ) ! bdy ice thermo 
    235232         END IF 
    236233         !                                             ! Ice surface fluxes in coupled mode  
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r6460 r7299  
    4747   USE traqsr         ! active tracers: light penetration 
    4848   USE sbcwave        ! Wave module 
    49    USE bdy_par        ! Require lk_bdy 
     49   USE bdy_oce   , ONLY: ln_bdy 
    5050   ! 
    5151   USE prtctl         ! Print control                    (prt_ctl routine) 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/SBC/sbctide.F90

    r6140 r7299  
    2222   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:) ::   pot_astro   ! 
    2323 
    24 #if defined key_tide 
    2524   !!---------------------------------------------------------------------- 
    26    !!   'key_tide' :                                        tidal potential 
     25   !!   tidal potential 
    2726   !!---------------------------------------------------------------------- 
    2827   !!   sbc_tide            :  
     
    3029   !!---------------------------------------------------------------------- 
    3130 
    32    LOGICAL, PUBLIC, PARAMETER ::   lk_tide  = .TRUE. 
    3331   REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   amp_pot, phi_pot 
    3432 
     
    125123   END SUBROUTINE tide_init_potential 
    126124 
    127 #else 
    128   !!---------------------------------------------------------------------- 
    129   !!   Default case :   Empty module 
    130   !!---------------------------------------------------------------------- 
    131   LOGICAL, PUBLIC, PARAMETER ::   lk_tide = .FALSE. 
    132 CONTAINS 
    133   SUBROUTINE sbc_tide( kt )      ! Empty routine 
    134     INTEGER         , INTENT(in) ::   kt         ! ocean time-step 
    135     WRITE(*,*) 'sbc_tide: You should not have seen this print! error?', kt 
    136   END SUBROUTINE sbc_tide 
    137 #endif 
    138  
    139125  !!====================================================================== 
    140126END MODULE sbctide 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/SBC/sbcwave.F90

    r6140 r7299  
    1212   !!---------------------------------------------------------------------- 
    1313   USE oce            !  
    14    USE sbc_oce        ! Surface boundary condition: ocean fields 
    15    USE bdy_oce        ! 
     14   USE sbc_oce        ! Surface boundary condition: ocean fields 
     15   USE bdy_oce   , ONLY: ln_bdy, bdytmask 
    1616   USE domvvl         ! 
    1717   ! 
     
    1919   USE in_out_manager ! I/O manager 
    2020   USE lib_mpp        ! distribued memory computing library 
    21    USE fldread        ! read input fields 
     21   USE fldread        ! read input fields 
    2222   USE wrk_nemo       ! 
    2323 
     
    3232   INTEGER , PARAMETER ::   jp_wn  = 3   ! index of wave number                 (1/m)    at T-point 
    3333 
    34    TYPE(FLD), ALLOCATABLE, DIMENSION(:)  :: sf_cd    ! structure of input fields (file informations, fields read) Drag Coefficient 
    35    TYPE(FLD), ALLOCATABLE, DIMENSION(:)  :: sf_sd    ! structure of input fields (file informations, fields read) Stokes Drift 
     34   TYPE(FLD), ALLOCATABLE, DIMENSION(:)  :: sf_cd         ! structure of input fields (file informations, fields read) Drag Coefficient 
     35   TYPE(FLD), ALLOCATABLE, DIMENSION(:)  :: sf_sd         ! structure of input fields (file informations, fields read) Stokes Drift 
    3636 
    3737   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION (:,:)   :: cdn_wave  
     
    172172            wsd3d(:,:,jk) = wsd3d(:,:,jk+1) - ze3hdiv(:,:,jk) 
    173173         END DO 
    174 #if defined key_bdy 
    175          IF( lk_bdy ) THEN 
     174         ! 
     175         IF( ln_bdy ) THEN 
    176176            DO jk = 1, jpkm1 
    177177               wsd3d(:,:,jk) = wsd3d(:,:,jk) * bdytmask(:,:) 
    178178            END DO 
    179179         ENDIF 
    180 #endif 
     180         ! 
    181181         CALL wrk_dealloc( jpi,jpj,jpk,   zusd_t, zvsd_t, ze3hdiv ) 
    182182         !  
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/SBC/tideini.F90

    r6140 r7299  
    2525   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   ftide        !: 
    2626 
     27   LOGICAL , PUBLIC ::   ln_tide         !: 
    2728   LOGICAL , PUBLIC ::   ln_tide_pot     !: 
    2829   LOGICAL , PUBLIC ::   ln_tide_ramp    !: 
     
    4849      INTEGER  ::   ios                 ! Local integer output status for namelist read 
    4950      ! 
    50       NAMELIST/nam_tide/ln_tide_pot, ln_tide_ramp, rdttideramp, clname 
     51      NAMELIST/nam_tide/ln_tide, ln_tide_pot, ln_tide_ramp, rdttideramp, clname 
    5152      !!---------------------------------------------------------------------- 
    52       ! 
    53       IF(lwp) THEN 
    54          WRITE(numout,*) 
    55          WRITE(numout,*) 'tide_init : Initialization of the tidal components' 
    56          WRITE(numout,*) '~~~~~~~~~ ' 
    57       ENDIF 
    58       ! 
    59       CALL tide_init_Wave 
    6053      ! 
    6154      ! Read Namelist nam_tide 
     
    6962      IF(lwm) WRITE ( numond, nam_tide ) 
    7063      ! 
     64      IF (ln_tide) THEN 
     65         IF (lwp) THEN 
     66            WRITE(numout,*) 
     67            WRITE(numout,*) 'tide_init : Initialization of the tidal components' 
     68            WRITE(numout,*) '~~~~~~~~~ ' 
     69            WRITE(numout,*) '   Namelist nam_tide' 
     70            WRITE(numout,*) '              Use tidal components : ln_tide      = ', ln_tide 
     71            WRITE(numout,*) '      Apply astronomical potential : ln_tide_pot  = ', ln_tide_pot 
     72            WRITE(numout,*) '                                     nb_harmo     = ', nb_harmo 
     73            WRITE(numout,*) '                                     ln_tide_ramp = ', ln_tide_ramp 
     74            WRITE(numout,*) '                                     rdttideramp  = ', rdttideramp 
     75         ENDIF 
     76      ELSE 
     77         IF(lwp) WRITE(numout,*) 
     78         IF(lwp) WRITE(numout,*) 'tide_init : tidal components not used (ln_tide = F)' 
     79         IF(lwp) WRITE(numout,*) '~~~~~~~~~ ' 
     80         RETURN 
     81      ENDIF 
     82      ! 
     83      CALL tide_init_Wave 
     84      ! 
    7185      nb_harmo=0 
    7286      DO jk = 1, jpmax_harmo 
     
    7993      IF( nb_harmo == 0 )   CALL ctl_stop( 'tide_init : No tidal components set in nam_tide' ) 
    8094      ! 
    81       IF(lwp) THEN 
    82          WRITE(numout,*) '   Namelist nam_tide' 
    83          WRITE(numout,*) '      Apply astronomical potential : ln_tide_pot  =', ln_tide_pot 
    84          WRITE(numout,*) '                                     nb_harmo     = ', nb_harmo 
    85          WRITE(numout,*) '                                     ln_tide_ramp = ', ln_tide_ramp  
    86          WRITE(numout,*) '                                     rdttideramp  = ', rdttideramp 
    87       ENDIF 
    8895      IF( ln_tide_ramp.AND.((nitend-nit000+1)*rdt/rday < rdttideramp) )   & 
    8996         &   CALL ctl_stop('rdttideramp must be lower than run duration') 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/SBC/updtide.F90

    r5913 r7299  
    55   !!====================================================================== 
    66   !! History :  9.0  !  07  (O. Le Galloudec)  Original code 
    7    !!---------------------------------------------------------------------- 
    8 #if defined key_tide 
    9    !!---------------------------------------------------------------------- 
    10    !!   'key_tide' :                                        tidal potential 
    117   !!---------------------------------------------------------------------- 
    128   !!   upd_tide       : update tidal potential 
     
    8177   END SUBROUTINE upd_tide 
    8278 
    83 #else 
    84   !!---------------------------------------------------------------------- 
    85   !!   Dummy module :                                        NO TIDE 
    86   !!---------------------------------------------------------------------- 
    87 CONTAINS 
    88   SUBROUTINE upd_tide( kt, kit, time_offset )  ! Empty routine 
    89     INTEGER, INTENT(in)           ::   kt      !  integer  arg, dummy routine 
    90     INTEGER, INTENT(in), OPTIONAL ::   kit     !  optional arg, dummy routine 
    91     INTEGER, INTENT(in), OPTIONAL ::   time_offset !  optional arg, dummy routine 
    92     WRITE(*,*) 'upd_tide: You should not have seen this print! error?', kt 
    93   END SUBROUTINE upd_tide 
    94  
    95 #endif 
    96  
    9779  !!====================================================================== 
    9880 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/TRA/tranxt.F90

    r6140 r7299  
    3737   USE ldftra          ! lateral physics on tracers 
    3838   USE ldfslp 
    39    USE bdy_oce         ! BDY open boundary condition variables 
     39   USE bdy_oce   , ONLY: ln_bdy 
    4040   USE bdytra          ! open boundary condition (bdy_tra routine) 
    4141   ! 
     
    7979      !!              - Apply lateral boundary conditions on (ta,sa)  
    8080      !!             at the local domain   boundaries through lbc_lnk call,  
    81       !!             at the one-way open boundaries (lk_bdy=T),  
     81      !!             at the one-way open boundaries (ln_bdy=T),  
    8282      !!             at the AGRIF zoom   boundaries (lk_agrif=T) 
    8383      !! 
     
    111111      CALL lbc_lnk( tsa(:,:,:,jp_sal), 'T', 1._wp ) 
    112112      ! 
    113 #if defined key_bdy  
    114       IF( lk_bdy )   CALL bdy_tra( kt )  ! BDY open boundaries 
    115 #endif 
     113      IF( ln_bdy )   CALL bdy_tra( kt )  ! BDY open boundaries 
    116114  
    117115      ! set time step size (Euler/Leapfrog) 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfric.F90

    r7048 r7299  
    205205         DO jj = 2, jpjm1 
    206206            DO ji = fs_2, fs_jpim1 
    207                IF( fsdept(ji,jj,jk) < ekm_dep(ji,jj) ) THEN 
     207               IF( gdept_n(ji,jj,jk) < ekm_dep(ji,jj) ) THEN 
    208208                  avmv(ji,jj,jk) = MAX( avmv(ji,jj,jk), rn_wvmix ) 
    209209                  avmu(ji,jj,jk) = MAX( avmu(ji,jj,jk), rn_wvmix ) 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r6152 r7299  
    5252#endif 
    5353   USE tideini        ! tidal components initialization   (tide_ini routine) 
     54   USE bdy_oce,   ONLY: ln_bdy 
    5455   USE bdyini         ! open boundary cond. setting       (bdy_init routine) 
    55    USE bdydta         ! open boundary cond. setting   (bdy_dta_init routine) 
    56    USE bdytides       ! open boundary cond. setting   (bdytide_init routine) 
    57    USE sbctide, ONLY  : lk_tide 
    5856   USE istate         ! initial state setting          (istate_init routine) 
    5957   USE ldfdyn         ! lateral viscosity setting      (ldfdyn_init routine) 
     
    433431      !                                      ! external forcing  
    434432!!gm to be added : creation and call of sbc_apr_init 
    435       IF( lk_tide       )   CALL    tide_init   ! tidal harmonics 
     433                            CALL    tide_init   ! tidal harmonics 
    436434                            CALL     sbc_init   ! surface boundary conditions (including sea-ice) 
    437 !!gm ==>> bdy_init should call bdy_dta_init and bdytide_init  NOT in nemogcm !!! 
    438       IF( lk_bdy        )   CALL     bdy_init   ! Open boundaries initialisation 
    439       IF( lk_bdy        )   CALL bdy_dta_init   ! Open boundaries initialisation of external data arrays 
    440       IF( lk_bdy .AND. lk_tide )   & 
    441          &                  CALL bdytide_init   ! Open boundaries initialisation of tidal harmonic forcing 
    442           
     435                            CALL     bdy_init   ! Open boundaries initialisation 
    443436      !                                      ! Ocean physics 
    444437      !                                         ! Vertical physics 
     
    659652      USE diadct    , ONLY: diadct_alloc  
    660653#endif  
    661 #if defined key_bdy 
    662654      USE bdy_oce   , ONLY: bdy_oce_alloc 
    663 #endif 
    664655      ! 
    665656      INTEGER :: ierr 
     
    676667      ierr = ierr + diadct_alloc    ()          !  
    677668#endif  
    678 #if defined key_bdy 
    679669      ierr = ierr + bdy_oce_alloc   ()          ! bdy masks (incl. initialization) 
    680 #endif 
    681670      ! 
    682671      IF( lk_mpp    )   CALL mpp_sum( ierr ) 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/step.F90

    r6464 r7299  
    104104      ! Update external forcing (tides, open boundaries, and surface boundary condition (including sea-ice) 
    105105      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    106       IF( lk_tide    )   CALL sbc_tide( kstp )                   ! update tide potential 
     106      IF( ln_tide    )   CALL sbc_tide( kstp )                   ! update tide potential 
    107107      IF( ln_apr_dyn )   CALL sbc_apr ( kstp )                   ! atmospheric pressure (NB: call before bdy_dta which needs ssh_ib)  
    108       IF( lk_bdy     )   CALL bdy_dta ( kstp, time_offset=+1 )   ! update dynamic & tracer data at open boundaries 
     108      IF( ln_bdy     )   CALL bdy_dta ( kstp, time_offset=+1 )   ! update dynamic & tracer data at open boundaries 
    109109                         CALL sbc     ( kstp )                   ! Sea Boundary Condition (including sea-ice) 
    110110 
     
    200200      IF(  lk_asminc .AND. ln_asmiau .AND. ln_dyninc )   & 
    201201               &         CALL dyn_asm_inc   ( kstp )  ! apply dynamics assimilation increment 
    202       IF( lk_bdy     )   CALL bdy_dyn3d_dmp ( kstp )  ! bdy damping trends 
     202      IF( ln_bdy     )   CALL bdy_dyn3d_dmp ( kstp )  ! bdy damping trends 
    203203#if defined key_agrif 
    204204      IF(.NOT. Agrif_Root())  &  
     
    259259      IF( lk_trabbl  )   CALL tra_bbl       ( kstp )  ! advective (and/or diffusive) bottom boundary layer scheme 
    260260      IF( ln_tradmp  )   CALL tra_dmp       ( kstp )  ! internal damping trends 
    261       IF( lk_bdy     )   CALL bdy_tra_dmp   ( kstp )  ! bdy damping trends 
     261      IF( ln_bdy     )   CALL bdy_tra_dmp   ( kstp )  ! bdy damping trends 
    262262#if defined key_agrif 
    263263      IF(.NOT. Agrif_Root())  &  
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/step_oce.F90

    r6140 r7299  
    4747   USE stopts  
    4848 
    49    USE bdy_par          ! for lk_bdy 
    50    USE bdy_oce          ! for dmp logical 
     49   USE bdy_oce    , ONLY: ln_bdy 
    5150   USE bdydta           ! open boundary condition data     (bdy_dta routine) 
    5251   USE bdytra           ! bdy cond. for tracers            (bdy_tra routine) 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/SAS_SRC/nemogcm.F90

    r6165 r7299  
    5959   USE lbcnfd, ONLY: isendto, nsndto, nfsloop, nfeloop ! Setup of north fold exchanges 
    6060   USE icbstp          ! handle bergs, calving, themodynamics and transport 
    61 #if defined key_bdy 
    6261   USE bdyini          ! open boundary cond. setting       (bdy_init routine). clem: mandatory for LIM3 
    63    USE bdydta          ! open boundary cond. setting   (bdy_dta_init routine). clem: mandatory for LIM3 
    64 #endif 
    65    USE bdy_par 
    6662 
    6763   IMPLICIT NONE 
     
    363359      !           the environment of ocean BDY. Therefore bdy is called in both OPA and SAS modules.  
    364360      !           This is not clean and should be changed in the future.  
    365       IF( lk_bdy        )   CALL     bdy_init 
    366       IF( lk_bdy        )   CALL bdy_dta_init 
     361                            CALL     bdy_init 
    367362      ! ==> 
    368363       
     
    514509      USE diawri    , ONLY: dia_wri_alloc 
    515510      USE dom_oce   , ONLY: dom_oce_alloc 
    516 #if defined key_bdy    
    517       USE bdy_oce   , ONLY: bdy_oce_alloc 
     511      USE bdy_oce   , ONLY: ln_bdy, bdy_oce_alloc 
    518512      USE oce         ! clem: mandatory for LIM3 because needed for bdy arrays 
    519 #else 
    520       USE oce       , ONLY : sshn, sshb, snwice_mass, snwice_mass_b, snwice_fmass 
    521 #endif 
    522513      ! 
    523514      INTEGER :: ierr,ierr1,ierr2,ierr3,ierr4,ierr5,ierr6,ierr7,ierr8 
     
    527518      ierr =        dia_wri_alloc   () 
    528519      ierr = ierr + dom_oce_alloc   ()          ! ocean domain 
    529 #if defined key_bdy 
    530520      ierr = ierr + bdy_oce_alloc   ()          ! bdy masks (incl. initialization) 
    531       ierr = ierr + oce_alloc       ()          ! (tsn...) 
    532 #endif 
    533  
    534 #if ! defined key_bdy 
    535        ALLOCATE( snwice_mass(jpi,jpj)  , snwice_mass_b(jpi,jpj),             & 
    536          &      snwice_fmass(jpi,jpj)  , STAT= ierr1 ) 
    537       ! 
    538       ! lim code currently uses surface temperature and salinity in tsn array for initialisation 
    539       ! and ub, vb arrays in ice dynamics, so allocate enough of arrays to use 
    540       ! clem: should not be needed. To be checked out 
    541       jpm = MAX(jp_tem, jp_sal) 
    542       ALLOCATE( tsn(jpi,jpj,1,jpm)  , STAT=ierr2 ) 
    543       ALLOCATE( ub(jpi,jpj,1)       , STAT=ierr3 ) 
    544       ALLOCATE( vb(jpi,jpj,1)       , STAT=ierr4 ) 
    545       ALLOCATE( tsb(jpi,jpj,1,jpm)  , STAT=ierr5 ) 
    546       ALLOCATE( sshn(jpi,jpj)       , STAT=ierr6 ) 
    547       ALLOCATE( un(jpi,jpj,1)       , STAT=ierr7 ) 
    548       ALLOCATE( vn(jpi,jpj,1)       , STAT=ierr8 ) 
    549       ierr = ierr + ierr1 + ierr2 + ierr3 + ierr4 + ierr5 + ierr6 + ierr7 + ierr8 
     521# if ! defined key_lim2 && ! defined key_lim3 
     522         ierr = ierr + oce_alloc       ()          ! (tsn...) 
     523# else 
     524         ALLOCATE( snwice_mass(jpi,jpj)  , snwice_mass_b(jpi,jpj),             & 
     525            &      snwice_fmass(jpi,jpj)  , STAT= ierr1 ) 
     526         ! 
     527         ! lim code currently uses surface temperature and salinity in tsn array for initialisation 
     528         ! and ub, vb arrays in ice dynamics, so allocate enough of arrays to use 
     529         ! clem: should not be needed. To be checked out 
     530         jpm = MAX(jp_tem, jp_sal) 
     531         ALLOCATE( tsn(jpi,jpj,1,jpm)  , STAT=ierr2 ) 
     532         ALLOCATE( ub(jpi,jpj,1)       , STAT=ierr3 ) 
     533         ALLOCATE( vb(jpi,jpj,1)       , STAT=ierr4 ) 
     534         ALLOCATE( tsb(jpi,jpj,1,jpm)  , STAT=ierr5 ) 
     535         ALLOCATE( sshn(jpi,jpj)       , STAT=ierr6 ) 
     536         ALLOCATE( un(jpi,jpj,1)       , STAT=ierr7 ) 
     537         ALLOCATE( vn(jpi,jpj,1)       , STAT=ierr8 ) 
     538         ierr = ierr + ierr1 + ierr2 + ierr3 + ierr4 + ierr5 + ierr6 + ierr7 + ierr8 
    550539#endif 
    551540      ! 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/SAS_SRC/step.F90

    r6140 r7299  
    2323   USE eosbn2           ! equation of state                (eos_bn2 routine) 
    2424   USE diawri           ! Standard run outputs             (dia_wri routine) 
    25    USE bdy_par          ! clem: mandatory for LIM3 
    26 #if defined key_bdy 
     25   USE bdy_oce   , ONLY: ln_bdy 
    2726   USE bdydta           ! clem: mandatory for LIM3 
    28 #endif 
    2927   USE stpctl           ! time stepping control            (stp_ctl routine) 
    3028   ! 
     
    8280      !           From SAS: ocean bdy data are wrong  (but we do not care) and ice bdy data are OK.   
    8381      !           This is not clean and should be changed in the future.  
    84 #if defined key_bdy 
    85       IF( lk_bdy     )       CALL bdy_dta ( kstp, time_offset=+1 )   ! update dynamic & tracer data at open boundaries 
    86 #endif 
     82      IF( ln_bdy     )       CALL bdy_dta ( kstp, time_offset=+1 )   ! update dynamic & tracer data at open boundaries 
    8783      ! ==> 
    8884                             CALL sbc    ( kstp )         ! Sea Boundary Condition (including sea-ice) 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/TOP_SRC/TRP/trcnxt.F90

    r6140 r7299  
    3333   USE trdtra 
    3434   USE tranxt 
     35   USE bdy_oce   , ONLY: ln_bdy 
    3536   USE trcbdy          ! BDY open boundaries 
    36    USE bdy_par, only: lk_bdy 
    3737# if defined key_agrif 
    3838   USE agrif_top_interp 
     
    9999      END DO 
    100100 
    101       IF( lk_bdy )  CALL trc_bdy( kt ) 
     101      IF( ln_bdy )  CALL trc_bdy( kt ) 
    102102 
    103103      !                                ! set time step size (Euler/Leapfrog) 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/TOP_SRC/TRP/trctrp.F90

    r6309 r7299  
    2525   USE trcsbc          ! surface boundary condition          (trc_sbc routine) 
    2626   USE zpshde          ! partial step: hor. derivative       (zps_hde routine) 
     27   USE bdy_oce   , ONLY: ln_bdy 
    2728   USE trcbdy          ! BDY open boundaries 
    28    USE bdy_par, only: lk_bdy 
    2929 
    3030#if defined key_agrif 
     
    6565         IF( lk_trabbl )        CALL trc_bbl    ( kt )      ! advective (and/or diffusive) bottom boundary layer scheme 
    6666         IF( ln_trcdmp )        CALL trc_dmp    ( kt )      ! internal damping trends 
    67          IF( lk_bdy )           CALL trc_bdy_dmp( kt )      ! BDY damping trends 
     67         IF( ln_bdy )           CALL trc_bdy_dmp( kt )      ! BDY damping trends 
    6868                                CALL trc_adv    ( kt )      ! horizontal & vertical advection  
    6969         !                                                         ! Partial top/bottom cell: GRADh( trb )   
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/TOP_SRC/trc.F90

    r6140 r7299  
    1414   USE par_oce 
    1515   USE par_trc 
    16 #if defined key_bdy 
    17    USE bdy_oce, only: nb_bdy, OBC_DATA 
    18 #endif 
     16   USE bdy_oce, only: ln_bdy, nb_bdy, OBC_DATA 
    1917    
    2018   IMPLICIT NONE 
     
    189187# endif 
    190188   ! 
    191 #if defined key_bdy 
    192189   CHARACTER(len=20), PUBLIC, ALLOCATABLE,  SAVE,  DIMENSION(:)   ::  cn_trc_dflt          ! Default OBC condition for all tracers 
    193190   CHARACTER(len=20), PUBLIC, ALLOCATABLE,  SAVE,  DIMENSION(:)   ::  cn_trc               ! Choice of boundary condition for tracers 
     
    195192   ! External data structure of BDY for TOP. Available elements: cn_obc, ll_trc, trcnow, dmp 
    196193   TYPE(OBC_DATA),    PUBLIC, ALLOCATABLE, DIMENSION(:,:), TARGET ::  trcdta_bdy           !: bdy external data (local process) 
    197 #endif 
    198194   ! 
    199195 
     
    210206      !!------------------------------------------------------------------- 
    211207      USE lib_mpp, ONLY: ctl_warn 
     208      INTEGER :: ierr(2) 
    212209      !!------------------------------------------------------------------- 
    213210      ! 
     211      ierr(:) = 0 
    214212      ALLOCATE( trn(jpi,jpj,jpk,jptra), trb(jpi,jpj,jpk,jptra), tra(jpi,jpj,jpk,jptra),       &   
    215213         &      trc_i(jpi,jpj,jptra)  , trc_o(jpi,jpj,jptra)                          ,       & 
     
    223221         &      ln_trc_sbc(jptra)     , ln_trc_cbc(jptra)     , ln_trc_obc(jptra)     ,       & 
    224222#endif 
    225 #if defined key_bdy 
    226          &      cn_trc_dflt(nb_bdy)   , cn_trc(nb_bdy)        , nn_trcdmp_bdy(nb_bdy) ,       & 
     223         &      STAT = ierr(1)  ) 
     224 
     225      IF ( ln_bdy ) THEN 
     226         ALLOCATE( cn_trc_dflt(nb_bdy)   , cn_trc(nb_bdy)     , nn_trcdmp_bdy(nb_bdy) ,       & 
    227227         &      trcdta_bdy(jptra,nb_bdy)                                              ,       & 
    228 #endif 
    229          &      STAT = trc_alloc  ) 
     228         &      STAT = ierr(2)  ) 
     229      ENDIF 
     230         ! 
     231      trc_alloc = MAXVAL( ierr ) 
    230232 
    231233      IF( trc_alloc /= 0 )   CALL ctl_warn('trc_alloc: failed to allocate arrays') 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/TOP_SRC/trcbc.F90

    r6140 r7299  
    1919   USE lib_mpp       !  MPP library 
    2020   USE fldread       !  read input fields 
    21 #if defined key_bdy 
    22    USE bdy_oce, only: nb_bdy , idx_bdy, ln_coords_file, rn_time_dmp, rn_time_dmp_out 
    23 #endif 
     21   USE bdy_oce,  ONLY: ln_bdy, nb_bdy , idx_bdy, ln_coords_file, rn_time_dmp, rn_time_dmp_out 
    2422 
    2523   IMPLICIT NONE 
     
    7876      !! 
    7977      NAMELIST/namtrc_bc/ cn_dir_sbc, cn_dir_cbc, cn_dir_obc, sn_trcobc, rn_trofac, sn_trcsbc, rn_trsfac, sn_trccbc, rn_trcfac 
    80 #if defined key_bdy 
    8178      NAMELIST/namtrc_bdy/ cn_trc_dflt, cn_trc, nn_trcdmp_bdy 
    82 #endif 
     79 
    8380      !!---------------------------------------------------------------------- 
    8481      IF( nn_timing == 1 )  CALL timing_start('trc_bc_init') 
     
    128125      IF(lwm) WRITE ( numont, namtrc_bc ) 
    129126 
    130 #if defined key_bdy 
    131       REWIND( numnat_ref )              ! Namelist namtrc_bc in reference namelist : Passive tracer data structure 
    132       READ  ( numnat_ref, namtrc_bdy, IOSTAT = ios, ERR = 903) 
    133 903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bdy in reference namelist', lwp ) 
    134  
    135       REWIND( numnat_cfg )              ! Namelist namtrc_bc in configuration namelist : Passive tracer data structure 
    136       READ  ( numnat_cfg, namtrc_bdy, IOSTAT = ios, ERR = 904 ) 
    137 904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bdy in configuration namelist', lwp ) 
    138       IF(lwm) WRITE ( numont, namtrc_bdy ) 
    139       ! setup up preliminary informations for BDY structure 
    140       DO jn = 1, ntrc 
    141          DO ib = 1, nb_bdy 
    142             ! Set type of obc in BDY data structure (around here we may plug user override of obc type from nml) 
    143             IF ( ln_trc_obc(jn) ) THEN 
    144                trcdta_bdy(jn,ib)%cn_obc = TRIM( cn_trc(ib) ) 
    145             ELSE 
    146                trcdta_bdy(jn,ib)%cn_obc = TRIM( cn_trc_dflt(ib) ) 
    147             ENDIF 
    148             ! set damping use in BDY data structure 
    149             trcdta_bdy(jn,ib)%dmp = .false. 
    150             IF(nn_trcdmp_bdy(ib) .EQ. 1 .AND. ln_trc_obc(jn) ) trcdta_bdy(jn,ib)%dmp = .true. 
    151             IF(nn_trcdmp_bdy(ib) .EQ. 2 ) trcdta_bdy(jn,ib)%dmp = .true. 
    152             IF(trcdta_bdy(jn,ib)%cn_obc == 'frs' .AND. nn_trcdmp_bdy(ib) .NE. 0 )  & 
    153                 & CALL ctl_stop( 'Use FRS OR relaxation' ) 
    154             IF (nn_trcdmp_bdy(ib) .LT. 0 .OR. nn_trcdmp_bdy(ib) .GT. 2)            & 
    155                 & CALL ctl_stop( 'Not a valid option for nn_trcdmp_bdy. Allowed: 0,1,2.' ) 
     127      IF ( ln_bdy ) THEN 
     128         REWIND( numnat_ref )              ! Namelist namtrc_bdy in reference namelist : Passive tracer data structure 
     129         READ  ( numnat_ref, namtrc_bdy, IOSTAT = ios, ERR = 903) 
     130903      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bdy in reference namelist', lwp ) 
     131 
     132         REWIND( numnat_cfg )              ! Namelist namtrc_bdy in configuration namelist : Passive tracer data structure 
     133         READ  ( numnat_cfg, namtrc_bdy, IOSTAT = ios, ERR = 904 ) 
     134904      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_bdy in configuration namelist', lwp ) 
     135         IF(lwm) WRITE ( numont, namtrc_bdy ) 
     136       
     137         ! setup up preliminary informations for BDY structure 
     138         DO jn = 1, ntrc 
     139            DO ib = 1, nb_bdy 
     140               ! Set type of obc in BDY data structure (around here we may plug user override of obc type from nml) 
     141               IF ( ln_trc_obc(jn) ) THEN 
     142                  trcdta_bdy(jn,ib)%cn_obc = TRIM( cn_trc(ib) ) 
     143               ELSE 
     144                  trcdta_bdy(jn,ib)%cn_obc = TRIM( cn_trc_dflt(ib) ) 
     145               ENDIF 
     146               ! set damping use in BDY data structure 
     147               trcdta_bdy(jn,ib)%dmp = .false. 
     148               IF(nn_trcdmp_bdy(ib) .EQ. 1 .AND. ln_trc_obc(jn) ) trcdta_bdy(jn,ib)%dmp = .true. 
     149               IF(nn_trcdmp_bdy(ib) .EQ. 2 ) trcdta_bdy(jn,ib)%dmp = .true. 
     150               IF(trcdta_bdy(jn,ib)%cn_obc == 'frs' .AND. nn_trcdmp_bdy(ib) .NE. 0 )  & 
     151                   & CALL ctl_stop( 'Use FRS OR relaxation' ) 
     152               IF (nn_trcdmp_bdy(ib) .LT. 0 .OR. nn_trcdmp_bdy(ib) .GT. 2)            & 
     153                   & CALL ctl_stop( 'Not a valid option for nn_trcdmp_bdy. Allowed: 0,1,2.' ) 
     154            ENDDO 
    156155         ENDDO 
    157       ENDDO 
    158  
    159 #else 
    160       ! Force all tracers OBC to false if bdy not used 
    161       ln_trc_obc = .false. 
    162 #endif 
     156      ELSE 
     157         ! Force all tracers OBC to false if bdy not used 
     158         ln_trc_obc = .false. 
     159      ENDIF 
     160 
    163161      ! compose BC data indexes 
    164162      DO jn = 1, ntrc 
     
    198196         WRITE(numout,*) ' ' 
    199197         WRITE(numout,'(a,i3)') '   Total tracers to be initialized with OPEN BCs data:', nb_trcobc 
    200 #if defined key_bdy 
    201          IF ( nb_trcobc > 0 ) THEN 
     198 
     199         IF ( ln_bdy .AND. nb_trcobc > 0 ) THEN 
    202200            WRITE(numout,*) '   #trc        NAME        Boundary     Mult.Fact.   OBC Settings' 
    203201            DO jn = 1, ntrc 
     
    217215            ENDDO 
    218216         ENDIF 
    219 #endif 
     217 
    220218         WRITE(numout,'(2a)') '   OPEN BC data repository : ', TRIM(cn_dir_obc) 
    221219      ENDIF 
     
    225223 
    226224      ! 
    227 #if defined key_bdy 
    228225      ! OPEN Lateral boundary conditions 
    229       IF( nb_trcobc > 0 ) THEN  
     226      IF( ln_bdy .AND. nb_trcobc > 0 ) THEN  
    230227         ALLOCATE ( sf_trcobc(nb_trcobc), rf_trofac(nb_trcobc), nbmap_ptr(nb_trcobc), STAT=ierr1 ) 
    231228         IF( ierr1 > 0 ) THEN 
     
    272269         CALL fld_fill( sf_trcobc, slf_i, cn_dir_obc, 'trc_bc_init', 'Passive tracer OBC data', 'namtrc_bc' ) 
    273270      ENDIF 
    274 #endif 
     271 
    275272      ! SURFACE Boundary conditions 
    276273      IF( nb_trcsbc > 0 ) THEN       !  allocate only if the number of tracer to initialise is greater than zero 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/TOP_SRC/trcbdy.F90

    r6140 r7299  
    99   !!            3.5  !  2012     (S. Mocavero, I. Epicoco) Optimization of BDY communications 
    1010   !!            3.6  !  2015     (T. Lovato) Adapt BDY for tracers in TOP component 
     11   !!            4.0  !  2016     (T. Lovato) Generalize OBC structure 
    1112   !!---------------------------------------------------------------------- 
    12 #if defined key_bdy && key_top 
     13#if defined key_top 
    1314   !!---------------------------------------------------------------------- 
    14    !!   'key_bdy'                     Unstructured Open Boundary Conditions 
    15    !!---------------------------------------------------------------------- 
    16    !!   trc_bdy            : Apply open boundary conditions to T and S 
    17    !!   trc_bdy_frs        : Apply Flow Relaxation Scheme 
     15   !!   trc_bdy       : Apply open boundary conditions & damping to tracers 
    1816   !!---------------------------------------------------------------------- 
    1917   USE timing                       ! Timing 
     
    2422   USE lbclnk                       ! ocean lateral boundary conditions (or mpp link) 
    2523   USE in_out_manager               ! I/O manager 
    26    USE bdy_oce, only: idx_bdy, OBC_INDEX, BDYTMASK, lk_bdy       ! ocean open boundary conditions 
     24   USE bdy_oce, only: idx_bdy       ! ocean open boundary conditions 
    2725 
    2826   IMPLICIT NONE 
     
    3331 
    3432   !!---------------------------------------------------------------------- 
    35    !! NEMO/OPA 3.6 , NEMO Consortium (2015) 
     33   !! NEMO/OPA 4.0 , NEMO Consortium (2016) 
    3634   !! $Id$  
    3735   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     
    4341      !!                  ***  SUBROUTINE trc_bdy  *** 
    4442      !! 
    45       !! ** Purpose : - Apply open boundary conditions for tracers in TOP component 
    46       !!                and scale the tracer data 
     43      !! ** Purpose : - Apply open boundary conditions for TOP tracers 
    4744      !! 
    4845      !!---------------------------------------------------------------------- 
    4946      INTEGER, INTENT( in ) :: kt     ! Main time step counter 
    5047      !! 
    51       INTEGER               :: ib_bdy, jn ! Loop indeces 
     48      INTEGER                           :: ib_bdy, jn ! Loop indeces 
     49      REAL(wp), POINTER, DIMENSION(:,:) ::  ztrc 
     50      REAL(wp), POINTER                 ::  zfac 
    5251      !!---------------------------------------------------------------------- 
    5352      ! 
    5453      IF( nn_timing == 1 ) CALL timing_start('trc_bdy') 
    5554      ! 
    56       DO jn = 1, jptra 
    57          DO ib_bdy=1, nb_bdy 
    58  
    59             SELECT CASE( trcdta_bdy(jn,ib_bdy)%cn_obc ) 
    60             CASE('none') 
    61                CYCLE 
    62             CASE('frs') 
    63                CALL bdy_trc_frs( jn, idx_bdy(ib_bdy), trcdta_bdy(jn,ib_bdy), kt ) 
    64             CASE('specified') 
    65                CALL bdy_trc_spe( jn, idx_bdy(ib_bdy), trcdta_bdy(jn,ib_bdy), kt ) 
    66             CASE('neumann') 
    67                CALL bdy_trc_nmn( jn, idx_bdy(ib_bdy), trcdta_bdy(jn,ib_bdy), kt ) 
    68             CASE('orlanski') 
    69                CALL bdy_trc_orlanski( jn, idx_bdy(ib_bdy), trcdta_bdy(jn,ib_bdy), ll_npo=.false. ) 
    70             CASE('orlanski_npo') 
    71                CALL bdy_trc_orlanski( jn, idx_bdy(ib_bdy), trcdta_bdy(jn,ib_bdy), ll_npo=.true. ) 
    72             CASE DEFAULT 
    73                CALL ctl_stop( 'trc_bdy : unrecognised option for open boundaries for passive tracers' ) 
     55      DO ib_bdy=1, nb_bdy 
     56         DO jn = 1, jptra 
     57            ! 
     58            ztrc => trcdta_bdy(jn,ib_bdy)%trc  
     59            zfac => trcdta_bdy(jn,ib_bdy)%rn_fac 
     60            ! 
     61            SELECT CASE( TRIM(trcdta_bdy(jn,ib_bdy)%cn_obc) ) 
     62            CASE('none'        )   ;   CYCLE 
     63            CASE('frs'         )   ;   CALL bdy_frs( idx_bdy(ib_bdy),                tra(:,:,:,jn), ztrc*zfac ) 
     64            CASE('specified'   )   ;   CALL bdy_spe( idx_bdy(ib_bdy),                tra(:,:,:,jn), ztrc*zfac ) 
     65            CASE('neumann'     )   ;   CALL bdy_nmn( idx_bdy(ib_bdy),                tra(:,:,:,jn) ) 
     66            CASE('orlanski'    )   ;   CALL bdy_orl( idx_bdy(ib_bdy), trb(:,:,:,jn), tra(:,:,:,jn), ztrc*zfac, ll_npo=.false. ) 
     67            CASE('orlanski_npo')   ;   CALL bdy_orl( idx_bdy(ib_bdy), trb(:,:,:,jn), tra(:,:,:,jn), ztrc*zfac, ll_npo=.true. ) 
     68            CASE DEFAULT           ;   CALL ctl_stop( 'trc_bdy : unrecognised option for open boundaries for passive tracers' ) 
    7469            END SELECT 
    75  
    7670            ! Boundary points should be updated 
    7771            CALL lbc_bdy_lnk( tra(:,:,:,jn), 'T', 1., ib_bdy ) 
    78  
    79          ENDDO 
    80       ENDDO 
     72            ! 
     73         END DO 
     74      END DO 
    8175      ! 
    8276      IF( nn_timing == 1 ) CALL timing_stop('trc_bdy') 
    8377 
    8478   END SUBROUTINE trc_bdy 
    85  
    86    SUBROUTINE bdy_trc_frs( jn, idx, dta, kt ) 
    87       !!---------------------------------------------------------------------- 
    88       !!                 ***  SUBROUTINE bdy_trc_frs  *** 
    89       !!                     
    90       !! ** Purpose : Apply the Flow Relaxation Scheme for tracers at open boundaries. 
    91       !!  
    92       !! Reference : Engedahl H., 1995, Tellus, 365-382. 
    93       !!---------------------------------------------------------------------- 
    94       INTEGER,         INTENT(in) ::   kt 
    95       INTEGER,         INTENT(in) ::   jn   ! Tracer index 
    96       TYPE(OBC_INDEX), INTENT(in) ::   idx  ! OBC indices 
    97       TYPE(OBC_DATA),  INTENT(in) ::   dta  ! OBC external data 
    98       !!  
    99       REAL(wp) ::   zwgt           ! boundary weight 
    100       INTEGER  ::   ib, ik, igrd   ! dummy loop indices 
    101       INTEGER  ::   ii, ij         ! 2D addresses 
    102       !!---------------------------------------------------------------------- 
    103       ! 
    104       IF( nn_timing == 1 ) CALL timing_start('bdy_trc_frs') 
    105       !  
    106       igrd = 1                       ! Everything is at T-points here 
    107       DO ib = 1, idx%nblen(igrd) 
    108          DO ik = 1, jpkm1 
    109             ii = idx%nbi(ib,igrd) 
    110             ij = idx%nbj(ib,igrd) 
    111             zwgt = idx%nbw(ib,igrd) 
    112             tra(ii,ij,ik,jn) = ( tra(ii,ij,ik,jn) + zwgt * ( ( dta%trc(ib,ik) * dta%rn_fac)  &  
    113                         &  - tra(ii,ij,ik,jn) ) ) * tmask(ii,ij,ik) 
    114          END DO 
    115       END DO  
    116       ! 
    117       IF( kt .eq. nit000 ) CLOSE( unit = 102 ) 
    118       ! 
    119       IF( nn_timing == 1 ) CALL timing_stop('bdy_trc_frs') 
    120       ! 
    121    END SUBROUTINE bdy_trc_frs 
    122    
    123    SUBROUTINE bdy_trc_spe( jn, idx, dta, kt ) 
    124       !!---------------------------------------------------------------------- 
    125       !!                 ***  SUBROUTINE bdy_trc_frs  *** 
    126       !!                     
    127       !! ** Purpose : Apply a specified value for tracers at open boundaries. 
    128       !!  
    129       !!---------------------------------------------------------------------- 
    130       INTEGER,         INTENT(in) ::   kt 
    131       INTEGER,         INTENT(in) ::   jn   ! Tracer index 
    132       TYPE(OBC_INDEX), INTENT(in) ::   idx  ! OBC indices 
    133       TYPE(OBC_DATA),  INTENT(in) ::   dta  ! OBC external data 
    134       !!  
    135       REAL(wp) ::   zwgt           ! boundary weight 
    136       INTEGER  ::   ib, ik, igrd   ! dummy loop indices 
    137       INTEGER  ::   ii, ij         ! 2D addresses 
    138       !!---------------------------------------------------------------------- 
    139       ! 
    140       IF( nn_timing == 1 ) CALL timing_start('bdy_trc_spe') 
    141       ! 
    142       igrd = 1                       ! Everything is at T-points here 
    143       DO ib = 1, idx%nblenrim(igrd) 
    144          ii = idx%nbi(ib,igrd) 
    145          ij = idx%nbj(ib,igrd) 
    146          DO ik = 1, jpkm1 
    147             tra(ii,ij,ik,jn) = dta%trc(ib,ik) * dta%rn_fac * tmask(ii,ij,ik) 
    148          END DO 
    149       END DO 
    150       ! 
    151       IF( kt .eq. nit000 ) CLOSE( unit = 102 ) 
    152       ! 
    153       IF( nn_timing == 1 ) CALL timing_stop('bdy_trc_spe') 
    154       ! 
    155    END SUBROUTINE bdy_trc_spe 
    156  
    157    SUBROUTINE bdy_trc_nmn( jn, idx, dta, kt ) 
    158       !!---------------------------------------------------------------------- 
    159       !!                 ***  SUBROUTINE bdy_trc_nmn  *** 
    160       !!                     
    161       !! ** Purpose : Duplicate the value for tracers at open boundaries. 
    162       !!  
    163       !!---------------------------------------------------------------------- 
    164       INTEGER,         INTENT(in) ::   kt 
    165       INTEGER,         INTENT(in) ::   jn   ! Tracer index 
    166       TYPE(OBC_INDEX), INTENT(in) ::   idx  ! OBC indices 
    167       TYPE(OBC_DATA),  INTENT(in) ::   dta  ! OBC external data 
    168       !!  
    169       REAL(wp) ::   zwgt           ! boundary weight 
    170       INTEGER  ::   ib, ik, igrd   ! dummy loop indices 
    171       INTEGER  ::   ii, ij, zcoef, zcoef1, zcoef2, ip, jp   ! 2D addresses 
    172       !!---------------------------------------------------------------------- 
    173       ! 
    174       IF( nn_timing == 1 ) CALL timing_start('bdy_trc_nmn') 
    175       ! 
    176       igrd = 1                       ! Everything is at T-points here 
    177       DO ib = 1, idx%nblenrim(igrd) 
    178          ii = idx%nbi(ib,igrd) 
    179          ij = idx%nbj(ib,igrd) 
    180          DO ik = 1, jpkm1 
    181             ! search the sense of the gradient 
    182             zcoef1 = bdytmask(ii-1,ij  ) +  bdytmask(ii+1,ij  ) 
    183             zcoef2 = bdytmask(ii  ,ij-1) +  bdytmask(ii  ,ij+1) 
    184             IF ( zcoef1+zcoef2 == 0) THEN 
    185                ! corner 
    186                zcoef = tmask(ii-1,ij,ik) + tmask(ii+1,ij,ik) +  tmask(ii,ij-1,ik) +  tmask(ii,ij+1,ik) 
    187                tra(ii,ij,ik,jn) = tra(ii-1,ij  ,ik,jn) * tmask(ii-1,ij  ,ik) + & 
    188                  &                tra(ii+1,ij  ,ik,jn) * tmask(ii+1,ij  ,ik) + & 
    189                  &                tra(ii  ,ij-1,ik,jn) * tmask(ii  ,ij-1,ik) + & 
    190                  &                tra(ii  ,ij+1,ik,jn) * tmask(ii  ,ij+1,ik) 
    191                tra(ii,ij,ik,jn) = ( tra(ii,ij,ik,jn) / MAX( 1, zcoef) ) * tmask(ii,ij,ik) 
    192             ELSE 
    193                ip = bdytmask(ii+1,ij  ) - bdytmask(ii-1,ij  ) 
    194                jp = bdytmask(ii  ,ij+1) - bdytmask(ii  ,ij-1) 
    195                tra(ii,ij,ik,jn) = tra(ii+ip,ij+jp,ik,jn) * tmask(ii+ip,ij+jp,ik) 
    196             ENDIF 
    197          END DO 
    198       END DO 
    199       ! 
    200       IF( kt .eq. nit000 ) CLOSE( unit = 102 ) 
    201       ! 
    202       IF( nn_timing == 1 ) CALL timing_stop('bdy_trc_nmn') 
    203       ! 
    204    END SUBROUTINE bdy_trc_nmn 
    205   
    206  
    207    SUBROUTINE bdy_trc_orlanski( jn, idx, dta, ll_npo ) 
    208       !!---------------------------------------------------------------------- 
    209       !!                 ***  SUBROUTINE bdy_trc_orlanski  *** 
    210       !!              
    211       !!              - Apply Orlanski radiation to tracers of TOP component.  
    212       !!              - Wrapper routine for bdy_orlanski_3d 
    213       !!  
    214       !! 
    215       !! References:  Marchesiello, McWilliams and Shchepetkin, Ocean Modelling vol. 3 (2001)     
    216       !!---------------------------------------------------------------------- 
    217       INTEGER,                      INTENT(in) ::   jn      ! Tracer index 
    218       TYPE(OBC_INDEX),              INTENT(in) ::   idx     ! OBC indices 
    219       TYPE(OBC_DATA),               INTENT(in) ::   dta     ! OBC external data 
    220       LOGICAL,                      INTENT(in) ::   ll_npo  ! switch for NPO version 
    221  
    222       INTEGER  ::   igrd                                    ! grid index 
    223       !!---------------------------------------------------------------------- 
    224  
    225       IF( nn_timing == 1 ) CALL timing_start('bdy_trc_orlanski') 
    226       ! 
    227       igrd = 1      ! Orlanski bc on tracers;  
    228       !             
    229       CALL bdy_orlanski_3d( idx, igrd, trb(:,:,:,jn), tra(:,:,:,jn), (dta%trc * dta%rn_fac), ll_npo ) 
    230       ! 
    231       IF( nn_timing == 1 ) CALL timing_stop('bdy_trc_orlanski') 
    232       ! 
    233  
    234    END SUBROUTINE bdy_trc_orlanski 
    23579 
    23680   SUBROUTINE trc_bdy_dmp( kt ) 
  • branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/TOP_SRC/trcsub.F90

    r7091 r7299  
    2020   USE domvvl 
    2121   USE divhor          ! horizontal divergence            (div_hor routine) 
    22    USE sbcrnf, ONLY: h_rnf, nk_rnf   ! River runoff  
    23    USE bdy_oce 
     22   USE sbcrnf    , ONLY: h_rnf, nk_rnf    ! River runoff 
     23   USE bdy_oce   , ONLY: ln_bdy, bdytmask ! BDY 
    2424#if defined key_agrif 
    2525   USE agrif_opa_update 
     
    493493      z1_rau0 = 0.5 / rau0 
    494494      ssha(:,:) = (  sshb(:,:) - z2dt * ( z1_rau0 * ( emp_b(:,:) + emp(:,:) ) + zhdiv(:,:) )  ) * tmask(:,:,1) 
    495 #if ! defined key_dynspg_ts 
     495 
     496      IF( .NOT.ln_dynspg_ts ) THEN 
    496497      ! These lines are not necessary with time splitting since 
    497498      ! boundary condition on sea level is set during ts loop 
     
    499500      CALL agrif_ssh( kt ) 
    500501#endif 
    501 #if defined key_bdy 
    502       ssha(:,:) = ssha(:,:) * bdytmask(:,:) 
    503       CALL lbc_lnk( ssha, 'T', 1. )  
    504 #endif 
    505 #endif 
     502         IF( ln_bdy ) THEN 
     503            ssha(:,:) = ssha(:,:) * bdytmask(:,:) 
     504            CALL lbc_lnk( ssha, 'T', 1. )  
     505         ENDIF 
     506      ENDIF 
    506507      ! 
    507508      !                                           !------------------------------! 
     
    514515            &                      - ( e3t_a(:,:,jk) - e3t_b(:,:,jk) )    & 
    515516            &                         * tmask(:,:,jk) * z1_2dt 
    516 #if defined key_bdy 
    517          wn(:,:,jk) = wn(:,:,jk) * bdytmask(:,:) 
    518 #endif 
     517         IF( ln_bdy ) wn(:,:,jk) = wn(:,:,jk) * bdytmask(:,:) 
    519518      END DO 
    520519      ! 
  • branches/2016/dev_CMCC_2016/NEMOGCM/SETTE/BATCH_TEMPLATE/batch-ifort_athena

    r6140 r7299  
    44#BSUB -n NPROCS 
    55#BSUB -a poe 
    6 #BSUB -J MPI_config 
     6#BSUB -J NEMO_SETTE 
    77#BSUB -o poe.stdout.%J 
    88#BSUB -e poe.stderr.%J 
  • branches/2016/dev_CMCC_2016/NEMOGCM/SETTE/BATCH_TEMPLATE/batch-ifort_athena_xios

    r6409 r7299  
    44#BSUB -n TOTAL_NPROCS 
    55#BSUB -a poe 
    6 #BSUB -J MPI_config 
     6#BSUB -J NEMO_SETTE 
    77#BSUB -o poe.stdout.%J 
    88#BSUB -e poe.stderr.%J 
  • branches/2016/dev_CMCC_2016/NEMOGCM/SETTE/sette.sh

    r7298 r7299  
    767767    export TEST_NAME="LONG" 
    768768    cd ${CONFIG_DIR} 
    769     . ./makenemo -m ${CMP_NAM} -n AMM12_LONG -r AMM12 -j 8 add_key "key_tide" del_key ${DEL_KEYS} 
     769    . ./makenemo -m ${CMP_NAM} -n AMM12_LONG -r AMM12 -j 8 del_key ${DEL_KEYS} 
    770770    cd ${SETTE_DIR} 
    771771    . ./param.cfg 
     
    829829    export TEST_NAME="REPRO_8_4" 
    830830    cd ${CONFIG_DIR} 
    831     . ./makenemo -m ${CMP_NAM} -n AMM12_32 -r AMM12 -j 8 add_key "key_tide" del_key ${DEL_KEYS} 
     831    . ./makenemo -m ${CMP_NAM} -n AMM12_32 -r AMM12 -j 8 del_key ${DEL_KEYS} 
    832832    cd ${SETTE_DIR} 
    833833    . ./param.cfg 
     
    949949    export TEST_NAME="REPRO_8_4" 
    950950    cd ${CONFIG_DIR} 
    951     . ./makenemo -m ${CMP_NAM} -n SAS_32 -r ORCA2_SAS_LIM -j 8 add_key del_key ${DEL_KEYS} 
     951    . ./makenemo -m ${CMP_NAM} -n SAS_32 -r ORCA2_SAS_LIM -j 8 del_key ${DEL_KEYS} 
    952952    cd ${SETTE_DIR} 
    953953    . ./param.cfg 
  • branches/2016/dev_CMCC_2016/NEMOGCM/TRUST/inputs/AMM12/namelist_cfg

    r6222 r7299  
    209209/ 
    210210!----------------------------------------------------------------------- 
    211 &nam_tide      !   tide parameters (#ifdef key_tide) 
    212 !----------------------------------------------------------------------- 
     211&nam_tide      !   tide parameters 
     212!----------------------------------------------------------------------- 
     213   ln_tide     = .true. 
    213214   clname(1)     =   'Q1'   !  name of constituent 
    214215   clname(2)     =   'O1' 
     
    228229/ 
    229230!----------------------------------------------------------------------- 
    230 &nambdy        !  unstructured open boundaries                          ("key_bdy") 
     231&nambdy        !  unstructured open boundaries 
     232    ln_bdy         = .true. 
    231233    nb_bdy         =  1 
    232234    cn_dyn2d       = 'flather' 
     
    236238/ 
    237239!----------------------------------------------------------------------- 
    238 &nambdy_dta      !  open boundaries - external data           ("key_bdy") 
     240&nambdy_dta      !  open boundaries - external data 
    239241!----------------------------------------------------------------------- 
    240242!          !  file name  ! frequency (hours) ! variable  ! time interp. !  clim  ! 'yearly'/ ! weights  ! rotation ! land/sea mask ! 
  • branches/2016/dev_CMCC_2016/NEMOGCM/TRUST/inputs/GYRE/namelist_cfg

    r6222 r7299  
    163163/ 
    164164!----------------------------------------------------------------------- 
    165 &nam_tide      !    tide parameters (#ifdef key_tide) 
    166 !----------------------------------------------------------------------- 
    167 / 
    168 !----------------------------------------------------------------------- 
    169 &nambdy        !  unstructured open boundaries                          ("key_bdy") 
    170 !----------------------------------------------------------------------- 
    171 / 
    172 !----------------------------------------------------------------------- 
    173 &nambdy_dta      !  open boundaries - external data           ("key_bdy") 
     165&nam_tide      !    tide parameters 
     166!----------------------------------------------------------------------- 
     167/ 
     168!----------------------------------------------------------------------- 
     169&nambdy        !  unstructured open boundaries 
     170!----------------------------------------------------------------------- 
     171/ 
     172!----------------------------------------------------------------------- 
     173&nambdy_dta      !  open boundaries - external data 
    174174!----------------------------------------------------------------------- 
    175175/ 
  • branches/2016/dev_CMCC_2016/NEMOGCM/fcm-make/inc/keys-amm12.cfg

    r6140 r7299  
    11preprocess.prop{fpp.defs} = \ 
    2   key_bdy key_tide key_dynspg_ts key_ldfslp key_zdfgls key_vvl key_diainstant key_mpp_mpi key_iomput 
     2  key_dynspg_ts key_ldfslp key_zdfgls key_vvl key_diainstant key_mpp_mpi key_iomput 
Note: See TracChangeset for help on using the changeset viewer.