mctc_env_testing Module

Provides a light-weight testing framework for usage in projects depending on the tool chain library.

Testsuites are defined by a collect_interface returning a set of unittest_type objects. To create a new test use the new_unittest constructor, which requires a test identifier and a procedure with a test_interface compatible signature. The error status is communicated by the allocation status of an error_type.

The necessary boilerplate code to setup the test entry point is just

program tester
   use, intrinsic :: iso_fortran_env, only : error_unit
   use mctc_env_testing, only : run_testsuite, new_testsuite, testsuite_type
   use test_suite1, only : collect_suite1
   use test_suite2, only : collect_suite2
   implicit none
   integer :: stat, ii
   type(testsuite_type), allocatable :: testsuites(:)
   character(len=*), parameter :: fmt = '("#", *(1x, a))'

   stat = 0

   testsuites = [ &
      & new_testsuite("suite1", collect_suite1), &
      & new_testsuite("suite2", collect_suite2) &
      & ]

   do ii = 1, size(testsuites)
      write(error_unit, fmt) "Testing:", testsuites(ii)%name
      call run_testsuite(testsuites(ii)%collect, error_unit, stat)
   end do

   if (stat > 0) then
      write(error_unit, '(i0, 1x, a)') stat, "test(s) failed!"
      error stop
   end if

end program tester

Every test is defined in a separate module using a collect function, which is exported and added to the testsuites array in the test runner. All test have a simple interface with just an allocatable error_type as output to provide the test results.

module test_suite1
   use mctc_env_testing, only : new_unittest, unittest_type, error_type, check
   implicit none
   private

   public :: collect_suite1

contains

!> Collect all exported unit tests
subroutine collect_suite1(testsuite)
   !> Collection of tests
   type(unittest_type), allocatable, intent(out) :: testsuite(:)

   testsuite = [ &
      & new_unittest("valid", test_valid), &
      & new_unittest("invalid", test_invalid, should_fail=.true.) &
      & ]

end subroutine collect_suite1

subroutine test_valid(error)
   type(error_type), allocatable, intent(out) :: error
   ! ...
end subroutine test_valid

subroutine test_invalid(error)
   type(error_type), allocatable, intent(out) :: error
   ! ...
end subroutine test_invalid

end module test_suite1

For an example setup checkout the test/ directory in this project.



Interfaces

public interface check

  • private subroutine check_stat(error, stat, message, more)

    Arguments

    Type IntentOptional Attributes Name
    type(error_type), intent(out), allocatable :: error

    Error handling

    integer, intent(in) :: stat

    Status of operation

    character(len=*), intent(in), optional :: message

    A detailed message describing the error

    character(len=*), intent(in), optional :: more

    Another line of error message

  • private subroutine check_logical(error, expression, message, more)

    Arguments

    Type IntentOptional Attributes Name
    type(error_type), intent(out), allocatable :: error

    Error handling

    logical, intent(in) :: expression

    Result of logical operator

    character(len=*), intent(in), optional :: message

    A detailed message describing the error

    character(len=*), intent(in), optional :: more

    Another line of error message

  • private subroutine check_float_sp(error, actual, expected, message, more, thr, rel)

    Arguments

    Type IntentOptional Attributes Name
    type(error_type), intent(out), allocatable :: error

    Error handling

    real(kind=sp), intent(in) :: actual

    Found floating point value

    real(kind=sp), intent(in) :: expected

    Expected floating point value

    character(len=*), intent(in), optional :: message

    A detailed message describing the error

    character(len=*), intent(in), optional :: more

    Another line of error message

    real(kind=sp), intent(in), optional :: thr

    Allowed threshold for matching floating point values

    logical, intent(in), optional :: rel

    Check for relative errors instead

  • private subroutine check_float_dp(error, actual, expected, message, more, thr, rel)

    Arguments

    Type IntentOptional Attributes Name
    type(error_type), intent(out), allocatable :: error

    Error handling

    real(kind=dp), intent(in) :: actual

    Found floating point value

    real(kind=dp), intent(in) :: expected

    Expected floating point value

    character(len=*), intent(in), optional :: message

    A detailed message describing the error

    character(len=*), intent(in), optional :: more

    Another line of error message

    real(kind=dp), intent(in), optional :: thr

    Allowed threshold for matching floating point values

    logical, intent(in), optional :: rel

    Check for relative errors instead

  • private subroutine check_int_i1(error, actual, expected, message, more)

    Arguments

    Type IntentOptional Attributes Name
    type(error_type), intent(out), allocatable :: error

    Error handling

    integer(kind=i1), intent(in) :: actual

    Found integer value

    integer(kind=i1), intent(in) :: expected

    Expected integer value

    character(len=*), intent(in), optional :: message

    A detailed message describing the error

    character(len=*), intent(in), optional :: more

    Another line of error message

  • private subroutine check_int_i2(error, actual, expected, message, more)

    Arguments

    Type IntentOptional Attributes Name
    type(error_type), intent(out), allocatable :: error

    Error handling

    integer(kind=i2), intent(in) :: actual

    Found integer value

    integer(kind=i2), intent(in) :: expected

    Expected integer value

    character(len=*), intent(in), optional :: message

    A detailed message describing the error

    character(len=*), intent(in), optional :: more

    Another line of error message

  • private subroutine check_int_i4(error, actual, expected, message, more)

    Arguments

    Type IntentOptional Attributes Name
    type(error_type), intent(out), allocatable :: error

    Error handling

    integer(kind=i4), intent(in) :: actual

    Found integer value

    integer(kind=i4), intent(in) :: expected

    Expected integer value

    character(len=*), intent(in), optional :: message

    A detailed message describing the error

    character(len=*), intent(in), optional :: more

    Another line of error message

  • private subroutine check_int_i8(error, actual, expected, message, more)

    Arguments

    Type IntentOptional Attributes Name
    type(error_type), intent(out), allocatable :: error

    Error handling

    integer(kind=i8), intent(in) :: actual

    Found integer value

    integer(kind=i8), intent(in) :: expected

    Expected integer value

    character(len=*), intent(in), optional :: message

    A detailed message describing the error

    character(len=*), intent(in), optional :: more

    Another line of error message

  • private subroutine check_bool(error, actual, expected, message, more)

    Arguments

    Type IntentOptional Attributes Name
    type(error_type), intent(out), allocatable :: error

    Error handling

    logical, intent(in) :: actual

    Found boolean value

    logical, intent(in) :: expected

    Expected boolean value

    character(len=*), intent(in), optional :: message

    A detailed message describing the error

    character(len=*), intent(in), optional :: more

    Another line of error message

  • private subroutine check_string(error, actual, expected, message, more)

    Arguments

    Type IntentOptional Attributes Name
    type(error_type), intent(out), allocatable :: error

    Error handling

    character(len=*), intent(in) :: actual

    Found boolean value

    character(len=*), intent(in) :: expected

    Expected boolean value

    character(len=*), intent(in), optional :: message

    A detailed message describing the error

    character(len=*), intent(in), optional :: more

    Another line of error message


Abstract Interfaces

abstract interface

  • public subroutine collect_interface(testsuite)

    Collect all tests

    Arguments

    Type IntentOptional Attributes Name
    type(unittest_type), intent(out), allocatable :: testsuite(:)

    Collection of tests

abstract interface

  • public subroutine test_interface(error)

    Entry point for tests

    Arguments

    Type IntentOptional Attributes Name
    type(error_type), intent(out), allocatable :: error

    Error handling


Derived Types

type, public ::  testsuite_type

Collection of unit tests

Components

Type Visibility Attributes Name Initial
procedure(collect_interface), public, pointer, nopass :: collect => null()

Entry point of the test

character(len=:), public, allocatable :: name

Name of the testsuite

type, public ::  unittest_type

Declaration of a unit test

Components

Type Visibility Attributes Name Initial
character(len=:), public, allocatable :: name

Name of the test

logical, public :: should_fail = .false.

Whether test is supposed to fail

procedure(test_interface), public, pointer, nopass :: test => null()

Entry point of the test


Functions

public function new_testsuite(name, collect) result(self)

Register a new testsuite

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: name

Name of the testsuite

procedure(collect_interface) :: collect

Entry point to collect tests

Return Value type(testsuite_type)

Newly registered testsuite

public function new_unittest(name, test, should_fail) result(self)

Register a new unit test

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: name

Name of the test

procedure(test_interface) :: test

Entry point for the test

logical, intent(in), optional :: should_fail

Whether test is supposed to error or not

Return Value type(unittest_type)

Newly registered test

public function select_suite(suites, name) result(pos)

Select a test suite from all available suites

Arguments

Type IntentOptional Attributes Name
type(testsuite_type) :: suites(:)

Available test suites

character(len=*), intent(in) :: name

Name identifying the test suite

Return Value integer

Selected test suite

public function select_test(tests, name) result(pos)

Select a unit test from all available tests

Arguments

Type IntentOptional Attributes Name
type(unittest_type) :: tests(:)

Available unit tests

character(len=*), intent(in) :: name

Name identifying the test suite

Return Value integer

Selected test suite


Subroutines

public subroutine run_selected(collect, name, unit, stat)

Driver for selective testing

Arguments

Type IntentOptional Attributes Name
procedure(collect_interface) :: collect

Collect tests

character(len=*), intent(in) :: name

Name of the selected test

integer, intent(in) :: unit

Unit for IO

integer, intent(inout) :: stat

Number of failed tests

public subroutine run_testsuite(collect, unit, stat, parallel)

Driver for testsuite

Arguments

Type IntentOptional Attributes Name
procedure(collect_interface) :: collect

Collect tests

integer, intent(in) :: unit

Unit for IO

integer, intent(inout) :: stat

Number of failed tests

logical, intent(in), optional :: parallel

Run tests in parallel

public subroutine test_failed(error, message, more)

Arguments

Type IntentOptional Attributes Name
type(error_type), intent(out), allocatable :: error

Error handling

character(len=*), intent(in) :: message

A detailed message describing the error

character(len=*), intent(in), optional :: more

Another line of error message