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

Ignore:
Timestamp:
2016-11-28T17:04:10+01:00 (7 years ago)
Author:
emanuelaclementi
Message:

ticket #1805 step 3: /2016/dev_INGV_UKMO_2016 aligned to the trunk at revision 7161

File:
1 edited

Legend:

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

    r5609 r7351  
    99!> @file 
    1010!> @brief  
    11 !> This program merge bathymetry file at boundaries. 
     11!> This program merges bathymetry file at boundaries. 
    1212!> 
    1313!> @details 
    1414!> @section sec1 method 
    15 !> Coarse grid Bathymetry is interpolated on fine grid.  
     15!> Coarse grid Bathymetry is interpolated on fine grid  
     16!> (nearest interpolation method is used).   
    1617!> Then fine Bathymetry and refined coarse bathymetry are merged at boundaries.<br/> 
    1718!>    @f[BathyFine= Weight * BathyCoarse + (1-Weight)*BathyFine@f] 
     
    3132!>    you could find a template of the namelist in templates directory. 
    3233!> 
    33 !>    merge_bathy.nam comprise 8 namelists: 
     34!>    merge_bathy.nam contains 7 namelists: 
    3435!>       - logger namelist (namlog) 
    3536!>       - config namelist (namcfg) 
    3637!>       - coarse grid namelist (namcrs) 
    3738!>       - fine grid namelist (namfin) 
    38 !>       - variable namelist (namvar) 
     39!       - variable namelist (namvar) 
    3940!>       - nesting namelist (namnst) 
    4041!>       - boundary namelist (nambdy) 
    4142!>       - output namelist (namout) 
    4243!>  
    43 !>    @note  
    44 !>       All namelists have to be in file merge_bathy.nam,  
    45 !>       however variables of those namelists are all optional. 
    46 !> 
    4744!>    * _logger namelist (namlog)_: 
    4845!>       - cn_logfile   : logger filename 
     
    5249!> 
    5350!>    * _config namelist (namcfg)_: 
    54 !>       - cn_varcfg : variable configuration file (see ./SIREN/cfg/variable.cfg) 
     51!>       - cn_varcfg : variable configuration file  
     52!> (see ./SIREN/cfg/variable.cfg) 
     53!>       - cn_dumcfg : useless (dummy) configuration file, for useless  
     54!> dimension or variable (see ./SIREN/cfg/dummy.cfg). 
    5555!> 
    5656!>    * _coarse grid namelist (namcrs)_: 
     
    6363!>       - in_perio1 : NEMO periodicity index 
    6464!> 
    65 !>    * _variable namelist (namvar)_: 
    66 !>       - cn_varinfo : list of variable and extra information about request(s)  
    67 !>       to be used (separated by ',').<br/> 
    68 !>          each elements of *cn_varinfo* is a string character.<br/> 
    69 !>          it is composed of the variable name follow by ':',  
    70 !>          then request(s) to be used on this variable.<br/>  
    71 !>          request could be: 
    72 !>             - int = interpolation method 
    73 !>  
    74 !>                requests must be separated by ';'.<br/> 
    75 !>                order of requests does not matter.<br/> 
    76 !> 
    77 !>          informations about available method could be find in  
    78 !>          @ref interp modules.<br/> 
    79 !>          Example: 'bathymetry: int=cubic' 
    80 !>          @note  
    81 !>             If you do not specify a method which is required,  
    82 !>             default one is apply. 
    83 !>          @warning  
    84 !>             variable name must be __Bathymetry__ here. 
     65!    * _variable namelist (namvar)_: 
     66!       - cn_varinfo : list of variable and extra information about request(s)  
     67!       to be used (separated by ',').<br/> 
     68!          each elements of *cn_varinfo* is a string character.<br/> 
     69!          it is composed of the variable name follow by ':',  
     70!          then request(s) to be used on this variable.<br/>  
     71!          request could be: 
     72!             - int = interpolation method 
     73!  
     74!                requests must be separated by ';'.<br/> 
     75!                order of requests does not matter.<br/> 
     76! 
     77!          informations about available method could be find in  
     78!          @ref interp modules.<br/> 
     79!          Example: 'bathymetry: int=cubic' 
     80!          @note  
     81!             If you do not specify a method which is required,  
     82!             default one is apply. 
     83!          @warning  
     84!             variable name must be __Bathymetry__ here. 
    8585!> 
    8686!>    * _nesting namelist (namnst)_: 
     
    128128!> - extrapolate all land points 
    129129!> - add attributes with boundary string character (as in namelist) 
     130!> @date September, 2015 
     131!> - manage useless (dummy) variable, attributes, and dimension 
    130132!> 
    131133!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    207209   ! namcfg 
    208210   CHARACTER(LEN=lc)                       :: cn_varcfg = 'variable.cfg'  
     211   CHARACTER(LEN=lc)                       :: cn_dumcfg = 'dummy.cfg' 
    209212 
    210213   ! namcrs 
     
    216219   INTEGER(i4)                             :: in_perio1 = -1 
    217220 
    218    ! namvar 
    219    CHARACTER(LEN=lc), DIMENSION(ip_maxvar) :: cn_varinfo = '' 
     221!   ! namvar 
     222!   CHARACTER(LEN=lc), DIMENSION(ip_maxvar) :: cn_varinfo = '' 
    220223 
    221224   ! namnst 
     
    244247 
    245248   NAMELIST /namcfg/ &  !< config namelist 
    246    &  cn_varcfg         !< variable configuration file 
     249   &  cn_varcfg, &       !< variable configuration file 
     250   &  cn_dumcfg          !< dummy configuration file 
    247251 
    248252   NAMELIST /namcrs/ &  !< coarse grid namelist 
     
    254258   &  in_perio1         !< periodicity index 
    255259  
    256    NAMELIST /namvar/ &  !< variable namelist 
    257    &  cn_varinfo        !< list of variable and interpolation  
    258                         !< method to be used.  
    259                         !< (ex: 'votemper|linear','vosaline|cubic' )  
     260!   NAMELIST /namvar/ &  !< variable namelist 
     261!   &  cn_varinfo        !< list of variable and interpolation  
     262!                        !< method to be used.  
     263!                        !< (ex: 'votemper|linear','vosaline|cubic' )  
    260264    
    261265   NAMELIST /namnst/ &  !< nesting namelist 
     
    315319      CALL var_def_extra(TRIM(cn_varcfg)) 
    316320 
     321      ! get dummy variable 
     322      CALL var_get_dummy(TRIM(cn_dumcfg)) 
     323      ! get dummy dimension 
     324      CALL dim_get_dummy(TRIM(cn_dumcfg)) 
     325      ! get dummy attribute 
     326      CALL att_get_dummy(TRIM(cn_dumcfg)) 
     327 
    317328      READ( il_fileid, NML = namcrs ) 
    318329      READ( il_fileid, NML = namfin ) 
    319       READ( il_fileid, NML = namvar ) 
    320       ! add user change in extra information 
    321       CALL var_chg_extra(cn_varinfo) 
     330!      READ( il_fileid, NML = namvar ) 
     331!      ! add user change in extra information 
     332!      CALL var_chg_extra(cn_varinfo) 
    322333 
    323334      READ( il_fileid, NML = namnst ) 
     
    630641   !> @param[inout] dd_weight    array of weight 
    631642   !> @param[in] dd_fill         fillValue 
     643   !> 
     644   !> @todo improve boundary weight function 
    632645   !------------------------------------------------------------------- 
    633646   SUBROUTINE merge_bathy_get_boundary( td_bathy0, td_bathy1, td_bdy, & 
     
    690703               il_jmax1=td_bdy%t_seg(jl)%i_index 
    691704 
     705               ! do not used grid point to compute  
     706               ! boundaries indices (cf create_boundary) 
     707               ! as Bathymetry always on T point 
     708 
    692709            CASE('south') 
    693710 
     
    703720               il_jmin1=td_bdy%t_seg(jl)%i_first 
    704721               il_jmax1=td_bdy%t_seg(jl)%i_last  
     722 
     723               ! do not used grid point to compute  
     724               ! boundaries indices (cf create_boundary) 
     725               ! as Bathymetry always on T point 
    705726 
    706727            CASE('west') 
     
    777798            tl_var0=iom_dom_read_var(tl_bathy0,'Bathymetry',tl_dom0) 
    778799 
     800            ! force to use nearest interpolation 
     801            tl_var0%c_interp(1)='nearest' 
     802 
    779803            ! close mpp files 
    780804            CALL iom_dom_close(tl_bathy0) 
     
    814838            CASE('north') 
    815839 
     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 
    816848               ! compute "distance" 
    817                dl_tmp1d(:)=(/(ji-1,ji=td_bdy%t_seg(jl)%i_width,1,-1)/) 
     849               dl_tmp1d(:)=(/(ji-1,ji=td_bdy%t_seg(jl)%i_width-1,1,-1),0/) 
    818850 
    819851               ! compute weight on segment 
     
    831863 
    832864               ! compute "distance" 
    833                dl_tmp1d(:)=(/(ji-1,ji=1,td_bdy%t_seg(jl)%i_width)/)                
     865               dl_tmp1d(:)=(/0,(ji-1,ji=1,td_bdy%t_seg(jl)%i_width-1)/)                
    834866 
    835867               ! compute weight on segment 
     
    847879 
    848880               ! compute "distance" 
    849                dl_tmp1d(:)=(/(ji-1,ji=td_bdy%t_seg(jl)%i_width,1,-1)/) 
     881               dl_tmp1d(:)=(/(ji-1,ji=td_bdy%t_seg(jl)%i_width-1,1,-1),0/) 
    850882 
    851883               ! compute weight on segment 
     
    863895 
    864896               ! compute "distance" 
    865                dl_tmp1d(:)=(/(ji-1,ji=1,td_bdy%t_seg(jl)%i_width)/)                
     897               dl_tmp1d(:)=(/0,(ji-1,ji=1,td_bdy%t_seg(jl)%i_width-1)/)                
    866898 
    867899               ! compute weight on segment 
Note: See TracChangeset for help on using the changeset viewer.