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/addline_deg.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/addline_deg.f90

    r12080 r13369  
    33!---------------------------------------------------------------------- 
    44!> @file 
    5 !> @brief  
     5!> @brief 
    66!> This program add line to all variables of the input file. 
    77!> 
     
    2525!> 
    2626!>    here after, each sub-namelist parameters is detailed. 
    27 !>    @note  
     27!>    @note 
    2828!>       default values are specified between brackets 
    2929!> 
     
    4444!>          - none 
    4545!> 
    46 !>    - **in_maxerror** [@a 5]<br/>  
     46!>    - **in_maxerror** [@a 5]<br/> 
    4747!>       maximum number of error allowed 
    4848!> 
     
    5252!>    - **cn_varcfg** [@a ./cfg/variable.cfg]<br/> 
    5353!>       path to the variable configuration file.<br/> 
    54 !>       the variable configuration file defines standard name,  
    55 !>       default interpolation method, axis,...  
    56 !>       to be used for some known variables.<br/>  
    57 !> 
    58 !>    - **cn_dimcfg** [@a ./cfg/dimension.cfg]<br/>  
    59 !>       path to the dimension configuration file.<br/>  
    60 !>       the dimension configuration file defines dimensions allowed.<br/>  
    61 !> 
    62 !>    - **cn_dumcfg** [@a ./cfg/dummy.cfg]<br/>  
     54!>       the variable configuration file defines standard name, 
     55!>       default interpolation method, axis,... 
     56!>       to be used for some known variables.<br/> 
     57!> 
     58!>    - **cn_dimcfg** [@a ./cfg/dimension.cfg]<br/> 
     59!>       path to the dimension configuration file.<br/> 
     60!>       the dimension configuration file defines dimensions allowed.<br/> 
     61!> 
     62!>    - **cn_dumcfg** [@a ./cfg/dummy.cfg]<br/> 
    6363!>       path to the useless (dummy) configuration file.<br/> 
    64 !>       the dummy configuration file defines useless  
     64!>       the dummy configuration file defines useless 
    6565!>       dimension or variable. these dimension(s) or variable(s) will not be 
    6666!>       processed.<br/> 
    6767!> 
    68 !> @subsection subsrc namsrc  
     68!> @subsection subsrc namsrc 
    6969!>    the source/coarse grid sub-namelist parameters are : 
    7070!> 
    71 !>    - **cn_coord0** [@a ]<br/>  
     71!>    - **cn_coord0** [@a ]<br/> 
    7272!>       path to the coordinate file 
    7373!> 
    74 !>    - **in_perio0** [@a ]<br/>  
    75 !>       NEMO periodicity index<br/>  
     74!>    - **in_perio0** [@a ]<br/> 
     75!>       NEMO periodicity index<br/> 
    7676!>       the NEMO periodicity could be choose between 0 to 6: 
    7777!>       <dl> 
     
    9595!>       </dl> 
    9696!>       @sa For more information see @ref md_src_docsrc_6_perio 
    97 !>       and Model Boundary Condition paragraph in the  
     97!>       and Model Boundary Condition paragraph in the 
    9898!>       [NEMO documentation](https://forge.ipsl.jussieu.fr/nemo/chrome/site/doc/NEMO/manual/pdf/NEMO_manual.pdf) 
    9999!> 
    100 !> @subsection subvar namvar  
     100!> @subsection subvar namvar 
    101101!>    the variable sub-namelist parameters are : 
    102102!> 
    103 !>    - **cn_varfile** [@a ]<br/>  
    104 !>       list of variable, and associated file  
     103!>    - **cn_varfile** [@a ]<br/> 
     104!>       list of variable, and associated file 
    105105!> 
    106106!>       *cn_varfile* is the path and filename of the file where find 
    107107!>       variable. 
    108 !>       @note  
     108!>       @note 
    109109!>          *cn_varfile* could be a matrix of value, if you want to handwrite 
    110110!>          variable value.<br/> 
    111111!>          the variable array of value is split into equal subdomain.<br/> 
    112 !>          each subdomain is filled with the corresponding value  
    113 !>          of the matrix.<br/>           
     112!>          each subdomain is filled with the corresponding value 
     113!>          of the matrix.<br/> 
    114114!>          separators used to defined matrix are: 
    115115!>             - ',' for line 
     
    120120!>                                      1 & 4 & 5 \end{array} \right) @f$ 
    121121!> 
    122 !>       Examples:  
     122!>       Examples: 
    123123!>          - 'Bathymetry:gridT.nc' 
    124124!> 
    125 !>       @note  
     125!>       @note 
    126126!>          Optionnaly, NEMO periodicity could be added following the filename. 
    127127!>          the periodicity must be separated by ';' 
     
    130130!>          - 'Bathymetry:gridT.nc ; perio=4'<br/> 
    131131!> 
    132 !>    - **cn_varinfo** [@a ]<br/>  
     132!>    - **cn_varinfo** [@a ]<br/> 
    133133!>       list of variable and extra information about request(s) to be used<br/> 
    134134!> 
    135135!>       each elements of *cn_varinfo* is a string character (separated by ',').<br/> 
    136 !>       it is composed of the variable name follow by ':',  
    137 !>       then request(s) to be used on this variable.<br/>  
     136!>       it is composed of the variable name follow by ':', 
     137!>       then request(s) to be used on this variable.<br/> 
    138138!>       request could be: 
    139139!>          - int = interpolation method 
     
    150150!>       informations about available method could be find in @ref interp, 
    151151!>       @ref extrap and @ref filter modules.<br/> 
    152 !>       Example:  
     152!>       Example: 
    153153!>          - 'Bathymetry: flt=2*hamming(2,3); min=0' 
    154154!> 
    155 !>       @note  
    156 !>          If you do not specify a method which is required,  
     155!>       @note 
     156!>          If you do not specify a method which is required, 
    157157!>          default one is apply. 
    158158!> 
    159 !> @subsection subout namout  
     159!> @subsection subout namout 
    160160!>    the output sub-namelist parameter is : 
    161161!> 
     
    163163!>       output filename 
    164164!>    - @b ln_extrap [@a .FALSE.]<br/> 
    165 !>       extrapolate extra line  
     165!>       extrapolate extra line 
    166166!>    - @b ln_copy [@a .FALSE.]<br/> 
    167167!>       copy extra line from above 
     
    220220 
    221221   TYPE(TATT)                                         :: tl_att 
    222     
     222 
    223223   TYPE(TVAR)                                         :: tl_lon 
    224224   TYPE(TVAR)                                         :: tl_lat 
     
    228228   TYPE(TVAR)                                         :: tl_tmp 
    229229   TYPE(TVAR)       , DIMENSION(:), ALLOCATABLE       :: tl_var 
    230     
     230 
    231231   TYPE(TDIM)       , DIMENSION(ip_maxdim)            :: tl_dim 
    232232 
     
    241241   ! namelist variable 
    242242   ! namlog 
    243    CHARACTER(LEN=lc)                       :: cn_logfile = 'addline.log'  
    244    CHARACTER(LEN=lc)                       :: cn_verbosity = 'warning'  
     243   CHARACTER(LEN=lc)                       :: cn_logfile = 'addline.log' 
     244   CHARACTER(LEN=lc)                       :: cn_verbosity = 'warning' 
    245245   INTEGER(i4)                             :: in_maxerror = 5 
    246246 
    247247   ! namcfg 
    248    CHARACTER(LEN=lc)                       :: cn_varcfg = 'variable.cfg'  
    249    CHARACTER(LEN=lc)                       :: cn_dimcfg = 'dimension.cfg'  
    250    CHARACTER(LEN=lc)                       :: cn_dumcfg = 'dummy.cfg'  
     248   CHARACTER(LEN=lc)                       :: cn_varcfg = 'variable.cfg' 
     249   CHARACTER(LEN=lc)                       :: cn_dimcfg = 'dimension.cfg' 
     250   CHARACTER(LEN=lc)                       :: cn_dumcfg = 'dummy.cfg' 
    251251 
    252252   ! namsrc 
    253    CHARACTER(LEN=lc)                       :: cn_coord0 = ''  
     253   CHARACTER(LEN=lc)                       :: cn_coord0 = '' 
    254254   INTEGER(i4)                             :: in_perio0 = -1 
    255255 
     
    259259 
    260260   ! namout 
    261    CHARACTER(LEN=lc)                       :: cn_fileout = 'addline_deg.nc'  
     261   CHARACTER(LEN=lc)                       :: cn_fileout = 'addline_deg.nc' 
    262262   LOGICAL                                 :: ln_extrap  = .FALSE. 
    263263   LOGICAL                                 :: ln_copy    = .FALSE. 
     
    281281   &  cn_coord0,  &      !< coordinate file 
    282282   &  in_perio0          !< periodicity index 
    283     
     283 
    284284   NAMELIST /namvar/ &   !< variable namelist 
    285285   &  cn_varinfo, &      !< list of variable and interpolation method to be used. (ex: 'votemper:linear','vosaline:cubic' ) 
     
    305305      CALL GET_COMMAND_ARGUMENT(1,cl_namelist) !f03 intrinsec 
    306306   ENDIF 
    307   
     307 
    308308   ! read namelist 
    309309   INQUIRE(FILE=TRIM(cl_namelist), EXIST=ll_exist) 
    310310   IF( ll_exist )THEN 
    311   
     311 
    312312      il_fileid=fct_getunit() 
    313313 
     
    349349      ! match variable with file 
    350350      tl_multi=multi_init(cn_varfile) 
    351        
     351 
    352352      READ( il_fileid, NML = namout ) 
    353353 
     
    373373   ELSE 
    374374      CALL logger_fatal("ADD LINE: no coarse grid coordinate found. "//& 
    375       &     "check namelist")       
     375      &     "check namelist") 
    376376   ENDIF 
    377377 
     
    393393      jk=0 
    394394      DO ji=1,tl_multi%i_nmpp 
    395        
     395 
    396396         IF( .NOT. ASSOCIATED(tl_multi%t_mpp(ji)%t_proc(1)%t_var) )THEN 
    397397 
     
    445445            CALL iom_mpp_close(tl_mpp) 
    446446 
    447             !- add line to input file variable  
     447            !- add line to input file variable 
    448448            DO jj=1,tl_multi%t_mpp(ji)%t_proc(1)%i_nvar 
    449449               jk=jk+1 
    450450               tl_tmp=var_copy(tl_multi%t_mpp(ji)%t_proc(1)%t_var(jj)) 
    451451               WRITE(*,'(2x,a)') "work on variable "//TRIM(tl_tmp%c_name) 
    452              
     452 
    453453               tl_var(jk)=add_line( tl_tmp, tl_mpp, & 
    454454               &                    tl_coord0 ) 
     
    500500   DO ji=1,ip_maxdim 
    501501 
    502       IF( tl_dim(ji)%l_use )THEN 
     502      IF( tl_dim(ji)%l_use .AND. .NOT. tl_mppout%t_dim(ji)%l_use )THEN 
    503503         CALL mpp_move_dim(tl_mppout, tl_dim(ji)) 
    504504         SELECT CASE(TRIM(tl_dim(ji)%c_sname)) 
     
    507507               CALL file_add_dim(tl_mppout%t_proc(jj), tl_dim(ji)) 
    508508            ENDDO 
    509          END SELECT  
     509         END SELECT 
    510510      ENDIF 
    511511 
     
    589589      CALL mpp_add_att(tl_mppout,tl_att) 
    590590   ENDIF 
    591     
     591 
    592592   ! print 
    593593   CALL mpp_print(tl_mppout) 
     
    620620   !> @brief 
    621621   !> This function add line to variable and return variable structure 
    622    !>  
     622   !> 
    623623   !> @author J.Paul 
    624624   !> @date October, 2015 - Initial Version 
    625625   !> 
    626    !> @param[in] td_var    variable structure  
     626   !> @param[in] td_var    variable structure 
    627627   !> @param[in] td_mpp    mpp file structure 
    628628   !> @param[in] td_coord  coordinate file structure 
    629629   !> @return variable structure 
    630630   !------------------------------------------------------------------- 
    631        
     631 
    632632      IMPLICIT NONE 
    633633 
    634634      ! Argument 
    635       TYPE(TVAR), INTENT(IN) :: td_var   
     635      TYPE(TVAR), INTENT(IN) :: td_var 
    636636      TYPE(TMPP), INTENT(IN) :: td_mpp 
    637637      TYPE(TMPP), INTENT(IN) :: td_coord 
     
    680680         ! add attribute to variable 
    681681         tl_att=att_init('src_file',TRIM(fct_basename(tl_mpp%c_name))) 
    682          CALL var_move_att(tf_var, tl_att)          
     682         CALL var_move_att(tf_var, tl_att) 
    683683 
    684684         tl_att=att_init('add_i_line',(/il_ghost(jp_I,1), il_ghost(jp_I,2)/)) 
     
    695695   END FUNCTION add_line 
    696696   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 
    697 END PROGRAM  
     697END PROGRAM 
Note: See TracChangeset for help on using the changeset viewer.