Skip to content

Commit

Permalink
Browse files Browse the repository at this point in the history
  • Loading branch information
aradi committed Nov 8, 2024
1 parent 7bbbc7a commit 450e864
Show file tree
Hide file tree
Showing 22 changed files with 1,436 additions and 227 deletions.
8 changes: 5 additions & 3 deletions src/fortuno.f90
Original file line number Diff line number Diff line change
Expand Up @@ -6,15 +6,17 @@
module fortuno
use fortuno_basetypes, only : test_base, test_case_base, test_item, test_list, test_ptr_item,&
& test_suite_base
use fortuno_chartypes, only : char_rep, char_rep_int, named_details, named_item, named_state
use fortuno_chartypes, only : stringable, details_dict, dict_item, state_dict,&
& matches_type_value, get_ptr_to
use fortuno_consolelogger, only : console_logger
use fortuno_env, only : nl
use fortuno_testcontext, only : context_factory, test_context
use fortuno_checkers, only : is_equal
use fortuno_checkers, only : all_close, all_equal, is_close, is_equal
use fortuno_cmdapp, only : cmd_app
use fortuno_testdriver, only : init_test_driver, test_driver, test_runner, test_selection
use fortuno_testinfo, only : check_result, drive_result, failure_info, failure_location,&
& init_drive_result, init_failure_location, test_result, teststatus
use fortuno_utils, only : as_char, nl
use fortuno_utils, only : str
implicit none

end module fortuno
25 changes: 13 additions & 12 deletions src/fortuno/argumentparser.f90
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,9 @@

!> Implements a simple command line argument parser
module fortuno_argumentparser
use fortuno_env, only : nl
use fortuno_testlogger, only : test_logger
use fortuno_utils, only : basename, nl, string, string_list
use fortuno_utils, only : basename, string_item, string_item_list
implicit none

private
Expand Down Expand Up @@ -125,7 +126,7 @@ subroutine argument_parser_parse_args(this, argumentvalues, logger, exitcode)
!> Exit code (-1, if processing can continue, >= 0 if processing should stop)
integer, intent(out) :: exitcode

type(string), allocatable :: cmdargs(:), posargs(:)
type(string_item), allocatable :: cmdargs(:), posargs(:)
logical, allocatable :: processed(:)
character(:), allocatable :: argname
integer :: nargs, nargdefs, iarg, iargdef
Expand All @@ -146,13 +147,13 @@ subroutine argument_parser_parse_args(this, argumentvalues, logger, exitcode)
iarg = 0
argloop: do while (iarg < nargs)
iarg = iarg + 1
associate (arg => cmdargs(iarg)%content)
associate (arg => cmdargs(iarg)%value)
if (arg == "--") then
optionsallowed = .false.
cycle
end if
if (.not. optionsallowed .or. arg(1:1) /= "-") then
posargs = [posargs, string(arg)]
posargs = [posargs, string_item(arg)]
cycle
end if
islong = arg(1:min(len(arg), 2)) == "--"
Expand All @@ -161,12 +162,12 @@ subroutine argument_parser_parse_args(this, argumentvalues, logger, exitcode)
else if (len(arg) == 2) then
argname = arg(2:2)
else
call logger%log_error("Invalid short option '" // cmdargs(iarg)%content // "'")
call logger%log_error("Invalid short option '" // cmdargs(iarg)%value // "'")
exitcode = 1
return
end if
if ((islong .and. argname == "help") .or. (.not. islong .and. argname == "h")) then
call print_help_(logger, cmdargs(0)%content, this%description, this%argdefs)
call print_help_(logger, cmdargs(0)%value, this%description, this%argdefs)
exitcode = 0
return
end if
Expand Down Expand Up @@ -228,7 +229,7 @@ subroutine argument_parser_parse_args(this, argumentvalues, logger, exitcode)
nn = size(argumentvalues%argvals)
allocate(argvalbuffer(nn + 1))
argvalbuffer(1 : nn) = argumentvalues%argvals
argvalbuffer(nn + 1) = argument_value(argdef%name, argval=string_list(posargs))
argvalbuffer(nn + 1) = argument_value(argdef%name, argval=string_item_list(posargs))
call move_alloc(argvalbuffer, argumentvalues%argvals)
end block
! +}
Expand Down Expand Up @@ -276,7 +277,7 @@ subroutine argument_values_get_value_stringlist(this, name, val)
character(*), intent(in) :: name

!> Value on exit
type(string), allocatable, intent(out) :: val(:)
type(string_item), allocatable, intent(out) :: val(:)

logical :: found
integer :: iargval
Expand All @@ -288,7 +289,7 @@ subroutine argument_values_get_value_stringlist(this, name, val)
end do
if (found) then
select type (argval => this%argvals(iargval)%argval)
type is (string_list)
type is (string_item_list)
val = argval%items
class default
error stop "Invalid argument type for argument '" // name // "'"
Expand Down Expand Up @@ -316,16 +317,16 @@ end function new_argument_value

!! Returns the command line arguments as an array of strings.
subroutine get_command_line_args_(cmdargs)
type(string), allocatable :: cmdargs(:)
type(string_item), allocatable :: cmdargs(:)

integer :: nargs, iarg, arglen

nargs = command_argument_count()
allocate(cmdargs(0:nargs))
do iarg = 0, nargs
call get_command_argument(iarg, length=arglen)
allocate(character(arglen) :: cmdargs(iarg)%content)
call get_command_argument(iarg, value=cmdargs(iarg)%content)
allocate(character(arglen) :: cmdargs(iarg)%value)
call get_command_argument(iarg, value=cmdargs(iarg)%value)
end do

end subroutine get_command_line_args_
Expand Down
Loading

0 comments on commit 450e864

Please sign in to comment.