Skip to content

Commit

Permalink
Rename stringable to char_rep
Browse files Browse the repository at this point in the history
  • Loading branch information
aradi committed Mar 23, 2024
1 parent 06f766e commit 3ac882d
Show file tree
Hide file tree
Showing 10 changed files with 45 additions and 44 deletions.
9 changes: 5 additions & 4 deletions example/fixtured_tests.f90
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,9 @@

module fixtured_tests
use mylib, only : factorial
use fortuno_serial, only : check => serial_check, named_state, failed => serial_failed,&
& named_item, test => serial_case_item, suite => serial_suite_item,&
& store_state => serial_store_state, serial_case_base, stringable_int, test_item
use fortuno_serial, only : char_rep_int, check => serial_check, named_state,&
& failed => serial_failed, named_item, test => serial_case_item, suite => serial_suite_item,&
& store_state => serial_store_state, serial_case_base, test_item
implicit none

private
Expand Down Expand Up @@ -82,9 +82,10 @@ subroutine random_test_case_run(this)
! Set-up fixture by creating a random number
call random_number(rand)
nn = int(20.0 * rand) + 1
! Store internal state to aid introspection/identification later
call store_state(&
named_state([&
named_item("n", stringable_int(nn))&
named_item("n", char_rep_int(nn))&
&])&
)
call this%proc(nn)
Expand Down
2 changes: 1 addition & 1 deletion src/fortuno.f90
Original file line number Diff line number Diff line change
Expand Up @@ -5,11 +5,11 @@
!> Interface module for the core library of the Fortuno testing framework
module fortuno
use fortuno_basetypes, only : test_base, test_case_base, test_item, test_ptr_item, test_suite_base
use fortuno_chartypes, only : char_rep, char_rep_int, named_details, named_item, named_state
use fortuno_consolelogger, only : console_logger
use fortuno_testcontext, only : context_factory, test_context
use fortuno_checkers, only : is_equal
use fortuno_cmdapp, only : cmd_app
use fortuno_namedtypes, only : named_details, named_item, named_state, stringable, stringable_int
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
Expand Down
2 changes: 1 addition & 1 deletion src/fortuno/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -6,10 +6,10 @@ target_sources(
fortuno PRIVATE
argumentparser.f90
basetypes.f90
chartypes.f90
checkers.f90
cmdapp.f90
consolelogger.f90
namedtypes.f90
testcontext.f90
testdriver.f90
testinfo.f90
Expand Down
44 changes: 22 additions & 22 deletions src/fortuno/namedtypes.f90 → src/fortuno/chartypes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -2,38 +2,38 @@
! Licensed under the BSD-2-Clause Plus Patent license.
! SPDX-License-Identifier: BSD-2-Clause-Patent

!> Contains a trivial implementation of name value pairs
module fortuno_namedtypes
!> Contains various types related to character representations.
module fortuno_chartypes
use fortuno_utils, only : as_char, nl, string, to_upper
implicit none

private
public :: stringable
public :: char_rep
public :: char_rep_int
public :: named_item, named_details, named_state
public :: stringable_int


!> Character representable object.
type, abstract :: stringable
type, abstract :: char_rep
contains
procedure(stringable_as_char), deferred :: as_char
end type stringable
procedure(char_rep_as_char), deferred :: as_char
end type char_rep


abstract interface

!> Character representation of the stringable object.
function stringable_as_char(this) result(repr)
import :: stringable
!> Character representation of the char_rep object.
function char_rep_as_char(this) result(repr)
import :: char_rep
implicit none

!> Instance
class(stringable), intent(in) :: this
class(char_rep), intent(in) :: this

!> Character representation of the object.
character(:), allocatable :: repr

end function stringable_as_char
end function char_rep_as_char

end interface

Expand All @@ -58,7 +58,7 @@ end function stringable_as_char


!> Represents failure details with an array of named items.
type, extends(stringable) :: named_details
type, extends(char_rep) :: named_details

!> Items containing the information about the failure details
type(named_item), allocatable :: items(:)
Expand All @@ -69,7 +69,7 @@ end function stringable_as_char


!> Represents test internal state with an array of named items.
type, extends(stringable) :: named_state
type, extends(char_rep) :: named_state

!> Items containing the information about the failure details
type(named_item), allocatable :: items(:)
Expand All @@ -80,14 +80,14 @@ end function stringable_as_char


!> Integer with string representation.
type, extends(stringable) :: stringable_int
type, extends(char_rep) :: char_rep_int

!> Value
integer :: value

contains
procedure :: as_char => stringable_int_as_char
end type stringable_int
procedure :: as_char => char_rep_int_as_char
end type char_rep_int

contains

Expand Down Expand Up @@ -129,17 +129,17 @@ end function named_state_as_char


!> Integer with string representation.
function stringable_int_as_char(this) result(repr)
function char_rep_int_as_char(this) result(repr)

!> Instance
class(stringable_int), intent(in) :: this
class(char_rep_int), intent(in) :: this

!> Character representation
character(:), allocatable :: repr

repr = as_char(this%value)

end function stringable_int_as_char
end function char_rep_int_as_char


!> Explicit constructor for named_item (to avoid gfortran compilation problems)
Expand Down Expand Up @@ -184,7 +184,7 @@ subroutine get_named_items_as_char_(items, repr, itemsep, namesep, capitalizenam
valuestrings(iitem)%content = namedvalue
class is (string)
valuestrings(iitem)%content = namedvalue%content
class is (stringable)
class is (char_rep)
valuestrings(iitem)%content = namedvalue%as_char()
class default
valuestrings(iitem)%content = "???"
Expand Down Expand Up @@ -218,4 +218,4 @@ subroutine get_named_items_as_char_(items, repr, itemsep, namesep, capitalizenam

end subroutine get_named_items_as_char_

end module fortuno_namedtypes
end module fortuno_chartypes
6 changes: 3 additions & 3 deletions src/fortuno/checkers.f90
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@

!> Contains some built-in checkers
module fortuno_checkers
use fortuno_namedtypes, only : named_details, named_item, stringable_int
use fortuno_chartypes, only : char_rep_int, named_details, named_item
use fortuno_testinfo, only : check_result
use fortuno_utils, only : string
implicit none
Expand Down Expand Up @@ -39,8 +39,8 @@ function is_equal_i0_i0(obtained, expected) result(checkresult)
if (.not. checkresult%success) then
checkresult%details = named_details([&
& named_item("failure", "Mismatching integer values"),&
& named_item("expected", stringable_int(expected)),&
& named_item("obtained", stringable_int(obtained))&
& named_item("expected", char_rep_int(expected)),&
& named_item("obtained", char_rep_int(obtained))&
& ])
end if

Expand Down
2 changes: 1 addition & 1 deletion src/fortuno/meson.build
Original file line number Diff line number Diff line change
Expand Up @@ -5,10 +5,10 @@
fortuno_sources += files(
'argumentparser.f90',
'basetypes.f90',
'chartypes.f90',
'checkers.f90',
'cmdapp.f90',
'consolelogger.f90',
'namedtypes.f90',
'testcontext.f90',
'testdriver.f90',
'testinfo.f90',
Expand Down
8 changes: 4 additions & 4 deletions src/fortuno/testcontext.f90
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@
!> Contains the base context definition
module fortuno_testcontext
use fortuno_basetypes, only : test_base, test_ptr_item
use fortuno_namedtypes, only : stringable
use fortuno_chartypes, only : char_rep
use fortuno_testinfo, only : check_result, failure_info, failure_location, init_failure_location,&
& teststatus
implicit none
Expand All @@ -25,7 +25,7 @@ module fortuno_testcontext
type(failure_info), allocatable :: failureinfo_

!> Info about the internal state of the test
class(stringable), allocatable :: state_
class(char_rep), allocatable :: state_

!> Status of the context
integer :: status_ = teststatus%succeeded
Expand Down Expand Up @@ -325,7 +325,7 @@ subroutine test_context_store_state(this, state)
class(test_context), intent(inout) :: this

!> Arbitrary (character representable) state object
class(stringable), intent(in) :: state
class(char_rep), intent(in) :: state

this%state_ = state

Expand All @@ -339,7 +339,7 @@ subroutine test_context_pop_state(this, state)
class(test_context), intent(inout) :: this

!> Popped state object
class(stringable), allocatable, intent(out) :: state
class(char_rep), allocatable, intent(out) :: state

if (allocated(this%state_)) call move_alloc(this%state_, state)

Expand Down
6 changes: 3 additions & 3 deletions src/fortuno/testdriver.f90
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@
!> Implements a generic test driver
module fortuno_testdriver
use fortuno_basetypes, only : test_base, test_case_base, test_item, test_suite_base
use fortuno_namedtypes, only : stringable
use fortuno_chartypes, only : char_rep
use fortuno_testcontext, only : context_factory, test_context
use fortuno_testinfo, only : drive_result, init_drive_result, test_result, teststatus
use fortuno_testlogger, only : test_logger, testtypes
Expand Down Expand Up @@ -406,7 +406,7 @@ recursive subroutine run_test_(testitems, identifier, ctx, runner, repr)
character(:), allocatable, intent(out) :: repr

class(test_base), pointer :: scopeptr
class(stringable), allocatable :: state
class(char_rep), allocatable :: state

scopeptr => testitems(identifier(1))%item
call ctx%push_scope_ptr(scopeptr)
Expand Down Expand Up @@ -441,7 +441,7 @@ recursive subroutine initialize_finalize_suite_(testitems, identifier, init, ctx
character(:), allocatable, intent(out) :: repr

class(test_base), pointer :: scopeptr
class(stringable), allocatable :: state
class(char_rep), allocatable :: state

scopeptr => testitems(identifier(1))%item
call ctx%push_scope_ptr(scopeptr)
Expand Down
6 changes: 3 additions & 3 deletions src/fortuno/testinfo.f90
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@

!> Types containing informations about tests and checks
module fortuno_testinfo
use fortuno_namedtypes, only : stringable
use fortuno_chartypes, only : char_rep
use fortuno_utils, only : as_char, nl
implicit none

Expand Down Expand Up @@ -45,7 +45,7 @@ module fortuno_testinfo
logical :: success = .false.

!> Further character representable information about the check (reason of failure)
class(stringable), allocatable :: details
class(char_rep), allocatable :: details

end type check_result

Expand Down Expand Up @@ -77,7 +77,7 @@ module fortuno_testinfo
class(failure_location), allocatable :: location

!> Character representable internal details of the check
class(stringable), allocatable :: details
class(char_rep), allocatable :: details

!> Contains previous failure_info (to be able to chain check infos)
type(failure_info), allocatable :: previous
Expand Down
4 changes: 2 additions & 2 deletions src/fortuno_serial/serialglobalctx.f90
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@

!> Global serial context to avoid explicit passing of context when using non-threaded serial driver
module fortuno_serial_serialglobalctx
use fortuno, only : check_result, stringable, test_ptr_item
use fortuno, only : check_result, char_rep, test_ptr_item
use fortuno_serial_serialcontext, only : serial_context
implicit none

Expand Down Expand Up @@ -126,7 +126,7 @@ end function serial_scope_pointers
subroutine serial_store_state(state)

!> State to store
class(stringable), intent(in) :: state
class(char_rep), intent(in) :: state

call serialglobalctx%store_state(state)

Expand Down

0 comments on commit 3ac882d

Please sign in to comment.