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

Ignore:
Timestamp:
2018-10-29T15:20:26+01:00 (5 years ago)
Author:
kingr
Message:

Rolled back to r10247 - i.e., undid merge of pkg br and 3.6_stable br

File:
1 edited

Legend:

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

    r10248 r10251  
    2828!> @endcode 
    2929!>     
    30 !> @note  
    31 !>    you could find a template of the namelist in templates directory. 
    32 !> 
    3330!>    merge_bathy.nam comprise 8 namelists: 
    3431!>       - logger namelist (namlog) 
     
    4845!>       - cn_logfile   : logger filename 
    4946!>       - cn_verbosity : verbosity ('trace','debug','info', 
    50 !>  'warning','error','fatal','none') 
     47!>  'warning','error','fatal') 
    5148!>       - in_maxerror  : maximum number of error allowed 
    5249!> 
     
    6562!>    * _variable namelist (namvar)_: 
    6663!>       - cn_varinfo : list of variable and extra information about request(s)  
    67 !>       to be used (separated by ',').<br/> 
     64!>       to be used.<br/> 
    6865!>          each elements of *cn_varinfo* is a string character.<br/> 
    6966!>          it is composed of the variable name follow by ':',  
    7067!>          then request(s) to be used on this variable.<br/>  
    7168!>          request could be: 
    72 !>             - int = interpolation method 
     69!>             - interpolation method 
    7370!>  
    7471!>                requests must be separated by ';'.<br/> 
     
    7774!>          informations about available method could be find in  
    7875!>          @ref interp modules.<br/> 
    79 !>          Example: 'bathymetry: int=cubic' 
     76!>          Example: 'bathymetry: cubic' 
    8077!>          @note  
    8178!>             If you do not specify a method which is required,  
     
    9895!>          segments are separated by '|'.<br/> 
    9996!>          each segments of the boundary is composed of: 
    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/> 
     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/> 
    105102!>             - optionally, boundary size could be added between '(' and ')'  
    106103!>             in the first segment defined. 
     
    109106!> 
    110107!>          Examples: 
    111 !>             - cn_north='index1,first1:last1(width)' 
    112 !>             - cn_north='index1(width),first1:last1|index2,first2:last2' 
    113 !> 
     108!>             - cn_north='index1,first1,last1(width)' 
     109!>             - cn_north='index1(width),first1,last1|index2,first2,last2' 
    114110!>       - cn_south : south boundary indices on fine grid<br/> 
    115111!>       - cn_east  : east  boundary indices on fine grid<br/> 
     
    125121!> @date Sepember, 2014  
    126122!> - add header for user 
    127 !> @date July, 2015  
    128 !> - extrapolate all land points 
    129 !> - add attributes with boundary string character (as in namelist) 
    130123!> 
    131124!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    160153   CHARACTER(LEN=lc)                                  :: cl_namelist 
    161154   CHARACTER(LEN=lc)                                  :: cl_date 
    162    CHARACTER(LEN=lc)                                  :: cl_tmp 
    163155 
    164156   INTEGER(i4)                                        :: il_narg 
     
    170162   INTEGER(i4)                                        :: il_jmin0 
    171163   INTEGER(i4)                                        :: il_jmax0 
    172    INTEGER(i4)                                        :: il_shift 
    173164   INTEGER(i4)      , DIMENSION(ip_maxdim)            :: il_rho 
    174165   INTEGER(i4)      , DIMENSION(2,2)                  :: il_ind 
     
    240231   NAMELIST /namlog/ &  !< logger namelist 
    241232   &  cn_logfile,    &  !< log file 
    242    &  cn_verbosity,  &  !< log verbosity 
    243    &  in_maxerror       !< logger maximum error 
     233   &  cn_verbosity      !< log verbosity 
    244234 
    245235   NAMELIST /namcfg/ &  !< config namelist 
     
    308298      READ( il_fileid, NML = namlog ) 
    309299      ! define log file 
    310       CALL logger_open(TRIM(cn_logfile),TRIM(cn_verbosity),in_maxerror) 
     300      CALL logger_open(TRIM(cn_logfile),TRIM(cn_verbosity), in_maxerror) 
    311301      CALL logger_header() 
    312302 
     
    520510   ENDIF 
    521511 
    522  
    523    IF( tl_bdy(jp_north)%l_use )THEN 
    524       ! add shift on north boundary 
    525       ! boundary compute on T point but express on U or V point 
    526       il_shift=1 
    527  
    528       cl_tmp=TRIM(fct_str(tl_bdy(jp_north)%t_seg(1)%i_index-il_shift))//','//& 
    529          &   TRIM(fct_str(tl_bdy(jp_north)%t_seg(1)%i_first))//':'//& 
    530          &   TRIM(fct_str(tl_bdy(jp_north)%t_seg(1)%i_last))//& 
    531          &   '('//TRIM(fct_str(tl_bdy(jp_north)%t_seg(1)%i_width))//')' 
    532       DO ji=2,tl_bdy(jp_north)%i_nseg 
    533          cl_tmp=TRIM(cl_tmp)//'|'//& 
    534             &   TRIM(fct_str(tl_bdy(jp_north)%t_seg(ji)%i_index-il_shift))//','//& 
    535             &   TRIM(fct_str(tl_bdy(jp_north)%t_seg(ji)%i_first))//':'//& 
    536             &   TRIM(fct_str(tl_bdy(jp_north)%t_seg(ji)%i_last)) 
    537       ENDDO 
    538       tl_att=att_init("bdy_north",TRIM(cl_tmp)) 
    539       CALL file_add_att(tl_fileout, tl_att) 
    540    ENDIF 
    541  
    542    IF( tl_bdy(jp_south)%l_use )THEN 
    543        
    544       cl_tmp=TRIM(fct_str(tl_bdy(jp_south)%t_seg(1)%i_index))//','//& 
    545          &   TRIM(fct_str(tl_bdy(jp_south)%t_seg(1)%i_first))//':'//& 
    546          &   TRIM(fct_str(tl_bdy(jp_south)%t_seg(1)%i_last))//& 
    547          &   '('//TRIM(fct_str(tl_bdy(jp_south)%t_seg(1)%i_width))//')' 
    548       DO ji=2,tl_bdy(jp_south)%i_nseg 
    549          cl_tmp=TRIM(cl_tmp)//'|'//& 
    550             &   TRIM(fct_str(tl_bdy(jp_south)%t_seg(ji)%i_index))//','//& 
    551             &   TRIM(fct_str(tl_bdy(jp_south)%t_seg(ji)%i_first))//':'//& 
    552             &   TRIM(fct_str(tl_bdy(jp_south)%t_seg(ji)%i_last)) 
    553       ENDDO 
    554  
    555       tl_att=att_init("bdy_south",TRIM(cl_tmp)) 
    556       CALL file_add_att(tl_fileout, tl_att) 
    557    ENDIF 
    558  
    559    IF( tl_bdy(jp_east)%l_use )THEN 
    560       ! add shift on east boundary 
    561       ! boundary compute on T point but express on U or V point 
    562       il_shift=1 
    563  
    564       cl_tmp=TRIM(fct_str(tl_bdy(jp_east)%t_seg(1)%i_index-il_shift))//','//& 
    565          &   TRIM(fct_str(tl_bdy(jp_east)%t_seg(1)%i_first))//':'//& 
    566          &   TRIM(fct_str(tl_bdy(jp_east)%t_seg(1)%i_last))//& 
    567          &   '('//TRIM(fct_str(tl_bdy(jp_east)%t_seg(1)%i_width))//')' 
    568       DO ji=2,tl_bdy(jp_east)%i_nseg 
    569          cl_tmp=TRIM(cl_tmp)//'|'//& 
    570             &   TRIM(fct_str(tl_bdy(jp_east)%t_seg(ji)%i_index-il_shift))//','//& 
    571             &   TRIM(fct_str(tl_bdy(jp_east)%t_seg(ji)%i_first))//':'//& 
    572             &   TRIM(fct_str(tl_bdy(jp_east)%t_seg(ji)%i_last)) 
    573       ENDDO 
    574  
    575       tl_att=att_init("bdy_east",TRIM(cl_tmp)) 
    576       CALL file_add_att(tl_fileout, tl_att) 
    577    ENDIF 
    578  
    579    IF( tl_bdy(jp_west)%l_use )THEN 
    580  
    581       cl_tmp=TRIM(fct_str(tl_bdy(jp_west)%t_seg(1)%i_index))//','//& 
    582          &   TRIM(fct_str(tl_bdy(jp_west)%t_seg(1)%i_first))//':'//& 
    583          &   TRIM(fct_str(tl_bdy(jp_west)%t_seg(1)%i_last))//& 
    584          &   '('//TRIM(fct_str(tl_bdy(jp_west)%t_seg(1)%i_width))//')' 
    585       DO ji=2,tl_bdy(jp_west)%i_nseg 
    586          cl_tmp=TRIM(cl_tmp)//'|'//& 
    587             &   TRIM(fct_str(tl_bdy(jp_west)%t_seg(ji)%i_index))//','//& 
    588             &   TRIM(fct_str(tl_bdy(jp_west)%t_seg(ji)%i_first))//':'//& 
    589             &   TRIM(fct_str(tl_bdy(jp_west)%t_seg(ji)%i_last)) 
    590       ENDDO 
    591  
    592       tl_att=att_init("bdy_west",TRIM(cl_tmp)) 
    593       CALL file_add_att(tl_fileout, tl_att) 
    594    ENDIF 
    595  
    596512   ! create file 
    597513   CALL iom_create(tl_fileout) 
     
    609525   CALL mpp_clean(tl_bathy0) 
    610526   DEALLOCATE(dl_weight) 
    611    CALL boundary_clean(tl_bdy(:)) 
    612527 
    613528   ! close log file 
     
    993908 
    994909      ! extrapolate variable 
    995       CALL extrap_fill_value( td_var ) 
     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 ) 
    996913 
    997914      ! interpolate Bathymetry 
Note: See TracChangeset for help on using the changeset viewer.