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

Ignore:
Timestamp:
2020-07-31T10:50:52+02:00 (4 years ago)
Author:
jpaul
Message:

update: cf changelog inside documentation

File:
1 edited

Legend:

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

    r12080 r13369  
    55! DESCRIPTION: 
    66!> @file 
    7 !> This program creates fine grid bathymetry file. 
     7!> This program creates target/fine grid bathymetry file. 
    88!> 
    99!> @section sec1 method 
    1010!> This bathymetry could be : 
    11 !> - extracted from a wider fine grid bathymetry file 
    12 !> - interpolated from a wider coarse grid bathymetry file 
     11!> - extracted from a wider target/fine grid bathymetry file 
     12!> - interpolated from a wider source/coarse grid bathymetry file 
    1313!> - handwritten 
    1414!> 
    15 !> @image html  bathy_40.png  
     15!> @image html  bathy_40.png 
    1616!> <center>@image latex bathy_30.png 
    1717!> </center> 
     
    4545!> 
    4646!>    here after, each sub-namelist parameters is detailed. 
    47 !>    @note  
     47!>    @note 
    4848!>       default values are specified between brackets 
    4949!> 
     
    6464!>          - none 
    6565!> 
    66 !>    - **in_maxerror** [@a 5]<br/>  
     66!>    - **in_maxerror** [@a 5]<br/> 
    6767!>       maximum number of error allowed 
    6868!> 
     
    7272!>    - **cn_varcfg** [@a ./cfg/variable.cfg]<br/> 
    7373!>       path to the variable configuration file.<br/> 
    74 !>       the variable configuration file defines standard name,  
    75 !>       default interpolation method, axis,...  
    76 !>       to be used for some known variables.<br/>  
    77 !> 
    78 !>    - **cn_dimcfg** [@a ./cfg/dimension.cfg]<br/>  
    79 !>       path to the dimension configuration file.<br/>  
    80 !>       the dimension configuration file defines dimensions allowed.<br/>  
    81 !> 
    82 !>    - **cn_dumcfg** [@a ./cfg/dummy.cfg]<br/>  
     74!>       the variable configuration file defines standard name, 
     75!>       default interpolation method, axis,... 
     76!>       to be used for some known variables.<br/> 
     77!> 
     78!>    - **cn_dimcfg** [@a ./cfg/dimension.cfg]<br/> 
     79!>       path to the dimension configuration file.<br/> 
     80!>       the dimension configuration file defines dimensions allowed.<br/> 
     81!> 
     82!>    - **cn_dumcfg** [@a ./cfg/dummy.cfg]<br/> 
    8383!>       path to the useless (dummy) configuration file.<br/> 
    84 !>       the dummy configuration file defines useless  
     84!>       the dummy configuration file defines useless 
    8585!>       dimension or variable. these dimension(s) or variable(s) will not be 
    8686!>       processed.<br/> 
    8787!> 
    88 !> @subsection subsrc namsrc  
     88!> @subsection subsrc namsrc 
    8989!>    the source/coarse grid sub-namelist parameters are : 
    9090!> 
    91 !>    - **cn_coord0** [@a ]<br/>  
     91!>    - **cn_coord0** [@a ]<br/> 
    9292!>       path to the coordinate file 
    9393!> 
    94 !>    - **in_perio0** [@a ]<br/>  
    95 !>       NEMO periodicity index<br/>  
     94!>    - **in_perio0** [@a ]<br/> 
     95!>       NEMO periodicity index<br/> 
    9696!>       the NEMO periodicity could be choose between 0 to 6: 
    9797!>       <dl> 
     
    115115!>       </dl> 
    116116!>       @sa For more information see @ref md_src_docsrc_6_perio 
    117 !>       and Model Boundary Condition paragraph in the  
     117!>       and Model Boundary Condition paragraph in the 
    118118!>       [NEMO documentation](https://forge.ipsl.jussieu.fr/nemo/chrome/site/doc/NEMO/manual/pdf/NEMO_manual.pdf) 
    119119!> 
    120 !> @subsection subtgt namtgt  
     120!> @subsection subtgt namtgt 
    121121!>    the target/fine grid sub-namelist parameters are : 
    122122!> 
    123 !>    - **cn_coord1** [@a ]<br/>  
     123!>    - **cn_coord1** [@a ]<br/> 
    124124!>       path to coordinate file 
    125125!> 
     
    133133!>       logical to fill closed sea or not 
    134134!> 
    135 !> @subsection subvar namvar  
     135!> @subsection subvar namvar 
    136136!>    the variable sub-namelist parameters are : 
    137137!> 
    138 !>    - **cn_varfile** [@a ]<br/>  
    139 !>       list of variable, and associated file  
    140 !>       @warning  
     138!>    - **cn_varfile** [@a ]<br/> 
     139!>       list of variable, and associated file 
     140!>       @warning 
    141141!>          variable name must be __Bathymetry__ here. 
    142142!> 
    143143!>       *cn_varfile* is the path and filename of the file where find 
    144144!>       variable. 
    145 !>       @note  
     145!>       @note 
    146146!>          *cn_varfile* could be a matrix of value, if you want to handwrite 
    147147!>          variable value.<br/> 
    148148!>          the variable array of value is split into equal subdomain.<br/> 
    149 !>          each subdomain is filled with the corresponding value  
    150 !>          of the matrix.<br/>           
     149!>          each subdomain is filled with the corresponding value 
     150!>          of the matrix.<br/> 
    151151!>          separators used to defined matrix are: 
    152152!>             - ',' for line 
     
    157157!>                                      1 & 4 & 5 \end{array} \right) @f$ 
    158158!> 
    159 !>       Examples:  
     159!>       Examples: 
    160160!>          - 'Bathymetry:gridT.nc' 
    161161!>          - 'Bathymetry:5000,5000,5000/5000,3000,5000/5000,5000,5000'<br/> 
    162162!> 
    163 !>       @note  
     163!>       @note 
    164164!>          Optionnaly, NEMO periodicity could be added following the filename. 
    165165!>          the periodicity must be separated by ';' 
     
    168168!>          - 'Bathymetry:gridT.nc ; perio=4'<br/> 
    169169!> 
    170 !>    - **cn_varinfo** [@a ]<br/>  
     170!>    - **cn_varinfo** [@a ]<br/> 
    171171!>       list of variable and extra information about request(s) to be used<br/> 
    172172!> 
    173173!>       each elements of *cn_varinfo* is a string character (separated by ',').<br/> 
    174 !>       it is composed of the variable name follow by ':',  
    175 !>       then request(s) to be used on this variable.<br/>  
     174!>       it is composed of the variable name follow by ':', 
     175!>       then request(s) to be used on this variable.<br/> 
    176176!>       request could be: 
    177177!>          - int = interpolation method 
     
    188188!>       informations about available method could be find in @ref interp, 
    189189!>       @ref extrap and @ref filter modules.<br/> 
    190 !>       Example:  
     190!>       Example: 
    191191!>          - 'Bathymetry: flt=2*hamming(2,3); min=0' 
    192192!> 
    193 !>       @note  
    194 !>          If you do not specify a method which is required,  
     193!>       @note 
     194!>          If you do not specify a method which is required, 
    195195!>          default one is apply. 
    196196!> 
    197 !>    - **ln_rand** [@a .False.]<br/>  
     197!>    - **ln_rand** [@a .False.]<br/> 
    198198!>          logical to add random value to Bathymetry<br/> 
    199 !>          Only for handmade Bathymetry.  
     199!>          Only for handmade Bathymetry. 
    200200!>          A random value (+/- 0.1% of the maximum depth) will 
    201201!>          will be added to avoid flat Bathymetry (which may cause issue). 
    202202!> 
    203 !> @subsection subnst namnst  
     203!> @subsection subnst namnst 
    204204!>    the nesting sub-namelist parameters are : 
    205205!> 
    206 !>    - **in_rhoi**  [@a 1]<br/>  
     206!>    - **in_rhoi**  [@a 1]<br/> 
    207207!>       refinement factor in i-direction 
    208208!> 
    209 !>    - **in_rhoj**  [@a 1]<br/>  
     209!>    - **in_rhoj**  [@a 1]<br/> 
    210210!>       refinement factor in j-direction 
    211211!> 
    212 !>    @note  
    213 !>       coarse grid indices will be deduced from fine grid 
     212!>    @note 
     213!>       source/coarse grid indices will be deduced from target/fine grid 
    214214!>       coordinate file. 
    215215!> 
    216 !> @subsection subout namout  
     216!> @subsection subout namout 
    217217!>    the output sub-namelist parameter is : 
    218218!> 
     
    224224!> 
    225225!> @date November, 2013 - Initial Version 
    226 !> @date Sepember, 2014  
     226!> @date Sepember, 2014 
    227227!> - add header for user 
    228228!> - Bug fix, compute offset depending of grid point 
     
    317317 
    318318   TYPE(TATT)                                         :: tl_att 
    319     
     319 
    320320   TYPE(TVAR)                                         :: tl_lon 
    321321   TYPE(TVAR)                                         :: tl_lat 
     
    325325   TYPE(TVAR)                                         :: tl_tmp 
    326326   TYPE(TVAR)       , DIMENSION(:), ALLOCATABLE       :: tl_var 
    327     
     327 
    328328   TYPE(TDIM)       , DIMENSION(ip_maxdim)            :: tl_dim 
    329329 
     
    341341   ! namelist variable 
    342342   ! namlog 
    343    CHARACTER(LEN=lc)                       :: cn_logfile    = 'create_bathy.log'  
    344    CHARACTER(LEN=lc)                       :: cn_verbosity  = 'warning'  
     343   CHARACTER(LEN=lc)                       :: cn_logfile    = 'create_bathy.log' 
     344   CHARACTER(LEN=lc)                       :: cn_verbosity  = 'warning' 
    345345   INTEGER(i4)                             :: in_maxerror   = 5 
    346346 
    347347   ! namcfg 
    348    CHARACTER(LEN=lc)                       :: cn_varcfg  = './cfg/variable.cfg'  
     348   CHARACTER(LEN=lc)                       :: cn_varcfg  = './cfg/variable.cfg' 
    349349   CHARACTER(LEN=lc)                       :: cn_dimcfg  = './cfg/dimension.cfg' 
    350350   CHARACTER(LEN=lc)                       :: cn_dumcfg  = './cfg/dummy.cfg' 
    351351 
    352352   ! namsrc 
    353    CHARACTER(LEN=lc)                       :: cn_coord0  = ''  
     353   CHARACTER(LEN=lc)                       :: cn_coord0  = '' 
    354354   INTEGER(i4)                             :: in_perio0  = -1 
    355355 
     
    369369 
    370370   ! namout 
    371    CHARACTER(LEN=lc)                       :: cn_fileout = 'bathy_fine.nc'  
     371   CHARACTER(LEN=lc)                       :: cn_fileout = 'bathy_fine.nc' 
    372372   !------------------------------------------------------------------- 
    373373 
     
    390390   &  in_perio1,     &  !< periodicity index 
    391391   &  ln_fillclosed     !< fill closed sea 
    392   
     392 
    393393   NAMELIST /namvar/ &  !< variable namelist 
    394394   &  cn_varfile,    &  !< list of variable file 
    395395   &  cn_varinfo,    &  !< list of variable and interpolation method to be used. (ex: 'votemper:linear','vosaline:cubic' ) 
    396396   &  ln_rand           !< add random value to avoid flat bathymetry 
    397   
     397 
    398398   NAMELIST /namnst/ &  !< nesting namelist 
    399399   &  in_rhoi,       &  !< refinement factor in i-direction 
     
    401401 
    402402   NAMELIST /namout/ &  !< output namelist 
    403    &  cn_fileout        !< fine grid bathymetry file 
     403   &  cn_fileout        !< target/fine grid bathymetry file 
    404404   !------------------------------------------------------------------- 
    405405 
     
    414414   IF( il_narg /= 1 )THEN 
    415415      WRITE(cl_errormsg,*) ' ERROR : one argument is needed ' 
    416       CALL fct_help(cp_myname,cl_errormsg)  
     416      CALL fct_help(cp_myname,cl_errormsg) 
    417417      CALL EXIT(1) 
    418418   ELSE 
     
    449449               IF( il_status /= 0 )THEN 
    450450                  WRITE(cl_errormsg,*) " ERROR : error opening "//TRIM(cl_namelist) 
    451                   CALL fct_help(cp_myname,cl_errormsg)  
     451                  CALL fct_help(cp_myname,cl_errormsg) 
    452452                  CALL EXIT(1) 
    453453               ENDIF 
    454454 
    455455               READ( il_fileid, NML = namlog ) 
    456   
     456 
    457457               ! define logger file 
    458458               CALL logger_open(TRIM(cn_logfile),TRIM(cn_verbosity),in_maxerror) 
     
    493493 
    494494               WRITE(cl_errormsg,*) " ERROR : can't find "//TRIM(cl_namelist) 
    495                CALL fct_help(cp_myname,cl_errormsg)  
     495               CALL fct_help(cp_myname,cl_errormsg) 
    496496               CALL EXIT(1) 
    497497 
     
    511511      CALL grid_get_info(tl_coord0) 
    512512   ELSE 
    513       CALL logger_fatal("CREATE BATHY: no coarse grid coordinate found. "//& 
    514       &     "check namelist")       
     513      CALL logger_fatal("CREATE BATHY: no source/coarse grid coordinate found. "//& 
     514      &     "check namelist") 
    515515   ENDIF 
    516516 
     
    522522      CALL grid_get_info(tl_coord1) 
    523523   ELSE 
    524       CALL logger_fatal("CREATE BATHY: no fine grid coordinate found. "//& 
     524      CALL logger_fatal("CREATE BATHY: no target/fine grid coordinate found. "//& 
    525525      &     "check namelist") 
    526526   ENDIF 
     
    550550 
    551551   ! check domain indices 
    552    ! compute coarse grid indices around fine grid 
     552   ! compute source/coarse grid indices around target/fine grid 
    553553   il_ind(:,:)=grid_get_coarse_index( tl_coord0, tl_coord1, & 
    554554   &                                  id_rho=il_rho(:) ) 
     
    560560   CALL grid_check_dom(tl_coord0, il_imin0, il_imax0, il_jmin0, il_jmax0) 
    561561 
    562    ! check coincidence between coarse and fine grid 
     562   ! check coincidence between coarse and target/fine grid 
    563563   CALL grid_check_coincidence( tl_coord0, tl_coord1, & 
    564564   &                            il_imin0, il_imax0, & 
     
    574574      jk=0 
    575575      DO ji=1,tl_multi%i_nmpp 
    576        
     576 
    577577         WRITE(cl_data,'(a,i2.2)') 'data-',jk+1 
    578578         IF( .NOT. ASSOCIATED(tl_multi%t_mpp(ji)%t_proc(1)%t_var) )THEN 
     
    622622            IF( ANY(tl_mpp%t_dim(1:2)%i_len /= tl_coord0%t_dim(1:2)%i_len).OR.& 
    623623            &   ALL(il_rho(:)==1) )THEN 
    624                !- extract bathymetry from fine grid bathymetry  
     624               !- extract bathymetry from target/fine grid bathymetry 
    625625               DO jj=1,tl_multi%t_mpp(ji)%t_proc(1)%i_nvar 
    626626                  jk=jk+1 
    627627                  tl_tmp=var_copy(tl_multi%t_mpp(ji)%t_proc(1)%t_var(jj)) 
    628   
     628 
    629629                  tl_var(jk)=create_bathy_extract( tl_tmp, tl_mpp, & 
    630630                  &                                tl_coord1 ) 
     
    633633               CALL var_clean(tl_tmp) 
    634634            ELSE 
    635                !- get bathymetry from coarse grid bathymetry  
     635               !- get bathymetry from source/coarse grid bathymetry 
    636636               DO jj=1,tl_multi%t_mpp(ji)%t_proc(1)%i_nvar 
    637637                  jk=jk+1 
     
    792792      CALL file_add_att(tl_fileout,tl_att) 
    793793   ENDIF 
    794     
     794 
    795795   ! create file 
    796796   CALL iom_create(tl_fileout) 
     
    821821   !> @brief 
    822822   !> This function create variable, filled with matrix value 
    823    !>  
    824    !> @details  
    825    !> A variable is create with the same name that the input variable,  
    826    !> and with dimension of the coordinate file.<br/>  
     823   !> 
     824   !> @details 
     825   !> A variable is create with the same name that the input variable, 
     826   !> and with dimension of the coordinate file.<br/> 
    827827   !> Then the variable array of value is split into equal subdomain. 
    828828   !> Each subdomain is filled with the corresponding value of the matrix. 
     
    834834   !> @date November, 2013 - Initial Version 
    835835   !> 
    836    !> @param[in] td_var    variable structure  
     836   !> @param[in] td_var    variable structure 
    837837   !> @param[in] td_coord  coordinate file structure 
    838838   !> @param[in] ld_rand   add random value to bathymetry 
     
    903903      CALL var_clean(tl_lon) 
    904904 
    905       ! split output domain in N subdomain depending of matrix dimension  
     905      ! split output domain in N subdomain depending of matrix dimension 
    906906      il_size(:) = tl_dim(1:2)%i_len / il_dim(:) 
    907907      il_rest(:) = MOD(tl_dim(1:2)%i_len, il_dim(:)) 
     
    923923      il_jshape(il_dim(2)+1)=il_jshape(il_dim(2)+1)+il_rest(2) 
    924924 
    925       ! write ouput array of value  
     925      ! write ouput array of value 
    926926      ALLOCATE(dl_value( tl_dim(1)%i_len, & 
    927927      &                  tl_dim(2)%i_len, & 
     
    932932      DO jj=2,il_dim(2)+1 
    933933         DO ji=2,il_dim(1)+1 
    934              
     934 
    935935            dl_value( 1+il_ishape(ji-1):il_ishape(ji), & 
    936936            &         1+il_jshape(jj-1):il_jshape(jj), & 
     
    944944         ALLOCATE(dl_ran(tl_dim(1)%i_len, & 
    945945         &               tl_dim(2)%i_len) ) 
    946        
     946 
    947947         ! set random value between 0 and 1 
    948948         CALL RANDOM_NUMBER(dl_ran(:,:)) 
     
    953953 
    954954         dl_value(:,:,1,1)=dl_value(:,:,1,1)+dl_ran(:,:) 
    955        
     955 
    956956         DEALLOCATE(dl_ran) 
    957957      ENDIF 
     
    976976   !> This function extract variable from file over coordinate domain and 
    977977   !> return variable structure 
    978    !>  
     978   !> 
    979979   !> @author J.Paul 
    980980   !> @date November, 2013 - Initial Version 
    981981   !> 
    982    !> @param[in] td_var    variable structure  
     982   !> @param[in] td_var    variable structure 
    983983   !> @param[in] td_mpp    mpp file structure 
    984984   !> @param[in] td_coord  coordinate file structure 
     
    989989 
    990990      ! Argument 
    991       TYPE(TVAR), INTENT(IN) :: td_var   
     991      TYPE(TVAR), INTENT(IN) :: td_var 
    992992      TYPE(TMPP), INTENT(IN) :: td_mpp 
    993993      TYPE(TMPP), INTENT(IN) :: td_coord 
     
    10711071         ! add attribute to variable 
    10721072         tl_att=att_init('src_file',TRIM(fct_basename(tl_mpp%c_name))) 
    1073          CALL var_move_att(tf_var, tl_att)          
     1073         CALL var_move_att(tf_var, tl_att) 
    10741074 
    10751075         tl_att=att_init('src_i_indices',(/tl_dom%i_imin, tl_dom%i_imax/)) 
     
    10941094   !------------------------------------------------------------------- 
    10951095   !> @brief 
    1096    !> This function get coarse grid variable, interpolate variable, and return 
    1097    !> variable structure over fine grid 
    1098    !>  
     1096   !> This function get source/coarse grid variable, interpolate variable, and return 
     1097   !> variable structure over target/fine grid 
     1098   !> 
    10991099   !> @author J.Paul 
    11001100   !> @date November, 2013 - Initial Version 
     
    11021102   !> @param[in] td_var    variable structure 
    11031103   !> @param[in] td_mpp    mpp file structure 
    1104    !> @param[in] id_imin   i-direction lower left  corner indice  
    1105    !> @param[in] id_imax   i-direction upper right corner indice  
     1104   !> @param[in] id_imin   i-direction lower left  corner indice 
     1105   !> @param[in] id_imax   i-direction upper right corner indice 
    11061106   !> @param[in] id_jmin   j-direction lower left  corner indice 
    1107    !> @param[in] id_jmax   j-direction upper right corner indice  
    1108    !> @param[in] id_offset offset between fine grid and coarse grid 
     1107   !> @param[in] id_jmax   j-direction upper right corner indice 
     1108   !> @param[in] id_offset offset between target/fine grid and source/coarse grid 
    11091109   !> @param[in] id_rho    array of refinement factor 
    11101110   !> @return variable structure 
     
    11141114 
    11151115      ! Argument 
    1116       TYPE(TVAR)                 , INTENT(IN) :: td_var   
    1117       TYPE(TMPP)                 , INTENT(IN) :: td_mpp  
     1116      TYPE(TVAR)                 , INTENT(IN) :: td_var 
     1117      TYPE(TMPP)                 , INTENT(IN) :: td_mpp 
    11181118      INTEGER(i4)                , INTENT(IN) :: id_imin 
    11191119      INTEGER(i4)                , INTENT(IN) :: id_imax 
     
    11641164      ALLOCATE( il_rho(il_size) ) 
    11651165      il_rho(:)=id_rho(:) 
    1166        
     1166 
    11671167      !- interpolate variable 
    11681168      CALL create_bathy_interp(tf_var, il_rho(:), id_offset(:,:)) 
     
    11751175      !- add ghost cell 
    11761176      CALL grid_add_ghost(tf_var,tl_dom%i_ghost(:,:)) 
    1177   
     1177 
    11781178      !- add attribute to variable 
    11791179      tl_att=att_init('src_file',TRIM(fct_basename(tl_mpp%c_name))) 
     
    11961196      CALL att_clean(tl_att) 
    11971197      CALL mpp_clean(tl_mpp) 
    1198   
     1198 
    11991199   END FUNCTION create_bathy_get_var 
    12001200   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 
     
    12041204   !> @brief 
    12051205   !> This subroutine interpolate variable 
    1206    !>  
     1206   !> 
    12071207   !> @author J.Paul 
    12081208   !> @date November, 2013 - Initial Version 
    12091209   !> 
    1210    !> @param[inout] td_var variable structure  
     1210   !> @param[inout] td_var variable structure 
    12111211   !> @param[in] id_rho    array of refinment factor 
    1212    !> @param[in] id_offset array of offset between fine and coarse grid 
     1212   !> @param[in] id_offset array of offset between target/fine and source/coarse grid 
    12131213   !> @param[in] id_iext   i-direction size of extra bands (default=im_minext) 
    12141214   !> @param[in] id_jext   j-direction size of extra bands (default=im_minext) 
     
    12621262 
    12631263      bl_mask(:,:,:,:)=1 
    1264       WHERE(td_var%d_value(:,:,:,:)==td_var%d_fill) bl_mask(:,:,:,:)=0       
     1264      WHERE(td_var%d_value(:,:,:,:)==td_var%d_fill) bl_mask(:,:,:,:)=0 
    12651265 
    12661266      SELECT CASE(TRIM(td_var%c_point)) 
     
    12951295      CALL extrap_del_extrabands(td_var, il_iext*id_rho(jp_I), il_jext*id_rho(jp_J)) 
    12961296 
    1297       ! keep original mask  
     1297      ! keep original mask 
    12981298      WHERE( tl_mask%d_value(:,:,:,:) == 0 ) 
    12991299         td_var%d_value(:,:,:,:)=td_var%d_fill 
     
    13101310   !> This subroutine get depth variable value in an open mpp structure 
    13111311   !> and check if agree with already input depth variable. 
    1312    !>  
    1313    !> @details  
     1312   !> 
     1313   !> @details 
    13141314   !> 
    13151315   !> @author J.Paul 
     
    13171317   !> 
    13181318   !> @param[in] td_mpp       mpp structure 
    1319    !> @param[inout] td_depth  depth variable structure  
     1319   !> @param[inout] td_depth  depth variable structure 
    13201320   !------------------------------------------------------------------- 
    13211321 
     
    13551355 
    13561356      ENDIF 
    1357        
     1357 
    13581358   END SUBROUTINE create_bathy_check_depth 
    13591359   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 
     
    13631363   !> This subroutine get date and time in an open mpp structure 
    13641364   !> and check if agree with date and time already read. 
    1365    !>  
    1366    !> @details  
     1365   !> 
     1366   !> @details 
    13671367   !> 
    13681368   !> @author J.Paul 
     
    13701370   !> 
    13711371   !> @param[in] td_mpp      mpp structure 
    1372    !> @param[inout] td_time  time variable structure  
     1372   !> @param[inout] td_time  time variable structure 
    13731373   !------------------------------------------------------------------- 
    13741374 
     
    14121412 
    14131413      ENDIF 
    1414        
     1414 
    14151415   END SUBROUTINE create_bathy_check_time 
    14161416   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 
Note: See TracChangeset for help on using the changeset viewer.