diff options
author | LKedward <laurence.kedward@bristol.ac.uk> | 2020-09-29 12:35:33 +0100 |
---|---|---|
committer | LKedward <laurence.kedward@bristol.ac.uk> | 2020-09-29 12:35:33 +0100 |
commit | 99da449d12232615ef1f57ea37f2c063755c2bee (patch) | |
tree | 91e98ba6b0fe98afea7bed3c5a7c3fa930900918 | |
parent | f10b174e6676031af9f32f704d9b317525fa5602 (diff) | |
download | fpm-99da449d12232615ef1f57ea37f2c063755c2bee.tar.gz fpm-99da449d12232615ef1f57ea37f2c063755c2bee.zip |
Add: [build] table to manifest with flags for auto-discovery
-rw-r--r-- | fpm/src/fpm.f90 | 24 | ||||
-rw-r--r-- | fpm/src/fpm/manifest.f90 | 14 | ||||
-rw-r--r-- | fpm/src/fpm/manifest/build_config.f90 | 140 | ||||
-rw-r--r-- | fpm/src/fpm/manifest/package.f90 | 18 |
4 files changed, 188 insertions, 8 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90 index a879341..9db2126 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, package_t + default_library, default_build_config, package_t use fpm_error, only : error_t use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, & & stdout=>output_unit, & @@ -57,7 +57,7 @@ subroutine build_model(model, settings, package, error) model%link_flags = '' ! Add sources from executable directories - if (is_dir('app')) then + if (is_dir('app') .and. package%build_config%auto_executables) then call add_sources_from_dir(model%sources,'app', FPM_SCOPE_APP, & with_executables=.true., error=error) @@ -66,7 +66,7 @@ subroutine build_model(model, settings, package, error) end if end if - if (is_dir('test')) then + if (is_dir('test') .and. package%build_config%auto_tests) then call add_sources_from_dir(model%sources,'test', FPM_SCOPE_TEST, & with_executables=.true., error=error) @@ -76,8 +76,9 @@ subroutine build_model(model, settings, package, error) end if if (allocated(package%executable)) then - call add_executable_sources(model%sources, package%executable, & - FPM_SCOPE_APP, auto_discover=.true., error=error) + call add_executable_sources(model%sources, package%executable, FPM_SCOPE_APP, & + auto_discover=package%build_config%auto_executables, & + error=error) if (allocated(error)) then return @@ -85,8 +86,9 @@ subroutine build_model(model, settings, package, error) end if if (allocated(package%test)) then - call add_executable_sources(model%sources, package%test, & - FPM_SCOPE_TEST, auto_discover=.true., error=error) + call add_executable_sources(model%sources, package%test, FPM_SCOPE_TEST, & + auto_discover=package%build_config%auto_tests, & + error=error) if (allocated(error)) then return @@ -119,6 +121,14 @@ if (allocated(error)) then error stop 1 end if +call package%info(stdout,10) + +! 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 af4e0fa..9b93c2c 100644 --- a/fpm/src/fpm/manifest.f90 +++ b/fpm/src/fpm/manifest.f90 @@ -7,6 +7,7 @@ ! Additionally, the required data types for users of this module are reexported ! to hide the actual implementation details. module fpm_manifest + use fpm_manifest_build_config, only: build_config_t use fpm_manifest_executable, only : executable_t use fpm_manifest_library, only : library_t use fpm_manifest_package, only : package_t, new_package @@ -16,12 +17,25 @@ 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/build_config.f90 b/fpm/src/fpm/manifest/build_config.f90 new file mode 100644 index 0000000..069c3e0 --- /dev/null +++ b/fpm/src/fpm/manifest/build_config.f90 @@ -0,0 +1,140 @@ +!> Implementation of the build configuration data. +! +! A build table can currently have the following fields +! +! ```toml +! [build] +! auto-executables = <bool> +! auto-tests = <bool> +! ``` +module fpm_manifest_build_config + use fpm_error, only : error_t, syntax_error, fatal_error + use fpm_toml, only : toml_table, toml_key, toml_stat, get_value + implicit none + private + + public :: build_config_t, new_build_config + + + !> Configuration data for build + type :: build_config_t + + !> Automatic discovery of executables + logical :: auto_executables + + !> Automatic discovery of tests + logical :: auto_tests + + contains + + !> Print information on this instance + procedure :: info + + end type build_config_t + + +contains + + + !> Construct a new build configuration from a TOML data structure + subroutine new_build_config(self, table, error) + + !> Instance of the build configuration + type(build_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 + + !> Status + integer :: stat + + call check(table, error) + if (allocated(error)) return + + call get_value(table, "auto-executables", self%auto_executables, .true., stat=stat) + + if (stat /= toml_stat%success) then + call fatal_error(error,"Error while reading value for 'auto-executables' in fpm.toml, expecting logical") + return + end if + + call get_value(table, "auto-tests", self%auto_tests, .true., stat=stat) + + if (stat /= toml_stat%success) then + call fatal_error(error,"Error while reading value for 'auto-tests' in fpm.toml, expecting logical") + return + end if + + end subroutine new_build_config + + + !> Check local schema for allowed entries + subroutine check(table, error) + + !> Instance of the TOML data structure + type(toml_table), intent(inout) :: table + + !> Error handling + type(error_t), allocatable, intent(out) :: error + + type(toml_key), allocatable :: list(:) + integer :: ikey + + call table%get_keys(list) + + ! table can be empty + if (size(list) < 1) return + + do ikey = 1, size(list) + select case(list(ikey)%key) + + case("auto-executables", "auto-tests") + continue + + case default + call syntax_error(error, "Key "//list(ikey)%key//" is not allowed in [build]") + exit + + end select + end do + + end subroutine check + + + !> Write information on build configuration instance + subroutine info(self, unit, verbosity) + + !> Instance of the build configuration + class(build_config_t), intent(in) :: self + + !> Unit for IO + integer, intent(in) :: unit + + !> Verbosity of the printout + integer, intent(in), optional :: verbosity + + integer :: pr + character(len=*), parameter :: fmt = '("#", 1x, a, t30, a)' + + if (present(verbosity)) then + pr = verbosity + else + pr = 1 + end if + + if (pr < 1) return + + write(unit, fmt) "Build configuration" + ! if (allocated(self%auto_executables)) then + write(unit, fmt) " - auto-discovery (apps) ", merge("enabled ", "disabled", self%auto_executables) + ! end if + ! if (allocated(self%auto_tests)) then + write(unit, fmt) " - auto-discovery (tests) ", merge("enabled ", "disabled", self%auto_tests) + ! end if + + end subroutine info + +end module fpm_manifest_build_config diff --git a/fpm/src/fpm/manifest/package.f90 b/fpm/src/fpm/manifest/package.f90 index dff81e5..4e83411 100644 --- a/fpm/src/fpm/manifest/package.f90 +++ b/fpm/src/fpm/manifest/package.f90 @@ -28,6 +28,7 @@ ! [[test]] ! ``` module fpm_manifest_package + use fpm_manifest_build_config, only: build_config_t, new_build_config 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 @@ -47,6 +48,9 @@ module fpm_manifest_package !> Name of the package character(len=:), allocatable :: name + !> Build configuration data + type(build_config_t), allocatable :: build_config + !> Library meta data type(library_t), allocatable :: library @@ -98,6 +102,13 @@ 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 + end if + call get_value(table, "dependencies", child, requested=.false.) if (associated(child)) then call new_dependencies(self%dependency, child, error) @@ -184,7 +195,7 @@ contains name_present = .true. case("version", "license", "author", "maintainer", "copyright", & - & "description", "keywords", "categories", "homepage", & + & "description", "keywords", "categories", "homepage", "build", & & "dependencies", "dev-dependencies", "test", "executable", & & "library") continue @@ -229,6 +240,11 @@ contains write(unit, fmt) "- name", self%name end if + if (allocated(self%build_config)) then + write(unit, fmt) "- build configuration", "" + call self%build_config%info(unit, pr - 1) + end if + if (allocated(self%library)) then write(unit, fmt) "- target", "archive" call self%library%info(unit, pr - 1) |