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 for branches/2016/dev_CMCC_2016/NEMOGCM/NEMO/OPA_SRC/BDY/bdyini.F90 – NEMO

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

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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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 
Note: See TracChangeset for help on using the changeset viewer.