diff options
author | Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> | 2020-09-03 11:13:29 +0200 |
---|---|---|
committer | Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> | 2020-09-03 11:15:43 +0200 |
commit | fd77e6ba357390ec9a21506315b5578aaff513ce (patch) | |
tree | b5b8ea014f431484fcc232f9a743d51b39a0a550 | |
parent | 58ef8896388385d0e79aedb49996367aeacdbb0c (diff) | |
download | fpm-fd77e6ba357390ec9a21506315b5578aaff513ce.tar.gz fpm-fd77e6ba357390ec9a21506315b5578aaff513ce.zip |
Rename config to manifest
-rw-r--r-- | fpm/src/fpm.f90 | 2 | ||||
-rw-r--r-- | fpm/src/fpm/manifest.f90 (renamed from fpm/src/fpm/config.f90) | 10 | ||||
-rw-r--r-- | fpm/src/fpm/manifest/dependency.f90 (renamed from fpm/src/fpm/config/dependency.f90) | 4 | ||||
-rw-r--r-- | fpm/src/fpm/manifest/executable.f90 (renamed from fpm/src/fpm/config/executable.f90) | 6 | ||||
-rw-r--r-- | fpm/src/fpm/manifest/library.f90 (renamed from fpm/src/fpm/config/library.f90) | 4 | ||||
-rw-r--r-- | fpm/src/fpm/manifest/package.f90 (renamed from fpm/src/fpm/config/package.f90) | 12 | ||||
-rw-r--r-- | fpm/src/fpm/manifest/test.f90 (renamed from fpm/src/fpm/config/test.f90) | 8 | ||||
-rw-r--r-- | fpm/src/fpm/toml.f90 | 10 | ||||
-rw-r--r-- | fpm/test/main.f90 | 6 | ||||
-rw-r--r-- | fpm/test/test_manifest.f90 (renamed from fpm/test/test_config.f90) | 42 | ||||
-rw-r--r-- | fpm/test/test_toml.f90 | 16 |
11 files changed, 60 insertions, 60 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90 index 5123436..9c8918b 100644 --- a/fpm/src/fpm.f90 +++ b/fpm/src/fpm.f90 @@ -1,6 +1,6 @@ module fpm use environment, only: get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS -use fpm_config, only : get_package_data, default_executable, default_library, & +use fpm_manifest, only : get_package_data, default_executable, default_library, & & package_t use fpm_error, only : error_t implicit none diff --git a/fpm/src/fpm/config.f90 b/fpm/src/fpm/manifest.f90 index 03ad768..af4e0fa 100644 --- a/fpm/src/fpm/config.f90 +++ b/fpm/src/fpm/manifest.f90 @@ -6,10 +6,10 @@ ! ! Additionally, the required data types for users of this module are reexported ! to hide the actual implementation details. -module fpm_config - use fpm_config_executable, only : executable_t - use fpm_config_library, only : library_t - use fpm_config_package, only : package_t, new_package +module fpm_manifest + use fpm_manifest_executable, only : executable_t + use fpm_manifest_library, only : library_t + use fpm_manifest_package, only : package_t, new_package use fpm_error, only : error_t, fatal_error, file_not_found_error use fpm_toml, only : toml_table, read_package_file implicit none @@ -76,4 +76,4 @@ contains end subroutine get_package_data -end module fpm_config +end module fpm_manifest diff --git a/fpm/src/fpm/config/dependency.f90 b/fpm/src/fpm/manifest/dependency.f90 index d98951f..1ee61b7 100644 --- a/fpm/src/fpm/config/dependency.f90 +++ b/fpm/src/fpm/manifest/dependency.f90 @@ -22,7 +22,7 @@ ! build the target declaring the dependency. ! Resolving a dependency will result in obtaining a new package configuration ! data for the respective project. -module fpm_config_dependency +module fpm_manifest_dependency use fpm_error, only : error_t, syntax_error use fpm_git, only : git_target_t, git_target_tag, git_target_branch, & & git_target_revision, git_target_default @@ -238,4 +238,4 @@ contains end subroutine info -end module fpm_config_dependency +end module fpm_manifest_dependency diff --git a/fpm/src/fpm/config/executable.f90 b/fpm/src/fpm/manifest/executable.f90 index f5078eb..704396a 100644 --- a/fpm/src/fpm/config/executable.f90 +++ b/fpm/src/fpm/manifest/executable.f90 @@ -9,8 +9,8 @@ ! main = "file" ! [executable.dependencies] ! ``` -module fpm_config_executable - use fpm_config_dependency, only : dependency_t, new_dependencies +module fpm_manifest_executable + use fpm_manifest_dependency, only : dependency_t, new_dependencies use fpm_error, only : error_t, syntax_error use fpm_toml, only : toml_table, toml_key, toml_stat, get_value implicit none @@ -170,4 +170,4 @@ contains end subroutine info -end module fpm_config_executable +end module fpm_manifest_executable diff --git a/fpm/src/fpm/config/library.f90 b/fpm/src/fpm/manifest/library.f90 index 0650051..a297c2f 100644 --- a/fpm/src/fpm/config/library.f90 +++ b/fpm/src/fpm/manifest/library.f90 @@ -7,7 +7,7 @@ ! source-dir = "path" ! build-script = "file" ! ``` -module fpm_config_library +module fpm_manifest_library use fpm_error, only : error_t, syntax_error use fpm_toml, only : toml_table, toml_key, toml_stat, get_value implicit none @@ -123,4 +123,4 @@ contains end subroutine info -end module fpm_config_library +end module fpm_manifest_library diff --git a/fpm/src/fpm/config/package.f90 b/fpm/src/fpm/manifest/package.f90 index 66f275d..f318ad7 100644 --- a/fpm/src/fpm/config/package.f90 +++ b/fpm/src/fpm/manifest/package.f90 @@ -27,11 +27,11 @@ ! [[executable]] ! [[test]] ! ``` -module fpm_config_package - use fpm_config_dependency, only : dependency_t, new_dependencies - use fpm_config_executable, only : executable_t, new_executable - use fpm_config_library, only : library_t, new_library - use fpm_config_test, only : test_t, new_test +module fpm_manifest_package + use fpm_manifest_dependency, only : dependency_t, new_dependencies + use fpm_manifest_executable, only : executable_t, new_executable + use fpm_manifest_library, only : library_t, new_library + use fpm_manifest_test, only : test_t, new_test use fpm_error, only : error_t, fatal_error, syntax_error use fpm_toml, only : toml_table, toml_array, toml_key, toml_stat, get_value, & & len @@ -267,4 +267,4 @@ contains end subroutine info -end module fpm_config_package +end module fpm_manifest_package diff --git a/fpm/src/fpm/config/test.f90 b/fpm/src/fpm/manifest/test.f90 index 5c6c9f3..9b50315 100644 --- a/fpm/src/fpm/config/test.f90 +++ b/fpm/src/fpm/manifest/test.f90 @@ -13,9 +13,9 @@ ! main = "file" ! [test.dependencies] ! ``` -module fpm_config_test - use fpm_config_dependency, only : dependency_t, new_dependencies - use fpm_config_executable, only : executable_t +module fpm_manifest_test + use fpm_manifest_dependency, only : dependency_t, new_dependencies + use fpm_manifest_executable, only : executable_t use fpm_error, only : error_t, syntax_error use fpm_toml, only : toml_table, toml_key, toml_stat, get_value implicit none @@ -163,4 +163,4 @@ contains end subroutine info -end module fpm_config_test +end module fpm_manifest_test diff --git a/fpm/src/fpm/toml.f90 b/fpm/src/fpm/toml.f90 index d847c69..d95a093 100644 --- a/fpm/src/fpm/toml.f90 +++ b/fpm/src/fpm/toml.f90 @@ -27,13 +27,13 @@ contains !> Process the configuration file to a TOML data structure - subroutine read_package_file(table, config, error) + subroutine read_package_file(table, manifest, error) !> TOML data structure type(toml_table), allocatable, intent(out) :: table !> Name of the package configuration file - character(len=*), intent(in) :: config + character(len=*), intent(in) :: manifest !> Error status of the operation type(error_t), allocatable, intent(out) :: error @@ -42,14 +42,14 @@ contains integer :: unit logical :: exist - inquire(file=config, exist=exist) + inquire(file=manifest, exist=exist) if (.not.exist) then - call file_not_found_error(error, config) + call file_not_found_error(error, manifest) return end if - open(file=config, newunit=unit) + open(file=manifest, newunit=unit) call toml_parse(table, unit, parse_error) close(unit) diff --git a/fpm/test/main.f90 b/fpm/test/main.f90 index c4bfee5..19bcdb6 100644 --- a/fpm/test/main.f90 +++ b/fpm/test/main.f90 @@ -3,7 +3,7 @@ program fpm_testing use, intrinsic :: iso_fortran_env, only : error_unit use testsuite, only : run_testsuite use test_toml, only : collect_toml - use test_config, only : collect_config + use test_manifest, only : collect_manifest implicit none integer :: stat character(len=*), parameter :: fmt = '("#", *(1x, a))' @@ -16,8 +16,8 @@ program fpm_testing error stop 1 end if - write(error_unit, fmt) "Testing:", "fpm_config" - call run_testsuite(collect_config, error_unit, stat) + write(error_unit, fmt) "Testing:", "fpm_manifest" + call run_testsuite(collect_manifest, error_unit, stat) if (stat > 0) then write(error_unit, '(i0, 1x, a)') stat, "tests failed!" diff --git a/fpm/test/test_config.f90 b/fpm/test/test_manifest.f90 index ecdf0a5..08236d5 100644 --- a/fpm/test/test_config.f90 +++ b/fpm/test/test_manifest.f90 @@ -1,43 +1,43 @@ -!> Define tests for the `fpm_config` modules -module test_config +!> Define tests for the `fpm_manifest` modules +module test_manifest use testsuite, only : new_unittest, unittest_t, error_t, test_failed - use fpm_config + use fpm_manifest implicit none private - public :: collect_config + public :: collect_manifest contains !> Collect all exported unit tests - subroutine collect_config(testsuite) + subroutine collect_manifest(testsuite) !> Collection of tests type(unittest_t), allocatable, intent(out) :: testsuite(:) testsuite = [ & - & new_unittest("valid-config", test_valid_config), & - & new_unittest("invalid-config", test_invalid_config, should_fail=.true.), & + & new_unittest("valid-manifest", test_valid_manifest), & + & new_unittest("invalid-manifest", test_invalid_manifest, should_fail=.true.), & & new_unittest("default-library", test_default_library), & & new_unittest("default-executable", test_default_executable)] - end subroutine collect_config + end subroutine collect_manifest !> Try to read some unnecessary obscure and convoluted but not invalid package file - subroutine test_valid_config(error) + subroutine test_valid_manifest(error) !> Error handling type(error_t), allocatable, intent(out) :: error type(package_t) :: package - character(len=*), parameter :: config = 'fpm-valid-config.toml' + character(len=*), parameter :: manifest = 'fpm-valid-manifest.toml' character(len=:), allocatable :: string integer :: unit - open(file=config, newunit=unit) + open(file=manifest, newunit=unit) write(unit, '(a)') & & 'name = "example"', & & '[dependencies.fpm]', & @@ -57,9 +57,9 @@ contains & 'lib""" # comment' close(unit) - call get_package_data(package, config, error) + call get_package_data(package, manifest, error) - open(file=config, newunit=unit) + open(file=manifest, newunit=unit) close(unit, status='delete') if (allocated(error)) return @@ -99,33 +99,33 @@ contains return end if - end subroutine test_valid_config + end subroutine test_valid_manifest !> Try to read a valid TOML document which represent an invalid package file - subroutine test_invalid_config(error) + subroutine test_invalid_manifest(error) !> Error handling type(error_t), allocatable, intent(out) :: error type(package_t) :: package - character(len=*), parameter :: config = 'fpm-invalid-config.toml' + character(len=*), parameter :: manifest = 'fpm-invalid-manifest.toml' character(len=:), allocatable :: string integer :: unit - open(file=config, newunit=unit) + open(file=manifest, newunit=unit) write(unit, '(a)') & & '[package]', & & 'name = "example"', & & 'version = "0.1.0"' close(unit) - call get_package_data(package, config, error) + call get_package_data(package, manifest, error) - open(file=config, newunit=unit) + open(file=manifest, newunit=unit) close(unit, status='delete') - end subroutine test_invalid_config + end subroutine test_invalid_manifest !> Create a default library @@ -185,4 +185,4 @@ contains end subroutine test_default_executable -end module test_config +end module test_manifest diff --git a/fpm/test/test_toml.f90 b/fpm/test/test_toml.f90 index 8d57150..d30ef0d 100644 --- a/fpm/test/test_toml.f90 +++ b/fpm/test/test_toml.f90 @@ -31,11 +31,11 @@ contains type(error_t), allocatable, intent(out) :: error type(toml_table), allocatable :: table - character(len=*), parameter :: config = 'fpm-valid-toml.toml' + character(len=*), parameter :: manifest = 'fpm-valid-toml.toml' character(len=:), allocatable :: string integer :: unit - open(file=config, newunit=unit) + open(file=manifest, newunit=unit) write(unit, '(a)') & & 'name = "example"', & & '[dependencies.fpm]', & @@ -55,9 +55,9 @@ contains & 'lib""" # comment' close(unit) - call read_package_file(table, config, error) + call read_package_file(table, manifest, error) - open(file=config, newunit=unit) + open(file=manifest, newunit=unit) close(unit, status='delete') end subroutine test_valid_toml @@ -70,11 +70,11 @@ contains type(error_t), allocatable, intent(out) :: error type(toml_table), allocatable :: table - character(len=*), parameter :: config = 'fpm-invalid-toml.toml' + character(len=*), parameter :: manifest = 'fpm-invalid-toml.toml' character(len=:), allocatable :: string integer :: unit - open(file=config, newunit=unit) + open(file=manifest, newunit=unit) write(unit, '(a)') & & '# INVALID TOML DOC', & & 'name = "example"', & @@ -84,9 +84,9 @@ contains & '"toml..f" = { path = ".." }' close(unit) - call read_package_file(table, config, error) + call read_package_file(table, manifest, error) - open(file=config, newunit=unit) + open(file=manifest, newunit=unit) close(unit, status='delete') end subroutine test_invalid_toml |