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 6440 for branches/UKMO/dev_r5518_GC3p0_package/NEMOGCM/TOOLS/SIREN/src/merge_bathy.f90 – NEMO

Ignore:
Timestamp:
2016-04-07T16:32:24+02:00 (8 years ago)
Author:
dancopsey
Message:

Merged in nemo_v3_6_STABLE_copy up to revision 6436.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_GC3p0_package/NEMOGCM/TOOLS/SIREN/src/merge_bathy.f90

    r5037 r6440  
    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] 
     
    2829!> @endcode 
    2930!>     
    30 !>    merge_bathy.nam comprise 8 namelists: 
     31!> @note  
     32!>    you could find a template of the namelist in templates directory. 
     33!> 
     34!>    merge_bathy.nam contains 7 namelists: 
    3135!>       - logger namelist (namlog) 
    3236!>       - config namelist (namcfg) 
    3337!>       - coarse grid namelist (namcrs) 
    3438!>       - fine grid namelist (namfin) 
    35 !>       - variable namelist (namvar) 
     39!       - variable namelist (namvar) 
    3640!>       - nesting namelist (namnst) 
    3741!>       - boundary namelist (nambdy) 
    3842!>       - output namelist (namout) 
    3943!>  
    40 !>    @note  
    41 !>       All namelists have to be in file merge_bathy.nam,  
    42 !>       however variables of those namelists are all optional. 
    43 !> 
    4444!>    * _logger namelist (namlog)_: 
    4545!>       - cn_logfile   : logger filename 
    4646!>       - cn_verbosity : verbosity ('trace','debug','info', 
    47 !>  'warning','error','fatal') 
     47!>  'warning','error','fatal','none') 
    4848!>       - in_maxerror  : maximum number of error allowed 
    4949!> 
    5050!>    * _config namelist (namcfg)_: 
    51 !>       - 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). 
    5255!> 
    5356!>    * _coarse grid namelist (namcrs)_: 
     
    6063!>       - in_perio1 : NEMO periodicity index 
    6164!> 
    62 !>    * _variable namelist (namvar)_: 
    63 !>       - cn_varinfo : list of variable and extra information about request(s)  
    64 !>       to be used.<br/> 
    65 !>          each elements of *cn_varinfo* is a string character.<br/> 
    66 !>          it is composed of the variable name follow by ':',  
    67 !>          then request(s) to be used on this variable.<br/>  
    68 !>          request could be: 
    69 !>             - interpolation method 
    70 !>  
    71 !>                requests must be separated by ';'.<br/> 
    72 !>                order of requests does not matter.<br/> 
    73 !> 
    74 !>          informations about available method could be find in  
    75 !>          @ref interp modules.<br/> 
    76 !>          Example: 'bathymetry: cubic' 
    77 !>          @note  
    78 !>             If you do not specify a method which is required,  
    79 !>             default one is apply. 
    80 !>          @warning  
    81 !>             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. 
    8285!> 
    8386!>    * _nesting namelist (namnst)_: 
     
    9598!>          segments are separated by '|'.<br/> 
    9699!>          each segments of the boundary is composed of: 
    97 !>             - orthogonal indice (.ie. for north boundary, 
    98 !>             J-indice where boundary are).  
    99 !>             - first indice of boundary (I-indice for north boundary)  
    100 !>             - last  indice of boundary (I-indice for north boundary)<br/> 
    101 !>                indices must be separated by ',' .<br/> 
     100!>             - indice of velocity (orthogonal to boundary .ie.  
     101!>                for north boundary, J-indice).  
     102!>             - indice of segment start (I-indice for north boundary)  
     103!>             - indice of segment end  (I-indice for north boundary)<br/> 
     104!>                indices must be separated by ':' .<br/> 
    102105!>             - optionally, boundary size could be added between '(' and ')'  
    103106!>             in the first segment defined. 
     
    106109!> 
    107110!>          Examples: 
    108 !>             - cn_north='index1,first1,last1(width)' 
    109 !>             - cn_north='index1(width),first1,last1|index2,first2,last2' 
     111!>             - cn_north='index1,first1:last1(width)' 
     112!>             - cn_north='index1(width),first1:last1|index2,first2:last2' 
     113!> 
    110114!>       - cn_south : south boundary indices on fine grid<br/> 
    111115!>       - cn_east  : east  boundary indices on fine grid<br/> 
     
    121125!> @date Sepember, 2014  
    122126!> - add header for user 
     127!> @date July, 2015  
     128!> - extrapolate all land points 
     129!> - add attributes with boundary string character (as in namelist) 
     130!> @date September, 2015 
     131!> - manage useless (dummy) variable, attributes, and dimension 
    123132!> 
    124133!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    153162   CHARACTER(LEN=lc)                                  :: cl_namelist 
    154163   CHARACTER(LEN=lc)                                  :: cl_date 
     164   CHARACTER(LEN=lc)                                  :: cl_tmp 
    155165 
    156166   INTEGER(i4)                                        :: il_narg 
     
    162172   INTEGER(i4)                                        :: il_jmin0 
    163173   INTEGER(i4)                                        :: il_jmax0 
     174   INTEGER(i4)                                        :: il_shift 
    164175   INTEGER(i4)      , DIMENSION(ip_maxdim)            :: il_rho 
    165176   INTEGER(i4)      , DIMENSION(2,2)                  :: il_ind 
     
    198209   ! namcfg 
    199210   CHARACTER(LEN=lc)                       :: cn_varcfg = 'variable.cfg'  
     211   CHARACTER(LEN=lc)                       :: cn_dumcfg = 'dummy.cfg' 
    200212 
    201213   ! namcrs 
     
    207219   INTEGER(i4)                             :: in_perio1 = -1 
    208220 
    209    ! namvar 
    210    CHARACTER(LEN=lc), DIMENSION(ip_maxvar) :: cn_varinfo = '' 
     221!   ! namvar 
     222!   CHARACTER(LEN=lc), DIMENSION(ip_maxvar) :: cn_varinfo = '' 
    211223 
    212224   ! namnst 
     
    231243   NAMELIST /namlog/ &  !< logger namelist 
    232244   &  cn_logfile,    &  !< log file 
    233    &  cn_verbosity      !< log verbosity 
     245   &  cn_verbosity,  &  !< log verbosity 
     246   &  in_maxerror       !< logger maximum error 
    234247 
    235248   NAMELIST /namcfg/ &  !< config namelist 
    236    &  cn_varcfg         !< variable configuration file 
     249   &  cn_varcfg, &       !< variable configuration file 
     250   &  cn_dumcfg          !< dummy configuration file 
    237251 
    238252   NAMELIST /namcrs/ &  !< coarse grid namelist 
     
    244258   &  in_perio1         !< periodicity index 
    245259  
    246    NAMELIST /namvar/ &  !< variable namelist 
    247    &  cn_varinfo        !< list of variable and interpolation  
    248                         !< method to be used.  
    249                         !< (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' )  
    250264    
    251265   NAMELIST /namnst/ &  !< nesting namelist 
     
    298312      READ( il_fileid, NML = namlog ) 
    299313      ! define log file 
    300       CALL logger_open(TRIM(cn_logfile),TRIM(cn_verbosity), in_maxerror) 
     314      CALL logger_open(TRIM(cn_logfile),TRIM(cn_verbosity),in_maxerror) 
    301315      CALL logger_header() 
    302316 
     
    305319      CALL var_def_extra(TRIM(cn_varcfg)) 
    306320 
     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 
    307328      READ( il_fileid, NML = namcrs ) 
    308329      READ( il_fileid, NML = namfin ) 
    309       READ( il_fileid, NML = namvar ) 
    310       ! add user change in extra information 
    311       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) 
    312333 
    313334      READ( il_fileid, NML = namnst ) 
     
    510531   ENDIF 
    511532 
     533 
     534   IF( tl_bdy(jp_north)%l_use )THEN 
     535      ! add shift on north boundary 
     536      ! boundary compute on T point but express on U or V point 
     537      il_shift=1 
     538 
     539      cl_tmp=TRIM(fct_str(tl_bdy(jp_north)%t_seg(1)%i_index-il_shift))//','//& 
     540         &   TRIM(fct_str(tl_bdy(jp_north)%t_seg(1)%i_first))//':'//& 
     541         &   TRIM(fct_str(tl_bdy(jp_north)%t_seg(1)%i_last))//& 
     542         &   '('//TRIM(fct_str(tl_bdy(jp_north)%t_seg(1)%i_width))//')' 
     543      DO ji=2,tl_bdy(jp_north)%i_nseg 
     544         cl_tmp=TRIM(cl_tmp)//'|'//& 
     545            &   TRIM(fct_str(tl_bdy(jp_north)%t_seg(ji)%i_index-il_shift))//','//& 
     546            &   TRIM(fct_str(tl_bdy(jp_north)%t_seg(ji)%i_first))//':'//& 
     547            &   TRIM(fct_str(tl_bdy(jp_north)%t_seg(ji)%i_last)) 
     548      ENDDO 
     549      tl_att=att_init("bdy_north",TRIM(cl_tmp)) 
     550      CALL file_add_att(tl_fileout, tl_att) 
     551   ENDIF 
     552 
     553   IF( tl_bdy(jp_south)%l_use )THEN 
     554       
     555      cl_tmp=TRIM(fct_str(tl_bdy(jp_south)%t_seg(1)%i_index))//','//& 
     556         &   TRIM(fct_str(tl_bdy(jp_south)%t_seg(1)%i_first))//':'//& 
     557         &   TRIM(fct_str(tl_bdy(jp_south)%t_seg(1)%i_last))//& 
     558         &   '('//TRIM(fct_str(tl_bdy(jp_south)%t_seg(1)%i_width))//')' 
     559      DO ji=2,tl_bdy(jp_south)%i_nseg 
     560         cl_tmp=TRIM(cl_tmp)//'|'//& 
     561            &   TRIM(fct_str(tl_bdy(jp_south)%t_seg(ji)%i_index))//','//& 
     562            &   TRIM(fct_str(tl_bdy(jp_south)%t_seg(ji)%i_first))//':'//& 
     563            &   TRIM(fct_str(tl_bdy(jp_south)%t_seg(ji)%i_last)) 
     564      ENDDO 
     565 
     566      tl_att=att_init("bdy_south",TRIM(cl_tmp)) 
     567      CALL file_add_att(tl_fileout, tl_att) 
     568   ENDIF 
     569 
     570   IF( tl_bdy(jp_east)%l_use )THEN 
     571      ! add shift on east boundary 
     572      ! boundary compute on T point but express on U or V point 
     573      il_shift=1 
     574 
     575      cl_tmp=TRIM(fct_str(tl_bdy(jp_east)%t_seg(1)%i_index-il_shift))//','//& 
     576         &   TRIM(fct_str(tl_bdy(jp_east)%t_seg(1)%i_first))//':'//& 
     577         &   TRIM(fct_str(tl_bdy(jp_east)%t_seg(1)%i_last))//& 
     578         &   '('//TRIM(fct_str(tl_bdy(jp_east)%t_seg(1)%i_width))//')' 
     579      DO ji=2,tl_bdy(jp_east)%i_nseg 
     580         cl_tmp=TRIM(cl_tmp)//'|'//& 
     581            &   TRIM(fct_str(tl_bdy(jp_east)%t_seg(ji)%i_index-il_shift))//','//& 
     582            &   TRIM(fct_str(tl_bdy(jp_east)%t_seg(ji)%i_first))//':'//& 
     583            &   TRIM(fct_str(tl_bdy(jp_east)%t_seg(ji)%i_last)) 
     584      ENDDO 
     585 
     586      tl_att=att_init("bdy_east",TRIM(cl_tmp)) 
     587      CALL file_add_att(tl_fileout, tl_att) 
     588   ENDIF 
     589 
     590   IF( tl_bdy(jp_west)%l_use )THEN 
     591 
     592      cl_tmp=TRIM(fct_str(tl_bdy(jp_west)%t_seg(1)%i_index))//','//& 
     593         &   TRIM(fct_str(tl_bdy(jp_west)%t_seg(1)%i_first))//':'//& 
     594         &   TRIM(fct_str(tl_bdy(jp_west)%t_seg(1)%i_last))//& 
     595         &   '('//TRIM(fct_str(tl_bdy(jp_west)%t_seg(1)%i_width))//')' 
     596      DO ji=2,tl_bdy(jp_west)%i_nseg 
     597         cl_tmp=TRIM(cl_tmp)//'|'//& 
     598            &   TRIM(fct_str(tl_bdy(jp_west)%t_seg(ji)%i_index))//','//& 
     599            &   TRIM(fct_str(tl_bdy(jp_west)%t_seg(ji)%i_first))//':'//& 
     600            &   TRIM(fct_str(tl_bdy(jp_west)%t_seg(ji)%i_last)) 
     601      ENDDO 
     602 
     603      tl_att=att_init("bdy_west",TRIM(cl_tmp)) 
     604      CALL file_add_att(tl_fileout, tl_att) 
     605   ENDIF 
     606 
    512607   ! create file 
    513608   CALL iom_create(tl_fileout) 
     
    525620   CALL mpp_clean(tl_bathy0) 
    526621   DEALLOCATE(dl_weight) 
     622   CALL boundary_clean(tl_bdy(:)) 
    527623 
    528624   ! close log file 
     
    545641   !> @param[inout] dd_weight    array of weight 
    546642   !> @param[in] dd_fill         fillValue 
     643   !> 
     644   !> @todo improve boundary weight function 
    547645   !------------------------------------------------------------------- 
    548646   SUBROUTINE merge_bathy_get_boundary( td_bathy0, td_bathy1, td_bdy, & 
     
    605703               il_jmax1=td_bdy%t_seg(jl)%i_index 
    606704 
     705               ! do not used grid point to compute  
     706               ! boundaries indices (cf create_boundary) 
     707               ! as Bathymetry always on T point 
     708 
    607709            CASE('south') 
    608710 
     
    618720               il_jmin1=td_bdy%t_seg(jl)%i_first 
    619721               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 
    620726 
    621727            CASE('west') 
     
    692798            tl_var0=iom_dom_read_var(tl_bathy0,'Bathymetry',tl_dom0) 
    693799 
     800            ! force to use nearest interpolation 
     801            tl_var0%c_interp(1)='nearest' 
     802 
    694803            ! close mpp files 
    695804            CALL iom_dom_close(tl_bathy0) 
     
    729838            CASE('north') 
    730839 
     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 
    731848               ! compute "distance" 
    732                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/) 
    733850 
    734851               ! compute weight on segment 
     
    746863 
    747864               ! compute "distance" 
    748                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)/)                
    749866 
    750867               ! compute weight on segment 
     
    762879 
    763880               ! compute "distance" 
    764                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/) 
    765882 
    766883               ! compute weight on segment 
     
    778895 
    779896               ! compute "distance" 
    780                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)/)                
    781898 
    782899               ! compute weight on segment 
     
    9081025 
    9091026      ! extrapolate variable 
    910       CALL extrap_fill_value( td_var, id_offset=id_offset(:,:), & 
    911       &                               id_rho=id_rho(:),         & 
    912       &                               id_iext=il_iext, id_jext=il_jext ) 
     1027      CALL extrap_fill_value( td_var ) 
    9131028 
    9141029      ! interpolate Bathymetry 
Note: See TracChangeset for help on using the changeset viewer.