diff options
-rw-r--r-- | fpm/src/fpm.f90 | 8 | ||||
-rw-r--r-- | fpm/src/fpm/manifest.f90 | 13 | ||||
-rw-r--r-- | fpm/src/fpm/manifest/package.f90 | 13 | ||||
-rw-r--r-- | fpm/test/fpm_test/test_manifest.f90 | 26 |
4 files changed, 8 insertions, 52 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90 index fc22324..bd93b2a 100644 --- a/fpm/src/fpm.f90 +++ b/fpm/src/fpm.f90 @@ -13,7 +13,7 @@ use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t, & use fpm_sources, only: add_executable_sources, add_sources_from_dir, & resolve_module_dependencies use fpm_manifest, only : get_package_data, default_executable, & - default_library, default_build_config, package_t + default_library, package_t use fpm_error, only : error_t use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, & & stdout=>output_unit, & @@ -121,12 +121,6 @@ if (allocated(error)) then error stop 1 end if -! Populate default build configuration if not included -if (.not.allocated(package%build_config)) then - allocate(package%build_config) - call default_build_config(package%build_config) -end if - ! Populate library in case we find the default src directory if (.not.allocated(package%library) .and. exists("src")) then allocate(package%library) diff --git a/fpm/src/fpm/manifest.f90 b/fpm/src/fpm/manifest.f90 index 9b93c2c..0098890 100644 --- a/fpm/src/fpm/manifest.f90 +++ b/fpm/src/fpm/manifest.f90 @@ -17,25 +17,12 @@ module fpm_manifest private public :: get_package_data, default_executable, default_library - public :: default_build_config public :: package_t contains - !> Populate build configuration with defaults - subroutine default_build_config(self) - - !> Instance of the build configuration data - type(build_config_t), intent(out) :: self - - self%auto_executables = .true. - self%auto_tests = .true. - - end subroutine default_build_config - - !> Populate library in case we find the default src directory subroutine default_library(self) diff --git a/fpm/src/fpm/manifest/package.f90 b/fpm/src/fpm/manifest/package.f90 index 4e83411..fcc4e3c 100644 --- a/fpm/src/fpm/manifest/package.f90 +++ b/fpm/src/fpm/manifest/package.f90 @@ -102,12 +102,14 @@ contains return end if - call get_value(table, "build", child, requested=.false.) - if (associated(child)) then - allocate(self%build_config) - call new_build_config(self%build_config, child, error) - if (allocated(error)) return + call get_value(table, "build", child, requested=.true., stat=stat) + if (stat /= toml_stat%success) then + call fatal_error(error, "Type mismatch for build entry, must be a table") + return end if + allocate(self%build_config) + call new_build_config(self%build_config, child, error) + if (allocated(error)) return call get_value(table, "dependencies", child, requested=.false.) if (associated(child)) then @@ -241,7 +243,6 @@ contains end if if (allocated(self%build_config)) then - write(unit, fmt) "- build configuration", "" call self%build_config%info(unit, pr - 1) end if diff --git a/fpm/test/fpm_test/test_manifest.f90 b/fpm/test/fpm_test/test_manifest.f90 index 4b428d1..e711ee4 100644 --- a/fpm/test/fpm_test/test_manifest.f90 +++ b/fpm/test/fpm_test/test_manifest.f90 @@ -22,7 +22,6 @@ contains testsuite = [ & & new_unittest("valid-manifest", test_valid_manifest), & & new_unittest("invalid-manifest", test_invalid_manifest, should_fail=.true.), & - & new_unittest("default-build-configuration", test_default_build_config), & & new_unittest("default-library", test_default_library), & & new_unittest("default-executable", test_default_executable), & & new_unittest("dependency-empty", test_dependency_empty, should_fail=.true.), & @@ -165,31 +164,6 @@ contains end subroutine test_invalid_manifest - !> Create a default build configuration - subroutine test_default_build_config(error) - - !> Error handling - type(error_t), allocatable, intent(out) :: error - - type(package_t) :: package - - allocate(package%build_config) - call default_build_config(package%build_config) - - if (.not. package%build_config%auto_executables) then - call test_failed(error,'Incorrect value for auto_executables in default build configuration, expecting .true.') - return - end if - - if (.not. package%build_config%auto_tests) then - call test_failed(error,'Incorrect value for auto_tests in default build configuration, expecting .true.') - return - end if - - - end subroutine test_default_build_config - - !> Create a default library subroutine test_default_library(error) |