203     logical :: initialized = .false.
   211     character(STRING), 
pointer:: options(:) => null()
   213     character(STRING) :: help_message
   215     logical :: optvalue_flag
   220     character(STRING) :: name  
   221     character(STRING) :: 
value    222     logical:: flag_called = .false.
   350     type(
args), 
intent(out) :: arg
   351     integer:: cmd_opts_max
   352     character(len = *), 
parameter :: subname = 
'DCArgsOpen'   354     if (arg % initialized) 
then   355       call messagenotify(
'W', subname, 
'This argument (type ARGS) is already opend.')
   361     allocate(arg % cmd_opts_list(cmd_opts_max))
   363     nullify( arg % opt_table )
   364     arg % initialized = .true.
   373     type(
args), 
intent(inout) :: arg
   376     if (arg % initialized) 
then   377       if ( 
associated( arg % opt_table ) ) 
then   378         do i = 1, 
size(arg % opt_table)
   379           deallocate(arg % opt_table(i) % options)
   382         deallocate(arg % opt_table)
   385       deallocate(arg % cmd_opts_list)
   435     type(
args), 
intent(inout) :: arg
   436     character(len = *), 
intent(in) :: options(:)
   437     logical, 
intent(out) :: flag
   438     character(len = *), 
intent(out), 
optional :: value
   439     character(len = *), 
intent(in), 
optional :: help
   440     integer :: i, j, options_size, table_size
   441     type(
opt_entry), 
allocatable :: local_tables(:)
   442     character(len = STRING) :: opt_name, opt_value, opt_full
   443     character(len = *), 
parameter  :: subname = 
'DCArgsOption'   446     if (
present(
value)) 
value = 
''   447     if (.not. arg % initialized) 
then   448       call messagenotify(
'W', subname, 
'Call Open before Option in dc_args.')
   451     options_size = 
size(options)
   452     if (options_size < 1) 
then   460     if ( .not. 
associated( arg % opt_table ) ) 
then   464       allocate(arg % opt_table(table_size + 1))
   468       table_size = 
size(arg % opt_table)
   469       allocate(local_tables(table_size))
   470       local_tables(1:table_size) = arg % opt_table(1:table_size)
   471       deallocate(arg % opt_table)
   472       allocate(arg % opt_table(table_size + 1))
   473       arg % opt_table(1:table_size) = local_tables(1:table_size)
   474       deallocate(local_tables)
   478     allocate(arg % opt_table(table_size + 1) % options(options_size))
   479     arg % opt_table(table_size + 1) % options = options
   480     arg % opt_table(table_size + 1) % help_message = 
''   481     if (
present(
help)) 
then   482       arg % opt_table(table_size + 1) % help_message = 
help   484     arg % opt_table(table_size + 1) % optvalue_flag = 
present(
value)
   488     do i = 1, options_size
   489       opt_full = arg % opt_table(table_size + 1) % options(i)
   491         arg % opt_table(table_size + 1) % options(i) = opt_name
   493         if (len(trim(adjustl(opt_full))) < 2) 
then   494           arg % opt_table(table_size + 1) % options(i) = &
   495             & 
'-' // trim(adjustl(opt_full))
   497           arg % opt_table(table_size + 1) % options(i) = &
   498             & 
'--' // trim(adjustl(opt_full))
   506     do i = 1, options_size
   507       do j = 1, 
size(arg % cmd_opts_list)
   508         if (trim(arg % opt_table(table_size + 1) % options(i)) &
   509           &             == trim(arg % cmd_opts_list(j) % name)) 
then   511           if (
present(
value)) 
then   512             value = arg % cmd_opts_list(j) % value
   514           arg % cmd_opts_list(j) % flag_called = .true.
   532     type(
args), 
intent(inout) :: arg
   534     character(STRING) :: VAL_debug
   535     character(len = *), 
parameter  :: subname = 
'DCArgsDebug'   537     if (.not. arg % initialized) 
then   538       call messagenotify(
'W', subname, 
'Call Open before Debug in dc_args.')
   541     call option(arg, 
stoa(
'-D', 
'--debug'), opt_debug, val_debug, &
   542       & 
help=
"call dc_trace#SetDebug (display a lot of messages for debug). " // &
   543       & 
"VAL is unit number (default is standard output)")
   545       if (trim(val_debug) == 
'') 
then   577     type(
args), 
intent(inout) :: arg
   578     logical, 
intent(in), 
optional :: force
   579     logical :: OPT_help, found, end
   580     character(STRING) :: VAL_help, options_msg, help_msg, category
   581     character(STRING), 
pointer :: localopts(:) => null()
   583     character(len = *), 
parameter  :: subname = 
'DCArgsHelp'   585     if (.not. arg % initialized) 
then   586       call messagenotify(
'W', subname, 
'Call Open before Help in dc_args.')
   590       & 
help=
"display this help and exit. " // &
   591       & 
"VAL is unit number (default is standard output)")
   595     if (trim(val_help) == 
'') 
then   598       unit = 
stoi(val_help)
   603     call dchashget(arg % helpmsg, 
'TITLE', help_msg, found)
   605       call printf(unit, 
'%c', c1=trim(help_msg))
   610     call dchashget(arg % helpmsg, 
'OVERVIEW', help_msg, found)
   612       call printf(unit, 
'Overview::')
   618     call dchashget(arg % helpmsg, 
'USAGE', help_msg, found)
   620       call printf(unit, 
'Usage::')
   626     call printf(unit, 
'Options::')
   627     if ( 
associated(arg % opt_table) ) 
then   628       do i = 1, 
size(arg % opt_table)
   630         if (arg % opt_table(i) % optvalue_flag) 
then   631           call concat(arg % opt_table(i) % options, 
'=VAL', localopts)
   633           allocate(localopts(
size(arg % opt_table(i) % options)))
   634           localopts = arg % opt_table(i) % options
   636         options_msg = trim(options_msg) // trim(
joinchar(localopts))
   637         deallocate(localopts)
   638         call printf(unit, 
' %c', c1=trim(options_msg))
   640           & arg % opt_table(i) % help_message, indent=
'     ')
   647       call dchashnext(arg % helpmsg, category, help_msg, end)
   650       call printf(unit, 
'%c%c::', &
   651         & c1=trim(
uchar(category(1:1))), c2=trim(
lchar(category(2:))))
   732     type(
args), 
intent(inout) :: arg
   733     character(*), 
intent(in) :: category
   734     character(*), 
intent(in) :: msg
   735     character(len = *), 
parameter  :: subname = 
'DCArgsHelpMsg'   737     if (.not. arg % initialized) 
then   738       call messagenotify(
'W', subname, 
'Call Open before Help in dc_args.')
   765     type(
args), 
intent(inout) :: arg
   766     logical, 
intent(in), 
optional :: severe
   767     character(STRING) :: err_mess
   769     character(len = *), 
parameter  :: subname = 
'DCArgsStrict'   771     if (.not. arg % initialized) 
then   772       call messagenotify(
'W', subname, 
'Call Open before Help in dc_args.')
   775     do i = 1, 
size(arg % cmd_opts_list)
   776       err_mess = trim(arg % cmd_opts_list(i) % name) // 
' is invalid option.'   777       if (.not. arg % cmd_opts_list(i) % flag_called) 
then   801     type(
args), 
intent(inout) :: arg
   802     character(*), 
pointer :: argv(:) 
   803     integer :: i, cmd_argv_max
   804     character(len = *), 
parameter  :: subname = 
'DCArgsGet'   806     if (.not. arg % initialized) 
then   807       call messagenotify(
'W', subname, 
'Call Open before Help in dc_args.')
   811     allocate(argv(cmd_argv_max))
   812     do i = 1, cmd_argv_max
   823     type(
args), 
intent(inout) :: arg
   825     character(len = *), 
parameter  :: subname = 
'DCArgsNumber'   827     if (.not. arg % initialized) 
then   828       call messagenotify(
'W', subname, 
'Call Open before Help in dc_args.')
   841     type(
args), 
intent(in) :: arg
   844     if (.not. arg % initialized) 
then   845       call printf(
stdout, 
'#<ARGS:: @initialized=%y>', l=(/arg % initialized/))
   848     call printf(
stdout, 
'#<ARGS:: @initialized=%y,', l=(/arg % initialized/))
   850     if ( 
associated(arg % opt_table) ) 
then   851       do i = 1, 
size(arg % opt_table)
   853         call printf(
stdout, 
'      @options=%c, @help_message=%c, @optvalue_flag=%y', &
   854           & c1=trim(
joinchar(arg % opt_table(i) % options)), &
   855           & c2=trim(arg % opt_table(i) % help_message), &
   856           & l=(/arg % opt_table(i) % optvalue_flag/))
   862     do i = 1, 
size(arg % cmd_opts_list)
   864       call printf(
stdout, 
'      @name=%c, @value=%c, @flag_called=%y', &
   865         & c1=trim(arg % cmd_opts_list(i) % name), &
   866         & c2=trim(arg % cmd_opts_list(i) % value), &
   867         & l=(/arg % cmd_opts_list(i) % flag_called/))
   891     character(*), 
intent(in) :: fmt
   892     integer,      
intent(in), 
optional :: length 
   893     character(*), 
intent(in), 
optional :: indent 
   894     integer,      
intent(in), 
optional :: unit   
   895     character(STRING), 
pointer :: carray_tmp(:) => null()
   896     character(STRING) :: store_str
   897     integer, 
parameter :: default_len = 70
   898     integer :: i, split_len, indent_len, unit_num
   899     logical :: new_line_flag
   901     if (
present(unit)) 
then   907     if (
present(indent)) 
then   908       indent_len = len(indent)
   913     if (
present(length)) 
then   914       split_len = length - indent_len
   916       split_len = default_len - indent_len
   921     call split(fmt, carray_tmp, 
'')
   923     new_line_flag = .true.
   926       if (i > 
size(carray_tmp)) 
then   927         write(unit_num, 
'(A)') trim(store_str)
   931       if (len(trim(store_str)) + len(trim(carray_tmp(i))) > split_len) 
then   932         if (new_line_flag) 
then   933           write(unit_num, 
'(A)') trim(carray_tmp(i))
   936           write(unit_num, 
'(A)') trim(store_str)
   938           new_line_flag = .true.
   943       if (new_line_flag .and. 
present(indent)) 
then   944         store_str = indent // trim(carray_tmp(i))
   946         store_str = trim(store_str) // 
' ' // trim(carray_tmp(i))
   948       new_line_flag = .false.
   965     character(STRING):: raw_arg, name, value
   966     integer:: i, cmd_argv_count, cmd_opts_count, cmd_argv_max, cmd_opts_max
   974         cmd_opts_count = cmd_opts_count + 1
   976         cmd_argv_count = cmd_argv_count + 1
   980     cmd_argv_max = cmd_argv_count
   981     cmd_opts_max = cmd_opts_count
   991         cmd_opts_count = cmd_opts_count + 1
   996         cmd_argv_count = cmd_argv_count + 1
  1014     integer:: i, narg, nargmax
  1015     character(len = STRING):: value
  1016     character(len = STRING), 
allocatable:: localtab(:)
  1020     allocate(localtab(nargmax))
  1025       localtab(narg) = 
value  1030     deallocate(localtab)
  1033   function dcoptionformc(argument, name, value) 
result(result)
  1065     character(len = *), 
intent(in):: argument
  1066     character(len = *), 
intent(out):: name, value
  1070     equal = index(argument, 
'=')
  1071     if (argument(1:1) == 
'-' .and. argument(2:2) /= 
'-') 
then  1073       if (equal == 0) 
then  1074         name = argument(1:2)
  1077         name = argument(1:2)
  1078         value = argument(equal+1: )
  1081     elseif (argument(1:2) == 
'--') 
then  1083       if (equal == 0) 
then  1087         name = argument(1:equal-1)
  1088         value = argument(equal+1: )
 
type(cmd_opts_internal), dimension(:), allocatable, save cmd_opts_list
 
subroutine, public setdebug(debug)
 
subroutine sysdepargget(idx_given, result)
 
logical function, public present_and_true(arg)
 
subroutine dcargsdebug0(arg)
 
subroutine dcargsget0(arg, argv)
 
integer function sysdepargcount()
 
subroutine dcargsputline0(arg)
 
subroutine dcargsopen0(arg)
 
character(string) function, public joinchar(carray, expr)
 
subroutine dcargshelp0(arg, force)
 
subroutine dcargshelpmsg0(arg, category, msg)
 
subroutine dcargsclose0(arg)
 
subroutine printautolinefeed(unit, fmt, length, indent)
 
integer, parameter, public stdout
標準出力の装置番号 
 
character(string), dimension(:), allocatable, save argstr_table
 
integer function dcargsnumber0(arg)
 
subroutine dcargsoption0(arg, options, flag, value, help)
 
character(string), dimension(:), allocatable, save cmd_argv_list
 
logical function dcoptionformc(argument, name, value)
 
subroutine dcargsstrict0(arg, severe)
 
integer, save argind_count
 
integer, parameter, public string
文字列を保持する 文字型変数の種別型パラメタ