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 7646 for trunk/NEMOGCM/TOOLS/SIREN/src/merge_bathy.f90 – NEMO

Ignore:
Timestamp:
2017-02-06T10:25:03+01:00 (7 years ago)
Author:
timgraham
Message:

Merge of dev_merge_2016 into trunk. UPDATE TO ARCHFILES NEEDED for XIOS2.
LIM_SRC_s/limrhg.F90 to follow in next commit due to change of kind (I'm unable to do it in this commit).
Merged using the following steps:

1) svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk .
2) Resolve minor conflicts in sette.sh and namelist_cfg for ORCA2LIM3 (due to a change in trunk after branch was created)
3) svn commit
4) svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
5) svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2016/dev_merge_2016 .
6) At this stage I checked out a clean copy of the branch to compare against what is about to be committed to the trunk.
6) svn commit #Commit code to the trunk

In this commit I have also reverted a change to Fcheck_archfile.sh which was causing problems on the Paris machine.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/TOOLS/SIREN/src/merge_bathy.f90

    r6393 r7646  
    5151!>       - cn_varcfg : variable configuration file  
    5252!> (see ./SIREN/cfg/variable.cfg) 
     53!>       - cn_dimcfg : dimension configuration file. define dimensions allowed 
     54!> (see ./SIREN/cfg/dimension.cfg). 
    5355!>       - cn_dumcfg : useless (dummy) configuration file, for useless  
    5456!> dimension or variable (see ./SIREN/cfg/dummy.cfg). 
     
    115117!>       - cn_east  : east  boundary indices on fine grid<br/> 
    116118!>       - cn_west  : west  boundary indices on fine grid<br/> 
     119!>       - in_ncrs  : number of point(s) with coarse value save at boundaries<br/> 
    117120!>       - ln_oneseg: use only one segment for each boundary or not 
    118121!> 
     
    130133!> @date September, 2015 
    131134!> - manage useless (dummy) variable, attributes, and dimension 
     135!> @date October, 2016 
     136!> - allow to choose the number of boundary point with coarse grid value. 
     137!> - dimension to be used select from configuration file 
    132138!> 
    133139!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    208214 
    209215   ! namcfg 
    210    CHARACTER(LEN=lc)                       :: cn_varcfg = 'variable.cfg'  
    211    CHARACTER(LEN=lc)                       :: cn_dumcfg = 'dummy.cfg' 
     216   CHARACTER(LEN=lc)                       :: cn_varcfg = './cfg/variable.cfg'  
     217   CHARACTER(LEN=lc)                       :: cn_dimcfg = './cfg/dimension.cfg' 
     218   CHARACTER(LEN=lc)                       :: cn_dumcfg = './cfg/dummy.cfg' 
    212219 
    213220   ! namcrs 
     
    231238   LOGICAL                                 :: ln_east  = .TRUE. 
    232239   LOGICAL                                 :: ln_west  = .TRUE. 
    233    LOGICAL                                 :: ln_oneseg= .TRUE. 
    234240   CHARACTER(LEN=lc)                       :: cn_north = '' 
    235241   CHARACTER(LEN=lc)                       :: cn_south = '' 
    236242   CHARACTER(LEN=lc)                       :: cn_east  = '' 
    237243   CHARACTER(LEN=lc)                       :: cn_west  = '' 
     244   INTEGER(i4)                             :: in_ncrs  = 2 
     245   LOGICAL                                 :: ln_oneseg= .TRUE. 
    238246 
    239247   ! namout 
     
    248256   NAMELIST /namcfg/ &  !< config namelist 
    249257   &  cn_varcfg, &       !< variable configuration file 
     258   &  cn_dimcfg, &       !< dimension configuration file 
    250259   &  cn_dumcfg          !< dummy configuration file 
    251260 
     
    276285   &  cn_east ,   &     !< east  boundary indices on fine grid 
    277286   &  cn_west ,   &     !< west  boundary indices on fine grid 
     287   &  in_ncrs,    &     !< number of point with coarse value save at boundaries  
    278288   &  ln_oneseg         !< use only one segment for each boundary or not 
    279289 
     
    319329      CALL var_def_extra(TRIM(cn_varcfg)) 
    320330 
     331      ! get dimension allowed 
     332      CALL dim_def_extra(TRIM(cn_dimcfg)) 
     333 
    321334      ! get dummy variable 
    322335      CALL var_get_dummy(TRIM(cn_dumcfg)) 
     
    435448   DO jk=1,ip_ncard 
    436449      CALL merge_bathy_get_boundary(tl_bathy0, tl_bathy1, tl_bdy(jk), & 
    437       &                             il_rho(:),                        & 
     450      &                             il_rho(:), in_ncrs,                      & 
    438451      &                             dl_refined(:,:,:,:), dl_weight(:,:,:,:), & 
    439452      &                             dl_fill) 
     
    621634   DEALLOCATE(dl_weight) 
    622635   CALL boundary_clean(tl_bdy(:)) 
     636   CALL var_clean_extra() 
    623637 
    624638   ! close log file 
     
    638652   !> @param[in] td_bdy          boundary structure 
    639653   !> @param[in] id_rho          array of refinement factor 
     654   !> @param[in] id_ncrs         number of point with coarse value save at boundaries 
    640655   !> @param[inout] dd_refined   array of refined bathymetry  
    641656   !> @param[inout] dd_weight    array of weight 
    642657   !> @param[in] dd_fill         fillValue 
    643658   !> 
    644    !> @todo improve boundary weight function 
    645659   !------------------------------------------------------------------- 
    646660   SUBROUTINE merge_bathy_get_boundary( td_bathy0, td_bathy1, td_bdy, & 
    647    &                                    id_rho,                       & 
     661   &                                    id_rho, id_ncrs,              & 
    648662   &                                    dd_refined, dd_weight, dd_fill ) 
    649663 
     
    655669      TYPE(TBDY)                     , INTENT(IN   ) :: td_bdy 
    656670      INTEGER(i4), DIMENSION(:)      , INTENT(IN   ) :: id_rho 
     671      INTEGER(i4)                    , INTENT(IN   ) :: id_ncrs 
    657672      REAL(dp)   , DIMENSION(:,:,:,:), INTENT(INOUT) :: dd_refined 
    658673      REAL(dp)   , DIMENSION(:,:,:,:), INTENT(INOUT) :: dd_weight 
     
    670685      INTEGER(i4) :: il_jmax0 
    671686 
     687      INTEGER(i4) :: il_width 
     688 
    672689      INTEGER(i4), DIMENSION(2,2)         :: il_offset 
    673690      INTEGER(i4), DIMENSION(2,2)         :: il_ind 
     
    838855            CASE('north') 
    839856 
    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  
     857 
     858               ! save n coarse point 
     859               il_width=td_bdy%t_seg(jl)%i_width-id_ncrs 
    848860               ! compute "distance" 
    849                dl_tmp1d(:)=(/(ji-1,ji=td_bdy%t_seg(jl)%i_width-1,1,-1),0/) 
     861               dl_tmp1d(:)=(/(ji,ji=il_width,1,-1),(0,ji=1,id_ncrs)/) 
    850862 
    851863               ! compute weight on segment 
    852864               dl_tmp1d(:)= 0.5 + 0.5*COS( (dp_pi*dl_tmp1d(:)) / & 
    853                &                           (td_bdy%t_seg(jl)%i_width) ) 
     865               &                           (il_width) ) 
     866 
    854867 
    855868               ALLOCATE( dl_wseg(tl_dom1%t_dim(1)%i_len, & 
     
    862875            CASE('south') 
    863876 
     877               ! save n coarse point 
     878               il_width=td_bdy%t_seg(jl)%i_width-id_ncrs 
    864879               ! compute "distance" 
    865                dl_tmp1d(:)=(/0,(ji-1,ji=1,td_bdy%t_seg(jl)%i_width-1)/)                
     880               dl_tmp1d(:)=(/(0,ji=1,id_ncrs),(ji,ji=1,il_width)/) 
    866881 
    867882               ! compute weight on segment 
    868883               dl_tmp1d(:)= 0.5 + 0.5*COS( (dp_pi*dl_tmp1d(:)) / & 
    869                &                           (td_bdy%t_seg(jl)%i_width) ) 
     884               &                           (il_width) ) 
     885 
    870886 
    871887               ALLOCATE( dl_wseg(tl_dom1%t_dim(1)%i_len, & 
     
    878894            CASE('east') 
    879895 
     896               ! save n coarse point 
     897               il_width=td_bdy%t_seg(jl)%i_width-id_ncrs 
    880898               ! compute "distance" 
    881                dl_tmp1d(:)=(/(ji-1,ji=td_bdy%t_seg(jl)%i_width-1,1,-1),0/) 
     899               dl_tmp1d(:)=(/(ji,ji=il_width,1,-1),(0,ji=1,id_ncrs)/) 
    882900 
    883901               ! compute weight on segment 
    884902               dl_tmp1d(:)= 0.5 + 0.5*COS( (dp_pi*dl_tmp1d(:)) / & 
    885                &                           (td_bdy%t_seg(jl)%i_width) ) 
     903               &                           (il_width) ) 
     904 
    886905 
    887906               ALLOCATE( dl_wseg(tl_dom1%t_dim(1)%i_len, & 
     
    894913            CASE('west') 
    895914 
     915               ! save n coarse point 
     916               il_width=td_bdy%t_seg(jl)%i_width-id_ncrs 
    896917               ! compute "distance" 
    897                dl_tmp1d(:)=(/0,(ji-1,ji=1,td_bdy%t_seg(jl)%i_width-1)/)                
     918               dl_tmp1d(:)=(/(0,ji=1,id_ncrs),(ji,ji=1,il_width)/) 
    898919 
    899920               ! compute weight on segment 
    900921               dl_tmp1d(:)= 0.5 + 0.5*COS( (dp_pi*dl_tmp1d(:)) / & 
    901                &                           (td_bdy%t_seg(jl)%i_width) ) 
     922               &                           (il_width) ) 
     923 
    902924 
    903925               ALLOCATE( dl_wseg(tl_dom1%t_dim(1)%i_len, & 
Note: See TracChangeset for help on using the changeset viewer.