new_test Subroutine

public subroutine new_test(self, table, error)

Construct a new test configuration from a TOML data structure

Arguments

Type IntentOptional Attributes Name
type(test_config_t), intent(out) :: self

Instance of the test configuration

type(toml_table), intent(inout) :: table

Instance of the TOML data structure

type(error_t), intent(out), allocatable :: error

Error handling


Source Code

    subroutine new_test(self, table, error)

        !> Instance of the test configuration
        type(test_config_t), intent(out) :: self

        !> Instance of the TOML data structure
        type(toml_table), intent(inout) :: table

        !> Error handling
        type(error_t), allocatable, intent(out) :: error

        type(toml_table), pointer :: child

        call check(table, error)
        if (allocated(error)) return

        call get_value(table, "name", self%name)
        if (.not.allocated(self%name)) then
           call syntax_error(error, "Could not retrieve test name")
           return
        end if
        if (bad_name_error(error,'test',self%name))then
           return
        endif
        call get_value(table, "source-dir", self%source_dir, "test")
        call get_value(table, "main", self%main, "main.f90")

        call get_value(table, "dependencies", child, requested=.false.)
        if (associated(child)) then
            call new_dependencies(self%dependency, child, error=error)
            if (allocated(error)) return
        end if

        call get_list(table, "link", self%link, error)
        if (allocated(error)) return

    end subroutine new_test