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 6862 for branches/2016/dev_r6522_SIMPLIF_3 – NEMO

Ignore:
Timestamp:
2016-08-12T15:16:24+02:00 (8 years ago)
Author:
lovato
Message:

#1729 - trunk: removed key_bdy from the code and set usage of ln_bdy. Tested with SETTE.

Location:
branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM
Files:
1 deleted
40 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/CONFIG/AMM12/EXP00/namelist_cfg

    r6489 r6862  
    208208/ 
    209209!----------------------------------------------------------------------- 
    210 &nambdy        !  unstructured open boundaries                          ("key_bdy") 
     210&nambdy        !  unstructured open boundaries 
     211    ln_bdy         = .true. 
    211212    nb_bdy         =  1 
    212213    cn_dyn2d       = 'flather' 
     
    216217/ 
    217218!----------------------------------------------------------------------- 
    218 &nambdy_dta      !  open boundaries - external data           ("key_bdy") 
     219&nambdy_dta      !  open boundaries - external data 
    219220!----------------------------------------------------------------------- 
    220221!          !  file name  ! frequency (hours) ! variable  ! time interp. !  clim  ! 'yearly'/ ! weights  ! rotation ! land/sea mask ! 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/CONFIG/AMM12/cpp_AMM12.fcm

    r6140 r6862  
    1  bld::tool::fppkeys  key_bdy key_tide key_zdfgls key_diainstant key_mpp_mpi key_iomput 
     1 bld::tool::fppkeys key_tide key_zdfgls key_diainstant key_mpp_mpi key_iomput 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/CONFIG/SHARED/namelist_ref

    r6497 r6862  
    621621&nambdy        !  unstructured open boundaries                          ("key_bdy") 
    622622!----------------------------------------------------------------------- 
     623    ln_bdy         = .false.              !  Use unstructured open boundaries 
    623624    nb_bdy         = 0                    !  number of open boundary sets 
    624625    ln_coords_file = .true.               !  =T : read bdy coordinates from file 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/NEMO/LIM_SRC_3/limcons.F90

    r6416 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/LIM_SRC_3/limrhg.F90

    r6416 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/LIM_SRC_3/limsbc.F90

    r6416 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/NST_SRC/agrif_user.F90

    r6140 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/BDY/bdy_oce.F90

    r6140 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/BDY/bdydta.F90

    r6140 r6862  
    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 
     
    899895   END SUBROUTINE bdy_dta_init 
    900896 
    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  
    917897   !!============================================================================== 
    918898END MODULE bdydta 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/BDY/bdydyn.F90

    r6140 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/BDY/bdydyn2d.F90

    r5930 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/BDY/bdydyn3d.F90

    r6140 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/BDY/bdyice_lim.F90

    r5836 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/BDY/bdyini.F90

    r6140 r6862  
    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 
     22   USE bdydta         ! open boundary cond. setting   (bdy_dta_init routine) 
     23   USE bdytides       ! open boundary cond. setting   (bdytide_init routine) 
    2524   USE sbctide  , ONLY: lk_tide ! Tidal forcing or not 
    2625   USE phycst   , ONLY: rday 
     
    9493      INTEGER                              ::   nbdyind, nbdybeg, nbdyend 
    9594      !! 
    96       NAMELIST/nambdy/ nb_bdy, ln_coords_file, cn_coords_file,                 & 
     95      NAMELIST/nambdy/ ln_bdy, nb_bdy, ln_coords_file, cn_coords_file,         & 
    9796         &             ln_mask_file, cn_mask_file, cn_dyn2d, nn_dyn2d_dta,     & 
    9897         &             cn_dyn3d, nn_dyn3d_dta, cn_tra, nn_tra_dta,             &   
    9998         &             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,                 & 
     99         &             cn_ice_lim, nn_ice_lim_dta,                             & 
     100         &             rn_ice_tem, rn_ice_sal, rn_ice_age,                     & 
    102101         &             ln_vol, nn_volctl, nn_rimwidth 
    103102         ! 
     
    108107      IF( nn_timing == 1 )   CALL timing_start('bdy_init') 
    109108      ! 
    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  
    117109      cgrid = (/'t','u','v'/) 
    118110       
     
    133125      ! ----------------------------------------- 
    134126      !                                   ! control prints 
    135       IF(lwp) WRITE(numout,*) '   nambdy' 
     127      IF ( ln_bdy ) THEN 
     128         IF(lwp) WRITE(numout,*) 
     129         IF(lwp) WRITE(numout,*) 'bdy_init : initialization of open boundaries' 
     130         IF(lwp) WRITE(numout,*) '~~~~~~~~' 
     131      ELSE 
     132         IF(lwp) WRITE(numout,*) 
     133         IF(lwp) WRITE(numout,*) 'bdy_init : open boundaries not used (ln_bdy = F)' 
     134         IF(lwp) WRITE(numout,*) '~~~~~~~~' 
     135         IF( nn_timing == 1 )   CALL timing_stop('bdy_init') 
     136         return 
     137      ENDIF 
     138 
     139      IF( jperio /= 0 )   CALL ctl_stop( 'bdy_init: Cyclic or symmetric,',   & 
     140         &                               ' and general open boundary condition are not compatible' ) 
    136141 
    137142      IF( nb_bdy == 0 ) THEN  
     
    13001305      CALL wrk_dealloc(jpi,jpj,   zfmask )  
    13011306      ! 
     1307      ! Open boundaries initialisation of external data arrays 
     1308      CALL bdy_dta_init 
     1309      ! 
     1310      ! Open boundaries initialisation of tidal harmonic forcing 
     1311      IF( lk_tide ) CALL bdytide_init 
     1312 
     1313      ! 
    13021314      IF( nn_timing == 1 )   CALL timing_stop('bdy_init') 
    13031315      ! 
     
    17131725   END SUBROUTINE bdy_ctl_corn 
    17141726 
    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  
    17241727   !!================================================================================= 
    17251728END MODULE bdyini 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/BDY/bdylib.F90

    r6140 r6862  
    66   !! History :  3.6  !  2013     (D. Storkey) original code 
    77   !!---------------------------------------------------------------------- 
    8 #if defined key_bdy  
    9    !!---------------------------------------------------------------------- 
    10    !!   'key_bdy' :                    Unstructured Open Boundary Condition 
    118   !!---------------------------------------------------------------------- 
    129   !!   bdy_orlanski_2d 
     
    355352   END SUBROUTINE bdy_orlanski_3d 
    356353 
    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  
    371354   !!====================================================================== 
    372355END MODULE bdylib 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/BDY/bdytides.F90

    r6140 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/BDY/bdytra.F90

    r6140 r6862  
    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    !!---------------------------------------------------------------------- 
    11 #if defined key_bdy 
    12    !!---------------------------------------------------------------------- 
    13    !!   'key_bdy'                     Unstructured Open Boundary Conditions 
    1410   !!---------------------------------------------------------------------- 
    1511   !!   bdy_tra            : Apply open boundary conditions to T and S 
     
    308304   END SUBROUTINE bdy_tra_dmp 
    309305  
    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  
    324306   !!====================================================================== 
    325307END MODULE bdytra 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/BDY/bdyvol.F90

    r6140 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/DIA/diahsb.F90

    r6140 r6862  
    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 
     
    399399      surf_tot  = glob_sum( surf(:,:) )                                       ! total ocean surface area 
    400400 
    401       IF( lk_bdy ) CALL ctl_warn( 'dia_hsb does not take open boundary fluxes into account' )          
     401      IF( ln_bdy ) CALL ctl_warn( 'dia_hsb does not take open boundary fluxes into account' )          
    402402      ! 
    403403      ! ---------------------------------- ! 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/DOM/dommsk.F90

    r6140 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/DYN/dynnxt.F90

    r6140 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg_ts.F90

    r6152 r6862  
    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 
     
    608608         ! Update only tidal forcing at open boundaries 
    609609#if defined key_tide 
    610          IF( lk_bdy      .AND. lk_tide )   CALL bdy_dta_tides( kt, kit=jn, time_offset= noffset+1 ) 
     610         IF( ln_bdy      .AND. lk_tide )   CALL bdy_dta_tides( kt, kit=jn, time_offset= noffset+1 ) 
    611611         IF( ln_tide_pot .AND. lk_tide )   CALL upd_tide     ( kt, kit=jn, time_offset= noffset   ) 
    612612#endif 
     
    705705         CALL lbc_lnk( ssha_e, 'T',  1._wp ) 
    706706 
    707 #if defined key_bdy 
    708707         ! Duplicate sea level across open boundaries (this is only cosmetic if linssh=T) 
    709          IF( lk_bdy )   CALL bdy_ssh( ssha_e ) 
    710 #endif 
     708         IF( ln_bdy )   CALL bdy_ssh( ssha_e ) 
     709 
    711710#if defined key_agrif 
    712711         IF( .NOT.Agrif_Root() )   CALL agrif_ssh_ts( jn ) 
     
    967966         CALL lbc_lnk_multi( ua_e, 'U', -1._wp, va_e , 'V', -1._wp ) 
    968967         ! 
    969 #if defined key_bdy   
    970968         !                                                 ! 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 
     969         IF( ln_bdy )   CALL bdy_dyn2d( jn, ua_e, va_e, un_e, vn_e, hur_e, hvr_e, ssha_e ) 
     970 
    973971#if defined key_agrif                                                            
    974972         IF( .NOT.Agrif_Root() )  CALL agrif_dyn_ts( jn )  ! Agrif 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/DYN/sshwzv.F90

    r6152 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/SBC/fldread.F90

    r6140 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim.F90

    r6416 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim_2.F90

    r6140 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r6460 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/SBC/sbcwave.F90

    r6140 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/TRA/tranxt.F90

    r6140 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r6152 r6862  
    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) 
    5756   USE sbctide, ONLY  : lk_tide 
    5857   USE istate         ! initial state setting          (istate_init routine) 
     
    435434      IF( lk_tide       )   CALL    tide_init   ! tidal harmonics 
    436435                            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           
     436                            CALL     bdy_init   ! Open boundaries initialisation 
    443437      !                                      ! Ocean physics 
    444438      !                                         ! Vertical physics 
     
    659653      USE diadct    , ONLY: diadct_alloc  
    660654#endif  
    661 #if defined key_bdy 
    662655      USE bdy_oce   , ONLY: bdy_oce_alloc 
    663 #endif 
    664656      ! 
    665657      INTEGER :: ierr 
     
    676668      ierr = ierr + diadct_alloc    ()          !  
    677669#endif  
    678 #if defined key_bdy 
    679670      ierr = ierr + bdy_oce_alloc   ()          ! bdy masks (incl. initialization) 
    680 #endif 
    681671      ! 
    682672      IF( lk_mpp    )   CALL mpp_sum( ierr ) 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/step.F90

    r6464 r6862  
    106106      IF( lk_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_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/step_oce.F90

    r6140 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/SAS_SRC/nemogcm.F90

    r6165 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/SAS_SRC/step.F90

    r6140 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/TOP_SRC/TRP/trcnxt.F90

    r6140 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/TOP_SRC/TRP/trctrp.F90

    r6309 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/TOP_SRC/trc.F90

    r6140 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/TOP_SRC/trcbc.F90

    r6140 r6862  
    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_r6522_SIMPLIF_3/NEMOGCM/NEMO/TOP_SRC/trcbdy.F90

    r6140 r6862  
    1010   !!            3.6  !  2015     (T. Lovato) Adapt BDY for tracers in TOP component 
    1111   !!---------------------------------------------------------------------- 
    12 #if defined key_bdy && key_top 
    13    !!---------------------------------------------------------------------- 
    14    !!   'key_bdy'                     Unstructured Open Boundary Conditions 
     12#if defined key_top 
    1513   !!---------------------------------------------------------------------- 
    1614   !!   trc_bdy            : Apply open boundary conditions to T and S 
     
    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, OBC_INDEX, BDYTMASK, ln_bdy       ! ocean open boundary conditions 
    2725 
    2826   IMPLICIT NONE 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/NEMO/TOP_SRC/trcsub.F90

    r6140 r6862  
    2020#endif 
    2121#if defined key_zdfgls 
    22    USE zdfgls, ONLY: en 
     22   USE zdfgls    , ONLY: en 
    2323#endif 
    2424   USE trabbl 
     
    2626   USE domvvl 
    2727   USE divhor          ! horizontal divergence            (div_hor routine) 
    28    USE sbcrnf, ONLY: h_rnf, nk_rnf   ! River runoff  
    29    USE bdy_oce 
     28   USE sbcrnf    , ONLY: h_rnf, nk_rnf    ! River runoff 
     29   USE bdy_oce   , ONLY: ln_bdy, bdytmask ! BDY 
    3030#if defined key_agrif 
    3131   USE agrif_opa_update 
     
    505505      CALL agrif_ssh( kt ) 
    506506#endif 
    507 #if defined key_bdy 
    508       ssha(:,:) = ssha(:,:) * bdytmask(:,:) 
    509       CALL lbc_lnk( ssha, 'T', 1. )  
    510 #endif 
     507      IF( ln_bdy ) THEN 
     508         ssha(:,:) = ssha(:,:) * bdytmask(:,:) 
     509         CALL lbc_lnk( ssha, 'T', 1. )  
     510      ENDIF 
    511511#endif 
    512512      ! 
     
    520520            &                      - ( e3t_a(:,:,jk) - e3t_b(:,:,jk) )    & 
    521521            &                         * tmask(:,:,jk) * z1_2dt 
    522 #if defined key_bdy 
    523          wn(:,:,jk) = wn(:,:,jk) * bdytmask(:,:) 
    524 #endif 
     522         IF( ln_bdy ) wn(:,:,jk) = wn(:,:,jk) * bdytmask(:,:) 
    525523      END DO 
    526524      ! 
Note: See TracChangeset for help on using the changeset viewer.