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 7026 for branches/2016/dev_r6999_CONFIGMAN_1/NEMOGCM/TOOLS/SIREN/src/merge_bathy.f90 – NEMO

Ignore:
Timestamp:
2016-10-13T15:50:54+02:00 (8 years ago)
Author:
jpaul
Message:

see ticket 1781

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_r6999_CONFIGMAN_1/NEMOGCM/TOOLS/SIREN/src/merge_bathy.f90

    r6393 r7026  
    115115!>       - cn_east  : east  boundary indices on fine grid<br/> 
    116116!>       - cn_west  : west  boundary indices on fine grid<br/> 
     117!>       - in_ncrs  : number of point(s) with coarse value save at boundaries<br/> 
    117118!>       - ln_oneseg: use only one segment for each boundary or not 
    118119!> 
     
    130131!> @date September, 2015 
    131132!> - manage useless (dummy) variable, attributes, and dimension 
     133!> @date October, 2016 
     134!> - allow to choose the number of boundary point with coarse grid value. 
    132135!> 
    133136!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    231234   LOGICAL                                 :: ln_east  = .TRUE. 
    232235   LOGICAL                                 :: ln_west  = .TRUE. 
    233    LOGICAL                                 :: ln_oneseg= .TRUE. 
    234236   CHARACTER(LEN=lc)                       :: cn_north = '' 
    235237   CHARACTER(LEN=lc)                       :: cn_south = '' 
    236238   CHARACTER(LEN=lc)                       :: cn_east  = '' 
    237239   CHARACTER(LEN=lc)                       :: cn_west  = '' 
     240   INTEGER(i4)                             :: in_ncrs  = 2 
     241   LOGICAL                                 :: ln_oneseg= .TRUE. 
    238242 
    239243   ! namout 
     
    276280   &  cn_east ,   &     !< east  boundary indices on fine grid 
    277281   &  cn_west ,   &     !< west  boundary indices on fine grid 
     282   &  in_ncrs,    &     !< number of point with coarse value save at boundaries  
    278283   &  ln_oneseg         !< use only one segment for each boundary or not 
    279284 
     
    435440   DO jk=1,ip_ncard 
    436441      CALL merge_bathy_get_boundary(tl_bathy0, tl_bathy1, tl_bdy(jk), & 
    437       &                             il_rho(:),                        & 
     442      &                             il_rho(:), in_ncrs,                      & 
    438443      &                             dl_refined(:,:,:,:), dl_weight(:,:,:,:), & 
    439444      &                             dl_fill) 
     
    638643   !> @param[in] td_bdy          boundary structure 
    639644   !> @param[in] id_rho          array of refinement factor 
     645   !> @param[in] id_ncrs         number of point with coarse value save at boundaries 
    640646   !> @param[inout] dd_refined   array of refined bathymetry  
    641647   !> @param[inout] dd_weight    array of weight 
    642648   !> @param[in] dd_fill         fillValue 
    643649   !> 
    644    !> @todo improve boundary weight function 
    645650   !------------------------------------------------------------------- 
    646651   SUBROUTINE merge_bathy_get_boundary( td_bathy0, td_bathy1, td_bdy, & 
    647    &                                    id_rho,                       & 
     652   &                                    id_rho, id_ncrs,              & 
    648653   &                                    dd_refined, dd_weight, dd_fill ) 
    649654 
     
    655660      TYPE(TBDY)                     , INTENT(IN   ) :: td_bdy 
    656661      INTEGER(i4), DIMENSION(:)      , INTENT(IN   ) :: id_rho 
     662      INTEGER(i4)                    , INTENT(IN   ) :: id_ncrs 
    657663      REAL(dp)   , DIMENSION(:,:,:,:), INTENT(INOUT) :: dd_refined 
    658664      REAL(dp)   , DIMENSION(:,:,:,:), INTENT(INOUT) :: dd_weight 
     
    670676      INTEGER(i4) :: il_jmax0 
    671677 
     678      INTEGER(i4) :: il_width 
     679 
    672680      INTEGER(i4), DIMENSION(2,2)         :: il_offset 
    673681      INTEGER(i4), DIMENSION(2,2)         :: il_ind 
     
    838846            CASE('north') 
    839847 
    840 !               ! npoint coarse 
    841 !               il_width=td_bdy%t_seg(jl)%i_width-id_npoint 
    842 !               ! compute "distance" 
    843 !               dl_tmp1d(:)=(/(ji,ji=il_width-1,1,-1),(0,ji=1,id_npoint)/) 
    844 !               ! compute weight on segment 
    845 !               dl_tmp1d(:)= 0.5 + 0.5*COS( (dp_pi*dl_tmp1d(:)) / & 
    846 !               &                           (il_width) ) 
    847  
     848 
     849               ! save n coarse point 
     850               il_width=td_bdy%t_seg(jl)%i_width-id_ncrs 
    848851               ! compute "distance" 
    849                dl_tmp1d(:)=(/(ji-1,ji=td_bdy%t_seg(jl)%i_width-1,1,-1),0/) 
     852               dl_tmp1d(:)=(/(ji,ji=il_width-1,1,-1),(0,ji=1,id_ncrs)/) 
    850853 
    851854               ! compute weight on segment 
    852855               dl_tmp1d(:)= 0.5 + 0.5*COS( (dp_pi*dl_tmp1d(:)) / & 
    853                &                           (td_bdy%t_seg(jl)%i_width) ) 
     856               &                           (il_width) ) 
     857 
    854858 
    855859               ALLOCATE( dl_wseg(tl_dom1%t_dim(1)%i_len, & 
     
    862866            CASE('south') 
    863867 
     868               ! save n coarse point 
     869               il_width=td_bdy%t_seg(jl)%i_width-id_ncrs 
    864870               ! compute "distance" 
    865                dl_tmp1d(:)=(/0,(ji-1,ji=1,td_bdy%t_seg(jl)%i_width-1)/)                
     871               dl_tmp1d(:)=(/(0,ji=1,id_ncrs),(ji,ji=1,il_width-1)/) 
    866872 
    867873               ! compute weight on segment 
    868874               dl_tmp1d(:)= 0.5 + 0.5*COS( (dp_pi*dl_tmp1d(:)) / & 
    869                &                           (td_bdy%t_seg(jl)%i_width) ) 
     875               &                           (il_width) ) 
     876 
    870877 
    871878               ALLOCATE( dl_wseg(tl_dom1%t_dim(1)%i_len, & 
     
    878885            CASE('east') 
    879886 
     887               ! save n coarse point 
     888               il_width=td_bdy%t_seg(jl)%i_width-id_ncrs 
    880889               ! compute "distance" 
    881                dl_tmp1d(:)=(/(ji-1,ji=td_bdy%t_seg(jl)%i_width-1,1,-1),0/) 
     890               dl_tmp1d(:)=(/(ji,ji=il_width-1,1,-1),(0,ji=1,id_ncrs)/) 
    882891 
    883892               ! compute weight on segment 
    884893               dl_tmp1d(:)= 0.5 + 0.5*COS( (dp_pi*dl_tmp1d(:)) / & 
    885                &                           (td_bdy%t_seg(jl)%i_width) ) 
     894               &                           (il_width) ) 
     895 
    886896 
    887897               ALLOCATE( dl_wseg(tl_dom1%t_dim(1)%i_len, & 
     
    894904            CASE('west') 
    895905 
     906               ! save n coarse point 
     907               il_width=td_bdy%t_seg(jl)%i_width-id_ncrs 
    896908               ! compute "distance" 
    897                dl_tmp1d(:)=(/0,(ji-1,ji=1,td_bdy%t_seg(jl)%i_width-1)/)                
     909               dl_tmp1d(:)=(/(0,ji=1,id_ncrs),(ji,ji=1,il_width-1)/) 
    898910 
    899911               ! compute weight on segment 
    900912               dl_tmp1d(:)= 0.5 + 0.5*COS( (dp_pi*dl_tmp1d(:)) / & 
    901                &                           (td_bdy%t_seg(jl)%i_width) ) 
     913               &                           (il_width) ) 
     914 
    902915 
    903916               ALLOCATE( dl_wseg(tl_dom1%t_dim(1)%i_len, & 
Note: See TracChangeset for help on using the changeset viewer.