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 12080 for utils/tools/SIREN/src/merge_bathy.f90 – NEMO

Ignore:
Timestamp:
2019-12-06T10:30:14+01:00 (4 years ago)
Author:
jpaul
Message:

update nemo trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • utils/tools/SIREN/src/merge_bathy.f90

    r9598 r12080  
    33!---------------------------------------------------------------------- 
    44! 
    5 ! 
    6 ! PROGRAM: merge_bathy 
    7 ! 
    85! DESCRIPTION: 
    96!> @file 
    107!> @brief  
    11 !> This program merges bathymetry file at boundaries. 
     8!> this program merges bathymetry file at boundaries. 
    129!> 
    1310!> @details 
    1411!> @section sec1 method 
    15 !> Coarse grid Bathymetry is interpolated on fine grid  
    16 !> (nearest interpolation method is used).   
    17 !> Then fine Bathymetry and refined coarse bathymetry are merged at boundaries.<br/> 
     12!> coarse grid bathymetry is interpolated on fine grid  
     13!> (nearest interpolation method is used).<br/>   
     14!> then fine bathymetry and refined coarse bathymetry are merged at boundaries.<br/> 
    1815!>    @f[BathyFine= Weight * BathyCoarse + (1-Weight)*BathyFine@f] 
    19 !> The weight function used is :<br/> 
     16!> the weight function used is :<br/> 
    2017!>       @f[Weight = 0.5 + 0.5*COS( \frac{\pi*dist}{width} )@f]<br/> 
    2118!> with 
     
    2421!> 
    2522!> @section sec2 how to 
    26 !>    to merge bathymetry file:<br/> 
    27 !> @code{.sh} 
    28 !>    ./SIREN/bin/merge_bathy merge_bathy.nam 
    29 !> @endcode 
    30 !>     
    31 !> @note  
    32 !>    you could find a template of the namelist in templates directory. 
    33 !> 
     23!> USAGE: merge_bathy merge_bathy.nam [-v] [-h]<br/> 
     24!>    - positional arguments:<br/> 
     25!>       - merge_bathy.nam<br/> 
     26!>          namelist of merge_bathy 
     27!>          @note 
     28!>             a template of the namelist could be created running (in templates directory): 
     29!>             @code{.sh} 
     30!>                python create_templates.py merge_bathy 
     31!>             @endcode 
     32!> 
     33!>    - optional arguments:<br/> 
     34!>       - -h, --help<br/> 
     35!>          show this help message (and exit)<br/> 
     36!>       - -v, --version<br/> 
     37!>          show Siren's version   (and exit) 
     38!> 
     39!> @section sec_merge merge_bathy.nam 
    3440!>    merge_bathy.nam contains 7 namelists: 
    35 !>       - logger namelist (namlog) 
    36 !>       - config namelist (namcfg) 
    37 !>       - coarse grid namelist (namcrs) 
    38 !>       - fine grid namelist (namfin) 
    39 !       - variable namelist (namvar) 
    40 !>       - nesting namelist (namnst) 
    41 !>       - boundary namelist (nambdy) 
    42 !>       - output namelist (namout) 
    43 !>  
    44 !>    * _logger namelist (namlog)_: 
    45 !>       - cn_logfile   : logger filename 
    46 !>       - cn_verbosity : verbosity ('trace','debug','info', 
    47 !>  'warning','error','fatal','none') 
    48 !>       - in_maxerror  : maximum number of error allowed 
    49 !> 
    50 !>    * _config namelist (namcfg)_: 
    51 !>       - cn_varcfg : variable configuration file  
    52 !> (see ./SIREN/cfg/variable.cfg) 
    53 !>       - cn_dimcfg : dimension configuration file. define dimensions allowed 
    54 !> (see ./SIREN/cfg/dimension.cfg). 
    55 !>       - cn_dumcfg : useless (dummy) configuration file, for useless  
    56 !> dimension or variable (see ./SIREN/cfg/dummy.cfg). 
    57 !> 
    58 !>    * _coarse grid namelist (namcrs)_: 
    59 !>       - cn_bathy0 : bathymetry file 
    60 !>       - in_perio0 : NEMO periodicity index (see Model Boundary Condition in 
    61 !> [NEMO documentation](http://www.nemo-ocean.eu/About-NEMO/Reference-manuals)) 
    62 !> 
    63 !>    * _fine grid namelist (namfin)_: 
    64 !>       - cn_bathy1 : bathymetry file 
    65 !>       - in_perio1 : NEMO periodicity index 
    66 !> 
    67 !    * _variable namelist (namvar)_: 
    68 !       - cn_varinfo : list of variable and extra information about request(s)  
    69 !       to be used (separated by ',').<br/> 
    70 !          each elements of *cn_varinfo* is a string character.<br/> 
    71 !          it is composed of the variable name follow by ':',  
    72 !          then request(s) to be used on this variable.<br/>  
    73 !          request could be: 
    74 !             - int = interpolation method 
    75 !  
    76 !                requests must be separated by ';'.<br/> 
    77 !                order of requests does not matter.<br/> 
    78 ! 
    79 !          informations about available method could be find in  
    80 !          @ref interp modules.<br/> 
    81 !          Example: 'bathymetry: int=cubic' 
    82 !          @note  
    83 !             If you do not specify a method which is required,  
    84 !             default one is apply. 
    85 !          @warning  
    86 !             variable name must be __Bathymetry__ here. 
    87 !> 
    88 !>    * _nesting namelist (namnst)_: 
    89 !>       - in_rhoi  : refinement factor in i-direction 
    90 !>       - in_rhoj  : refinement factor in j-direction 
    91 !> 
    92 !>    * _boundary namelist (nambdy)_: 
    93 !>       - ln_north : use north boundary or not 
    94 !>       - ln_south : use south boundary or not 
    95 !>       - ln_east  : use east  boundary or not 
    96 !>       - ln_west  : use west  boundary or not 
    97 !>       - cn_north : north boundary indices on fine grid<br/> 
    98 !>          *cn_north* is a string character defining boundary 
    99 !>          segmentation.<br/> 
    100 !>          segments are separated by '|'.<br/> 
    101 !>          each segments of the boundary is composed of: 
    102 !>             - indice of velocity (orthogonal to boundary .ie.  
    103 !>                for north boundary, J-indice).  
    104 !>             - indice of segment start (I-indice for north boundary)  
    105 !>             - indice of segment end   (I-indice for north boundary)<br/> 
    106 !>                indices must be separated by ':' .<br/> 
    107 !>             - optionally, boundary size could be added between '(' and ')'  
    108 !>             in the first segment defined. 
    109 !>                @note  
    110 !>                   boundary size is the same for all segments of one boundary. 
    111 !> 
    112 !>          Examples: 
    113 !>             - cn_north='index1,first1:last1(width)' 
    114 !>             - cn_north='index1(width),first1:last1|index2,first2:last2' 
    115 !> 
    116 !>       - cn_south : south boundary indices on fine grid<br/> 
    117 !>       - cn_east  : east  boundary indices on fine grid<br/> 
    118 !>       - cn_west  : west  boundary indices on fine grid<br/> 
    119 !>       - in_ncrs  : number of point(s) with coarse value save at boundaries<br/> 
    120 !>       - ln_oneseg: use only one segment for each boundary or not 
    121 !> 
    122 !>    * _output namelist (namout)_: 
    123 !>       - cn_fileout : merged bathymetry file 
    124 !> 
     41!>       - **namlog** to set logger parameters 
     42!>       - **namcfg** to set configuration file parameters 
     43!>       - **namsrc** to set source/coarse grid parameters 
     44!>       - **namtgt** to set target/fine grid parameters 
     45!>       - **namnst** to set sub domain and nesting paramters 
     46!>       - **nambdy** to set boundary parameters 
     47!>       - **namout** to set output parameters 
     48!> 
     49!>    here after, each sub-namelist parameters is detailed. 
     50!>    @note  
     51!>       default values are specified between brackets 
     52!> 
     53!> @subsection sublog namlog 
     54!>    the logger sub-namelist parameters are : 
     55!> 
     56!>    - **cn_logfile** [@a merge_bathy.log]<br/> 
     57!>       logger filename 
     58!> 
     59!>    - **cn_verbosity** [@a warning]<br/> 
     60!>       verbosity level, choose between : 
     61!>          - trace 
     62!>          - debug 
     63!>          - info 
     64!>          - warning 
     65!>          - error 
     66!>          - fatal 
     67!>          - none 
     68!> 
     69!>    - **in_maxerror** [@a 5]<br/>  
     70!>       maximum number of error allowed 
     71!> 
     72!> @subsection subcfg namcfg 
     73!>    the configuration sub-namelist parameters are :  
     74!> 
     75!>    - **cn_varcfg** [@a ./cfg/variable.cfg]<br/> 
     76!>       path to the variable configuration file.<br/> 
     77!>       the variable configuration file defines standard name,  
     78!>       default interpolation method, axis,...  
     79!>       to be used for some known variables.<br/>  
     80!> 
     81!>    - **cn_dimcfg** [@a ./cfg/dimension.cfg]<br/>  
     82!>       path to the dimension configuration file.<br/>  
     83!>       the dimension configuration file defines dimensions allowed.<br/>  
     84!> 
     85!>    - **cn_dumcfg** [@a ./cfg/dummy.cfg]<br/>  
     86!>       path to the useless (dummy) configuration file.<br/> 
     87!>       the dummy configuration file defines useless  
     88!>       dimension or variable. these dimension(s) or variable(s) will not be 
     89!>       processed.<br/> 
     90!> 
     91!> @subsection subsrc namsrc  
     92!>    the source/coarse grid sub-namelist parameters are : 
     93!> 
     94!>    - **cn_bathy0** [@a ]<br/>  
     95!>       path to the bathymetry file 
     96!>       @warning  
     97!>          variable name must be __Bathymetry__ here. 
     98!> 
     99!>    - **in_perio0** [@a ]<br/>  
     100!>       NEMO periodicity index<br/>  
     101!>       the NEMO periodicity could be choose between 0 to 6: 
     102!>       <dl> 
     103!>          <dt>in_perio=0</dt> 
     104!>          <dd>standard regional model</dd> 
     105!>          <dt>in_perio=1</dt> 
     106!>          <dd>east-west cyclic model</dd> 
     107!>          <dt>in_perio=2</dt> 
     108!>          <dd>model with symmetric boundary condition across the equator</dd> 
     109!>          <dt>in_perio=3</dt> 
     110!>          <dd>regional model with North fold boundary and T-point pivot</dd> 
     111!>          <dt>in_perio=4</dt> 
     112!>          <dd>global model with a T-point pivot.<br/> 
     113!>          example: ORCA2, ORCA025, ORCA12</dd> 
     114!>          <dt>in_perio=5</dt> 
     115!>          <dd>regional model with North fold boundary and F-point pivot</dd> 
     116!>          <dt>in_perio=6</dt> 
     117!>          <dd>global model with a F-point pivot<br/> 
     118!>          example: ORCA05</dd> 
     119!>          </dd> 
     120!>       </dl> 
     121!>       @sa For more information see @ref md_src_docsrc_6_perio 
     122!>       and Model Boundary Condition paragraph in the  
     123!>       [NEMO documentation](https://forge.ipsl.jussieu.fr/nemo/chrome/site/doc/NEMO/manual/pdf/NEMO_manual.pdf) 
     124!> 
     125!> @subsection subtgt namtgt  
     126!>    the target/fine grid sub-namelist parameters are : 
     127!> 
     128!>    - **cn_bathy1** [@a ]<br/>  
     129!>       path to bathymetry file 
     130!>       @warning  
     131!>          variable name must be __Bathymetry__ here. 
     132!> 
     133!>    - **in_perio1** [@a ]<br/> 
     134!>       NEMO periodicity index (see above) 
     135!>    @note if the fine/target coordinates file (cn_coord1) was created by SIREN, you do 
     136!>    not need to fill this parameter. SIREN will read it on the global attributes of 
     137!>    the coordinates file. 
     138!> 
     139!> @subsection subnst namnst  
     140!>    the nesting sub-namelist parameters are (default value are specified between brackets): 
     141!>    - **in_rhoi**  [@a 1]<br/>  
     142!>       refinement factor in i-direction 
     143!> 
     144!>    - **in_rhoj**  [@a 1]<br/>  
     145!>       refinement factor in j-direction 
     146!> 
     147!>    @note  
     148!>       coarse grid indices will be deduced from fine grid 
     149!>       coordinate file. 
     150!> 
     151!> @subsection subbdy nambdy 
     152!>    the boundary sub-namelist parameters are : 
     153!> 
     154!>    - **ln_north** [@a .TRUE.]<br/>  
     155!>       logical to use north boundary or not 
     156!>    - **ln_south** [@a .TRUE.]<br/> 
     157!>       logical to use south boundary or not 
     158!>    - **ln_east**  [@a .TRUE.]<br/> 
     159!>       logical to use east boundary or not 
     160!>    - **ln_west**  [@a .TRUE.]<br/> 
     161!>       logical to use west  boundary or not 
     162!>    <br/> <br/> 
     163!>    - **cn_north** [@a ]<br/> 
     164!>       north boundary indices on fine grid<br/> 
     165!>    - **cn_south** [@a ]<br/> 
     166!>       south boundary indices on fine grid<br/> 
     167!>    - **cn_east**  [@a ]<br/> 
     168!>       east  boundary indices on fine grid<br/> 
     169!>    - **cn_west**  [@a ]<br/> 
     170!>       west  boundary indices on fine grid<br/> 
     171!> 
     172!>       *cn_north* is a string character defining boundary 
     173!>       segmentation.<br/> 
     174!>       segments are separated by '|'.<br/> 
     175!>       each segments of the boundary is composed of: 
     176!>          - indice of velocity (orthogonal to boundary .ie.  
     177!>             for north boundary, J-indice).  
     178!>          - indice of segment start (I-indice for north boundary)  
     179!>          - indice of segment end   (I-indice for north boundary)<br/> 
     180!>             indices must be separated by ':' .<br/> 
     181!>          - optionally, boundary size could be added between '(' and ')'  
     182!>          in the first segment defined. 
     183!>             @note  
     184!>                boundary size is the same for all segments of one boundary. 
     185!> 
     186!>       Examples: 
     187!>          - cn_north='index1,first1:last1(width)' 
     188!>          - cn_north='index1(width),first1:last1|index2,first2:last2' 
     189!> 
     190!>       @image html  boundary_50.png  
     191!>       <center>@image latex boundary_50.png 
     192!>       </center> 
     193!> 
     194!>    - **in_ncrs**  [@a 2]<br/>  
     195!>       number of point(s) with coarse value save at boundaries 
     196!> 
     197!>    - **ln_oneseg** [@a .TRUE.]<br/> 
     198!>       logical to use only one segment for each boundary or not 
     199!> 
     200!> @subsection subout namout  
     201!>    the output sub-namelist parameter is : 
     202!> 
     203!>    - **cn_fileout** [@a bathy_merged.nc]<br/> 
     204!>       output bathymetry filename 
     205!> 
     206!> <hr> 
    125207!> @author J.Paul 
    126 ! REVISION HISTORY: 
     208!> 
    127209!> @date November, 2013 - Initial Version 
    128210!> @date Sepember, 2014  
     
    136218!> - allow to choose the number of boundary point with coarse grid value. 
    137219!> - dimension to be used select from configuration file 
    138 !> 
    139 !> @note Software governed by the CeCILL licence     (./LICENSE) 
     220!> @date January, 2019 
     221!> - add url path to global attributes of output file(s) 
     222!> @date February, 2019 
     223!> - rename sub namelist namcrs to namsrc 
     224!> - rename sub namelist namfin to namtgt 
     225!> @date May, 2019 
     226!> - create and clean file structure to avoid memory leaks 
     227!> @date Ocober, 2019 
     228!> - add help and version optional arguments 
     229!> 
     230!> 
     231!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    140232!---------------------------------------------------------------------- 
    141233PROGRAM merge_bathy 
     
    165257   IMPLICIT NONE 
    166258 
     259   ! parameters 
     260   CHARACTER(LEN=lc), PARAMETER  :: cp_myname = "merge_bathy" 
     261 
    167262   ! local variable 
     263   CHARACTER(LEN=lc)                                  :: cl_arg 
    168264   CHARACTER(LEN=lc)                                  :: cl_namelist 
    169265   CHARACTER(LEN=lc)                                  :: cl_date 
    170266   CHARACTER(LEN=lc)                                  :: cl_tmp 
     267   CHARACTER(LEN=lc)                                  :: cl_url 
     268   CHARACTER(LEN=lc)                                  :: cl_errormsg 
    171269 
    172270   INTEGER(i4)                                        :: il_narg 
     
    190288   TYPE(TMPP)                                         :: tl_bathy0 
    191289   TYPE(TMPP)                                         :: tl_bathy1 
     290 
     291   TYPE(TFILE)                                        :: tl_file 
    192292   TYPE(TFILE)                                        :: tl_fileout 
    193293    
     
    218318   CHARACTER(LEN=lc)                       :: cn_dumcfg = './cfg/dummy.cfg' 
    219319 
    220    ! namcrs 
     320   ! namsrc 
    221321   CHARACTER(LEN=lc)                       :: cn_bathy0 = ''  
    222322   INTEGER(i4)                             :: in_perio0 = -1 
    223323 
    224    ! namfin 
     324   ! namtgt 
    225325   CHARACTER(LEN=lc)                       :: cn_bathy1 = ''  
    226326   INTEGER(i4)                             :: in_perio1 = -1 
     
    230330 
    231331   ! namnst 
    232    INTEGER(i4)                             :: in_rhoi  = 0 
    233    INTEGER(i4)                             :: in_rhoj  = 0 
     332   INTEGER(i4)                             :: in_rhoi  = 1 
     333   INTEGER(i4)                             :: in_rhoj  = 1 
    234334 
    235335   ! nambdy 
     
    249349   !------------------------------------------------------------------- 
    250350 
    251    NAMELIST /namlog/ &  !< logger namelist 
    252    &  cn_logfile,    &  !< log file 
    253    &  cn_verbosity,  &  !< log verbosity 
    254    &  in_maxerror       !< logger maximum error 
    255  
    256    NAMELIST /namcfg/ &  !< config namelist 
     351   NAMELIST /namlog/ &   !< logger namelist 
     352   &  cn_logfile,    &   !< log file 
     353   &  cn_verbosity,  &   !< log verbosity 
     354   &  in_maxerror        !< logger maximum error 
     355 
     356   NAMELIST /namcfg/ &   !< configuration namelist 
    257357   &  cn_varcfg, &       !< variable configuration file 
    258358   &  cn_dimcfg, &       !< dimension configuration file 
    259359   &  cn_dumcfg          !< dummy configuration file 
    260360 
    261    NAMELIST /namcrs/ &  !< coarse grid namelist 
    262    &  cn_bathy0,  &     !< bathymetry file 
    263    &  in_perio0         !< periodicity index 
     361   NAMELIST /namsrc/ &   !< source/coarse grid namelist 
     362   &  cn_bathy0,  &      !< bathymetry file 
     363   &  in_perio0          !< periodicity index 
    264364    
    265    NAMELIST /namfin/ &  !< fine grid namelist 
    266    &  cn_bathy1,     &  !< bathymetry file 
    267    &  in_perio1         !< periodicity index 
     365   NAMELIST /namtgt/ &   !< target/fine grid namelist 
     366   &  cn_bathy1,     &   !< bathymetry file 
     367   &  in_perio1          !< periodicity index 
    268368  
    269369!   NAMELIST /namvar/ &  !< variable namelist 
     
    292392   !------------------------------------------------------------------- 
    293393 
    294    ! namelist 
    295    ! get namelist 
     394   ! 
     395   ! Initialisation 
     396   ! -------------- 
     397   ! 
    296398   il_narg=COMMAND_ARGUMENT_COUNT() !f03 intrinsec 
    297    IF( il_narg/=1 )THEN 
    298       PRINT *,"MERGE BATHY: ERROR. need a namelist" 
    299       STOP 
     399 
     400   ! Traitement des arguments fournis 
     401   ! -------------------------------- 
     402   IF( il_narg /= 1 )THEN 
     403      WRITE(cl_errormsg,*) ' ERROR : one argument is needed ' 
     404      CALL fct_help(cp_myname,cl_errormsg)  
     405      CALL EXIT(1) 
    300406   ELSE 
    301       CALL GET_COMMAND_ARGUMENT(1,cl_namelist) !f03 intrinsec 
    302    ENDIF 
    303     
    304    ! read namelist 
    305    INQUIRE(FILE=TRIM(cl_namelist), EXIST=ll_exist) 
    306    IF( ll_exist )THEN 
    307        
    308       il_fileid=fct_getunit() 
    309  
    310       OPEN( il_fileid, FILE=TRIM(cl_namelist), & 
    311       &                FORM='FORMATTED',       & 
    312       &                ACCESS='SEQUENTIAL',    & 
    313       &                STATUS='OLD',           & 
    314       &                ACTION='READ',          & 
    315       &                IOSTAT=il_status) 
    316       CALL fct_err(il_status) 
    317       IF( il_status /= 0 )THEN 
    318          PRINT *,"MERGE BATHY: ERROR opening "//TRIM(cl_namelist) 
    319          STOP 
    320       ENDIF 
    321  
    322       READ( il_fileid, NML = namlog ) 
    323       ! define log file 
    324       CALL logger_open(TRIM(cn_logfile),TRIM(cn_verbosity),in_maxerror) 
    325       CALL logger_header() 
    326  
    327       READ( il_fileid, NML = namcfg ) 
    328       ! get variable extra information 
    329       CALL var_def_extra(TRIM(cn_varcfg)) 
    330  
    331       ! get dimension allowed 
    332       CALL dim_def_extra(TRIM(cn_dimcfg)) 
    333  
    334       ! get dummy variable 
    335       CALL var_get_dummy(TRIM(cn_dumcfg)) 
    336       ! get dummy dimension 
    337       CALL dim_get_dummy(TRIM(cn_dumcfg)) 
    338       ! get dummy attribute 
    339       CALL att_get_dummy(TRIM(cn_dumcfg)) 
    340  
    341       READ( il_fileid, NML = namcrs ) 
    342       READ( il_fileid, NML = namfin ) 
    343 !      READ( il_fileid, NML = namvar ) 
    344 !      ! add user change in extra information 
    345 !      CALL var_chg_extra(cn_varinfo) 
    346  
    347       READ( il_fileid, NML = namnst ) 
    348       READ( il_fileid, NML = nambdy ) 
    349  
    350       READ( il_fileid, NML = namout ) 
    351  
    352       CLOSE( il_fileid, IOSTAT=il_status ) 
    353       CALL fct_err(il_status) 
    354       IF( il_status /= 0 )THEN 
    355          CALL logger_error("MERGE BATHY: ERROR closing "//TRIM(cl_namelist)) 
    356       ENDIF 
    357  
    358    ELSE 
    359  
    360       PRINT *,"MERGE BATHY: ERROR. can not find "//TRIM(cl_namelist) 
    361  
     407 
     408      CALL GET_COMMAND_ARGUMENT(1,cl_arg) !f03 intrinsec 
     409      SELECT CASE (cl_arg) 
     410         CASE ('-v', '--version') 
     411 
     412            CALL fct_version(cp_myname) 
     413            CALL EXIT(0) 
     414 
     415         CASE ('-h', '--help') 
     416 
     417            CALL fct_help(cp_myname) 
     418            CALL EXIT(0) 
     419 
     420         CASE DEFAULT 
     421 
     422            cl_namelist=cl_arg 
     423 
     424            ! read namelist 
     425            INQUIRE(FILE=TRIM(cl_namelist), EXIST=ll_exist) 
     426            IF( ll_exist )THEN 
     427 
     428               il_fileid=fct_getunit() 
     429 
     430               OPEN( il_fileid, FILE=TRIM(cl_namelist),  & 
     431               &                FORM='FORMATTED',        & 
     432               &                ACCESS='SEQUENTIAL',     & 
     433               &                STATUS='OLD',            & 
     434               &                ACTION='READ',           & 
     435               &                IOSTAT=il_status) 
     436               CALL fct_err(il_status) 
     437               IF( il_status /= 0 )THEN 
     438                  WRITE(cl_errormsg,*) " ERROR : error opening "//TRIM(cl_namelist) 
     439                  CALL fct_help(cp_myname,cl_errormsg)  
     440                  CALL EXIT(1) 
     441               ENDIF 
     442 
     443               READ( il_fileid, NML = namlog ) 
     444               ! define log file 
     445               CALL logger_open(TRIM(cn_logfile),TRIM(cn_verbosity),in_maxerror) 
     446               CALL logger_header() 
     447 
     448               READ( il_fileid, NML = namcfg ) 
     449               ! get variable extra information 
     450               CALL var_def_extra(TRIM(cn_varcfg)) 
     451 
     452               ! get dimension allowed 
     453               CALL dim_def_extra(TRIM(cn_dimcfg)) 
     454 
     455               ! get dummy variable 
     456               CALL var_get_dummy(TRIM(cn_dumcfg)) 
     457               ! get dummy dimension 
     458               CALL dim_get_dummy(TRIM(cn_dumcfg)) 
     459               ! get dummy attribute 
     460               CALL att_get_dummy(TRIM(cn_dumcfg)) 
     461 
     462               READ( il_fileid, NML = namsrc ) 
     463               READ( il_fileid, NML = namtgt ) 
     464!               READ( il_fileid, NML = namvar ) 
     465!               ! add user change in extra information 
     466!               CALL var_chg_extra(cn_varinfo) 
     467 
     468               READ( il_fileid, NML = namnst ) 
     469               READ( il_fileid, NML = nambdy ) 
     470 
     471               READ( il_fileid, NML = namout ) 
     472 
     473               CLOSE( il_fileid, IOSTAT=il_status ) 
     474               CALL fct_err(il_status) 
     475               IF( il_status /= 0 )THEN 
     476                  CALL logger_error("MERGE BATHY: ERROR closing "//TRIM(cl_namelist)) 
     477               ENDIF 
     478 
     479            ELSE 
     480 
     481               WRITE(cl_errormsg,*) " ERROR : can't find "//TRIM(cl_namelist) 
     482               CALL fct_help(cp_myname,cl_errormsg)  
     483               CALL EXIT(1) 
     484 
     485            ENDIF 
     486 
     487      END SELECT 
    362488   ENDIF 
    363489 
    364490   ! open files 
    365491   IF( TRIM(cn_bathy0) /= '' )THEN 
    366       tl_bathy0=mpp_init( file_init(TRIM(cn_bathy0)), id_perio=in_perio0) 
     492      tl_file=file_init(TRIM(cn_bathy0)) 
     493      tl_bathy0=mpp_init( tl_file, id_perio=in_perio0) 
     494      ! clean 
     495      CALL file_clean(tl_file) 
    367496      CALL grid_get_info(tl_bathy0) 
    368497   ELSE 
     
    372501 
    373502   IF( TRIM(cn_bathy1) /= '' )THEN 
    374       tl_bathy1=mpp_init( file_init(TRIM(cn_bathy1)), id_perio=in_perio1) 
     503      tl_file=file_init(TRIM(cn_bathy1)) 
     504      tl_bathy1=mpp_init( tl_file, id_perio=in_perio1) 
     505      ! clean 
     506      CALL file_clean(tl_file) 
    375507      CALL grid_get_info(tl_bathy1) 
    376508   ELSE 
     
    515647   CALL file_add_att(tl_fileout, tl_att) 
    516648 
     649   !add source url 
     650   cl_url=fct_split(fct_split(cp_url,2,'$'),2,'URL:') 
     651   tl_att=att_init("SIREN_url",cl_url) 
     652   CALL file_add_att(tl_fileout, tl_att) 
     653 
     654   ! add date of creation 
    517655   cl_date=date_print(date_now()) 
    518656   tl_att=att_init("Creation_date",cl_date) 
     
    641779 
    642780CONTAINS 
     781   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 
     782   SUBROUTINE merge_bathy_get_boundary(td_bathy0, td_bathy1, td_bdy, & 
     783         &                             id_rho, id_ncrs,              & 
     784         &                             dd_refined, dd_weight, dd_fill) 
    643785   !------------------------------------------------------------------- 
    644786   !> @brief 
     
    658800   !> 
    659801   !------------------------------------------------------------------- 
    660    SUBROUTINE merge_bathy_get_boundary( td_bathy0, td_bathy1, td_bdy, & 
    661    &                                    id_rho, id_ncrs,              & 
    662    &                                    dd_refined, dd_weight, dd_fill ) 
    663802 
    664803      IMPLICIT NONE 
     
    8651004               &                           (il_width) ) 
    8661005 
    867  
    8681006               ALLOCATE( dl_wseg(tl_dom1%t_dim(1)%i_len, & 
    8691007               &                 tl_dom1%t_dim(2)%i_len) ) 
     
    8841022               &                           (il_width) ) 
    8851023 
    886  
    8871024               ALLOCATE( dl_wseg(tl_dom1%t_dim(1)%i_len, & 
    8881025               &                 tl_dom1%t_dim(2)%i_len) ) 
     
    9031040               &                           (il_width) ) 
    9041041 
    905  
    9061042               ALLOCATE( dl_wseg(tl_dom1%t_dim(1)%i_len, & 
    9071043               &                 tl_dom1%t_dim(2)%i_len) ) 
     
    9221058               &                           (il_width) ) 
    9231059 
    924  
    9251060               ALLOCATE( dl_wseg(tl_dom1%t_dim(1)%i_len, & 
    9261061               &                 tl_dom1%t_dim(2)%i_len) ) 
     
    9581093      ENDIF 
    9591094   END SUBROUTINE merge_bathy_get_boundary 
     1095   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 
     1096   SUBROUTINE merge_bathy_interp(td_var, id_rho, id_offset, id_iext, id_jext) 
    9601097   !------------------------------------------------------------------- 
    9611098   !> @brief 
     
    9711108   !> @param[in] id_jext   j-direction size of extra bands (default=im_minext) 
    9721109   !------------------------------------------------------------------- 
    973    SUBROUTINE merge_bathy_interp( td_var,          & 
    974    &                              id_rho,          & 
    975    &                              id_offset,       & 
    976    &                              id_iext, id_jext) 
    9771110 
    9781111      IMPLICIT NONE 
     
    10621195 
    10631196   END SUBROUTINE merge_bathy_interp 
     1197   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 
    10641198END PROGRAM merge_bathy 
Note: See TracChangeset for help on using the changeset viewer.