aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--CONTRIBUTING.md2
-rw-r--r--PACKAGING.md6
-rw-r--r--README.md2
-rw-r--r--fpm/fpm.toml2
-rw-r--r--fpm/src/fpm.f90100
-rw-r--r--fpm/src/fpm/manifest.f9070
-rw-r--r--fpm/src/fpm/manifest/build.f90 (renamed from fpm/src/fpm/manifest/build_config.f90)4
-rw-r--r--fpm/src/fpm/manifest/dependency.f9012
-rw-r--r--fpm/src/fpm/manifest/executable.f9014
-rw-r--r--fpm/src/fpm/manifest/library.f9010
-rw-r--r--fpm/src/fpm/manifest/package.f9036
-rw-r--r--fpm/src/fpm/manifest/test.f9014
-rw-r--r--fpm/src/fpm_command_line.f90164
-rw-r--r--fpm/src/fpm_sources.f906
-rw-r--r--fpm/test/fpm_test/test_manifest.f9096
-rw-r--r--manifest-reference.md6
16 files changed, 312 insertions, 232 deletions
diff --git a/CONTRIBUTING.md b/CONTRIBUTING.md
index 9a1f5a3..b74aeda 100644
--- a/CONTRIBUTING.md
+++ b/CONTRIBUTING.md
@@ -77,7 +77,7 @@ decisions. This is the workflow that we follow:
one person disagrees.
At this stage, the scope of the fix/feature, its behavior, and API if
applicable should be defined.
- Only when you have community concensus on these items you should proceed to
+ Only when you have community consensus on these items you should proceed to
writing code and opening a PR.
**When actively working on code towards a PR, please assign yourself to the
issue on GitHub.**
diff --git a/PACKAGING.md b/PACKAGING.md
index 44a0c02..663db62 100644
--- a/PACKAGING.md
+++ b/PACKAGING.md
@@ -177,7 +177,7 @@ Based on the output of `fpm build`, *fpm* first ran `gfortran` to emit the
binary object (`math_constants.o`) and module (`math_constants.mod`) files.
Then it ran `ar` to create a static library archive `math_constants.a`.
`build/debug/library` is thus both your include and library path, should you
-want to compile and link an exteranl program with this library.
+want to compile and link an external program with this library.
For modules in the top-level (`src`) directory, *fpm* requires that:
@@ -585,7 +585,7 @@ And now, `fpm run` will output the following:
```
Additionally, any users of your library will now automatically depend on your
-dependencies too. So if you don’t need that depedency for the library, like in
+dependencies too. So if you don’t need that dependency for the library, like in
the above example, then you can specify it for the specific executable like
below. Then fpm will still fetch and compile it when building your executable,
but users of your library won’t have to.
@@ -677,7 +677,7 @@ the build script:
* `FC` – The Fortran compiler to be used.
* `FFLAGS` – The flags that should be passed to the Fortran compiler.
* `BUILD_DIR` – Where the compiled files should be placed.
-* `INCLUDE_DIRS` – The folders where any dependencies can be found, space seperated.
+* `INCLUDE_DIRS` – The folders where any dependencies can be found, space separated.
It is then the responsibility of the build script to generate the appropriate
include flags.
diff --git a/README.md b/README.md
index d131b84..a9d1a02 100644
--- a/README.md
+++ b/README.md
@@ -72,7 +72,7 @@ with the following contents and initialized as a git repository.
* `fpm.toml` – with your project’s name and some default standard meta-data
* `README.md` – with your project’s name
-* `.gitgnore`
+* `.gitignore`
* `src/project_name.f90` – with a simple hello world subroutine
* `app/main.f90` (if `--with-executable` flag used) – a program that calls the subroutine
* `test/main.f90` (if `--with-test` flag used) – an empty test program
diff --git a/fpm/fpm.toml b/fpm/fpm.toml
index 404e65c..7afc0a0 100644
--- a/fpm/fpm.toml
+++ b/fpm/fpm.toml
@@ -12,7 +12,7 @@ tag = "v0.2.1"
[dependencies.M_CLI2]
git = "https://github.com/urbanjost/M_CLI2.git"
-rev = "649075aceb97f997665a1a4656514fd2e9b4becc"
+rev = "893cac0ce374bf07a70ffb9556439c7390e58131"
[[test]]
name = "cli-test"
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90
index daa4d98..5e190c8 100644
--- a/fpm/src/fpm.f90
+++ b/fpm/src/fpm.f90
@@ -12,14 +12,13 @@ use fpm_model, only: fpm_model_t, srcfile_t, build_target_t, &
use fpm_sources, only: add_executable_sources, add_sources_from_dir
use fpm_targets, only: targets_from_sources, resolve_module_dependencies
-use fpm_manifest, only : get_package_data, default_executable, &
- default_library, package_t, default_test
+use fpm_manifest, only : get_package_data, package_config_t
use fpm_error, only : error_t, fatal_error
-use fpm_manifest_test, only : test_t
+use fpm_manifest_test, only : test_config_t
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
& stdout=>output_unit, &
& stderr=>error_unit
-use fpm_manifest_dependency, only: dependency_t
+use fpm_manifest_dependency, only: dependency_config_t
implicit none
private
public :: cmd_build, cmd_install, cmd_run
@@ -34,7 +33,7 @@ recursive subroutine add_libsources_from_package(sources,link_libraries,package_
type(srcfile_t), allocatable, intent(inout), target :: sources(:)
type(string_t), allocatable, intent(inout) :: link_libraries(:)
type(string_t), allocatable, intent(inout) :: package_list(:)
- type(package_t), intent(in) :: package
+ type(package_config_t), intent(in) :: package
character(*), intent(in) :: package_root
logical, intent(in) :: dev_depends
type(error_t), allocatable, intent(out) :: error
@@ -76,16 +75,16 @@ recursive subroutine add_libsources_from_package(sources,link_libraries,package_
contains
subroutine add_dependencies(dependency_list)
- type(dependency_t), intent(in) :: dependency_list(:)
+ type(dependency_config_t), intent(in) :: dependency_list(:)
integer :: i
type(string_t) :: dep_name
- type(package_t) :: dependency
+ type(package_config_t) :: dependency
character(:), allocatable :: dependency_path
do i=1,size(dependency_list)
-
+
if (dependency_list(i)%name .in. package_list) then
cycle
end if
@@ -100,7 +99,7 @@ recursive subroutine add_libsources_from_package(sources,link_libraries,package_
end if
else if (allocated(dependency_list(i)%path)) then
-
+
dependency_path = join_path(package_root,dependency_list(i)%path)
end if
@@ -121,11 +120,11 @@ recursive subroutine add_libsources_from_package(sources,link_libraries,package_
dependency%library%source_dir = "src"
end if
-
+
call add_libsources_from_package(sources,link_libraries,package_list,dependency, &
package_root=dependency_path, &
dev_depends=.false., error=error)
-
+
if (allocated(error)) then
error%message = 'Error while processing sources for dependency package "'//&
new_line('a')//dependency%name//'"'//&
@@ -135,8 +134,8 @@ recursive subroutine add_libsources_from_package(sources,link_libraries,package_
dep_name%s = dependency_list(i)%name
package_list = [package_list, dep_name]
- if (allocated(dependency%build_config%link)) then
- link_libraries = [link_libraries, dependency%build_config%link]
+ if (allocated(dependency%build%link)) then
+ link_libraries = [link_libraries, dependency%build%link]
end if
end do
@@ -151,15 +150,15 @@ subroutine build_model(model, settings, package, error)
!
type(fpm_model_t), intent(out) :: model
type(fpm_build_settings), intent(in) :: settings
- type(package_t), intent(in) :: package
+ type(package_config_t), intent(in) :: package
type(error_t), allocatable, intent(out) :: error
integer :: i
type(string_t), allocatable :: package_list(:)
model%package_name = package%name
- if (allocated(package%build_config%link)) then
- model%link_libraries = package%build_config%link
+ if (allocated(package%build%link)) then
+ model%link_libraries = package%build%link
else
allocate(model%link_libraries(0))
end if
@@ -189,7 +188,7 @@ subroutine build_model(model, settings, package, error)
model%link_flags = ''
! Add sources from executable directories
- if (is_dir('app') .and. package%build_config%auto_executables) then
+ if (is_dir('app') .and. package%build%auto_executables) then
call add_sources_from_dir(model%sources,'app', FPM_SCOPE_APP, &
with_executables=.true., error=error)
@@ -198,7 +197,7 @@ subroutine build_model(model, settings, package, error)
end if
end if
- if (is_dir('test') .and. package%build_config%auto_tests) then
+ if (is_dir('test') .and. package%build%auto_tests) then
call add_sources_from_dir(model%sources,'test', FPM_SCOPE_TEST, &
with_executables=.true., error=error)
@@ -209,7 +208,7 @@ 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=package%build_config%auto_executables, &
+ auto_discover=package%build%auto_executables, &
error=error)
if (allocated(error)) then
@@ -219,7 +218,7 @@ 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=package%build_config%auto_tests, &
+ auto_discover=package%build%auto_tests, &
error=error)
if (allocated(error)) then
@@ -245,53 +244,21 @@ subroutine build_model(model, settings, package, error)
end subroutine build_model
-!> Apply package defaults
-subroutine package_defaults(package)
- type(package_t), intent(inout) :: package
-
- ! Populate library in case we find the default src directory
- if (.not.allocated(package%library) .and. exists("src")) then
- allocate(package%library)
- call default_library(package%library)
- end if
-
- ! Populate executable in case we find the default app
- if (.not.allocated(package%executable) .and. &
- exists(join_path('app',"main.f90"))) then
- allocate(package%executable(1))
- call default_executable(package%executable(1), package%name)
- end if
-
- ! Populate test in case we find the default test directory
- if (.not.allocated(package%test) .and. &
- exists(join_path("test","main.f90"))) then
- allocate(package%test(1))
- call default_test(package%test(1), package%name)
- endif
-
- if (.not.(allocated(package%library) .or. allocated(package%executable))) then
- print '(a)', "Neither library nor executable found, there is nothing to do"
- error stop 1
- end if
-
-end subroutine
subroutine cmd_build(settings)
type(fpm_build_settings), intent(in) :: settings
-type(package_t) :: package
+type(package_config_t) :: package
type(fpm_model_t) :: model
type(error_t), allocatable :: error
integer :: i
-call get_package_data(package, "fpm.toml", error)
+call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
if (allocated(error)) then
print '(a)', error%message
error stop 1
end if
-call package_defaults(package)
-
call build_model(model, settings, package, error)
if (allocated(error)) then
print '(a)', error%message
@@ -322,22 +289,19 @@ subroutine cmd_run(settings,test)
integer :: i, j, col_width, nCol
logical :: found(size(settings%name))
type(error_t), allocatable :: error
- type(package_t) :: package
+ type(package_config_t) :: package
type(fpm_model_t) :: model
type(string_t) :: exe_cmd
type(string_t), allocatable :: executables(:)
type(build_target_t), pointer :: exe_target
type(srcfile_t), pointer :: exe_source
- call get_package_data(package, "fpm.toml", error)
+ call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
if (allocated(error)) then
print '(a)', error%message
error stop 1
end if
-
- call package_defaults(package)
-
call build_model(model, settings%fpm_build_settings, package, error)
if (allocated(error)) then
print '(a)', error%message
@@ -358,7 +322,7 @@ subroutine cmd_run(settings,test)
exe_source => exe_target%dependencies(1)%ptr%source
if (exe_source%unit_scope == &
- merge(FPM_SCOPE_TEST,FPM_SCOPE_APP,test)) then
+ merge(FPM_SCOPE_TEST,FPM_SCOPE_APP,test)) then
col_width = max(col_width,len(basename(exe_target%output_file))+2)
@@ -372,7 +336,7 @@ subroutine cmd_run(settings,test)
do j=1,size(settings%name)
if (trim(settings%name(j))==exe_source%exe_name) then
-
+
found(j) = .true.
exe_cmd%s = exe_target%output_file
executables = [executables, exe_cmd]
@@ -382,7 +346,7 @@ subroutine cmd_run(settings,test)
end do
end if
-
+
end if
end if
@@ -415,14 +379,14 @@ subroutine cmd_run(settings,test)
do i=1,size(model%targets)
exe_target => model%targets(i)%ptr
-
+
if (exe_target%target_type == FPM_TARGET_EXECUTABLE .and. &
allocated(exe_target%dependencies)) then
exe_source => exe_target%dependencies(1)%ptr%source
if (exe_source%unit_scope == &
- merge(FPM_SCOPE_TEST,FPM_SCOPE_APP,test)) then
+ merge(FPM_SCOPE_TEST,FPM_SCOPE_APP,test)) then
write(stderr,'(A)',advance=(merge("yes","no ",modulo(j,nCol)==0))) &
& [character(len=col_width) :: basename(exe_target%output_file)]
@@ -451,9 +415,13 @@ subroutine cmd_run(settings,test)
if (settings%list) then
write(stderr,*) executables(i)%s
else
-
+
if (exists(executables(i)%s)) then
- call run(executables(i)%s//" "//settings%args)
+ if(settings%runner .ne. ' ')then
+ call run(settings%runner//' '//executables(i)%s//" "//settings%args)
+ else
+ call run(executables(i)%s//" "//settings%args)
+ endif
else
write(stderr,*)'fpm::run<ERROR>',executables(i)%s,' not found'
stop 1
diff --git a/fpm/src/fpm/manifest.f90 b/fpm/src/fpm/manifest.f90
index 9d2e793..362ac69 100644
--- a/fpm/src/fpm/manifest.f90
+++ b/fpm/src/fpm/manifest.f90
@@ -7,18 +7,19 @@
!> 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
+ use fpm_manifest_build, only: build_config_t
+ use fpm_manifest_executable, only : executable_config_t
+ use fpm_manifest_library, only : library_config_t
+ use fpm_manifest_package, only : package_config_t, new_package
use fpm_error, only : error_t, fatal_error, file_not_found_error
use fpm_toml, only : toml_table, read_package_file
- use fpm_manifest_test, only : test_t
+ use fpm_manifest_test, only : test_config_t
+ use fpm_filesystem, only: join_path, exists
implicit none
private
public :: get_package_data, default_executable, default_library, default_test
- public :: package_t
+ public :: package_config_t
contains
@@ -28,7 +29,7 @@ contains
subroutine default_library(self)
!> Instance of the library meta data
- type(library_t), intent(out) :: self
+ type(library_config_t), intent(out) :: self
self%source_dir = "src"
@@ -39,7 +40,7 @@ contains
subroutine default_executable(self, name)
!> Instance of the executable meta data
- type(executable_t), intent(out) :: self
+ type(executable_config_t), intent(out) :: self
!> Name of the package
character(len=*), intent(in) :: name
@@ -54,7 +55,7 @@ contains
subroutine default_test(self, name)
!> Instance of the executable meta data
- type(test_t), intent(out) :: self
+ type(test_config_t), intent(out) :: self
!> Name of the package
character(len=*), intent(in) :: name
@@ -67,10 +68,10 @@ contains
!> Obtain package meta data from a configuation file
- subroutine get_package_data(package, file, error)
+ subroutine get_package_data(package, file, error, apply_defaults)
!> Parsed package meta data
- type(package_t), intent(out) :: package
+ type(package_config_t), intent(out) :: package
!> Name of the package configuration file
character(len=*), intent(in) :: file
@@ -78,6 +79,9 @@ contains
!> Error status of the operation
type(error_t), allocatable, intent(out) :: error
+ !> Apply package defaults (uses file system operations)
+ logical, intent(in), optional :: apply_defaults
+
type(toml_table), allocatable :: table
call read_package_file(table, file, error)
@@ -90,7 +94,51 @@ contains
call new_package(package, table, error)
+ if (present(apply_defaults)) then
+ if (apply_defaults) then
+ call package_defaults(package, error)
+ if (allocated(error)) return
+ end if
+ end if
+
end subroutine get_package_data
+ !> Apply package defaults
+ subroutine package_defaults(package, error)
+
+ !> Parsed package meta data
+ type(package_config_t), intent(inout) :: package
+
+ !> Error status of the operation
+ type(error_t), allocatable, intent(out) :: error
+
+ ! Populate library in case we find the default src directory
+ if (.not.allocated(package%library) .and. exists("src")) then
+ allocate(package%library)
+ call default_library(package%library)
+ end if
+
+ ! Populate executable in case we find the default app
+ if (.not.allocated(package%executable) .and. &
+ exists(join_path('app',"main.f90"))) then
+ allocate(package%executable(1))
+ call default_executable(package%executable(1), package%name)
+ end if
+
+ ! Populate test in case we find the default test directory
+ if (.not.allocated(package%test) .and. &
+ exists(join_path("test","main.f90"))) then
+ allocate(package%test(1))
+ call default_test(package%test(1), package%name)
+ endif
+
+ if (.not.(allocated(package%library) .or. allocated(package%executable))) then
+ call fatal_error(error, "Neither library nor executable found, there is nothing to do")
+ return
+ end if
+
+ end subroutine package_defaults
+
+
end module fpm_manifest
diff --git a/fpm/src/fpm/manifest/build_config.f90 b/fpm/src/fpm/manifest/build.f90
index 612c051..85fd2c7 100644
--- a/fpm/src/fpm/manifest/build_config.f90
+++ b/fpm/src/fpm/manifest/build.f90
@@ -8,7 +8,7 @@
!>auto-tests = bool
!>link = ["lib"]
!>```
-module fpm_manifest_build_config
+module fpm_manifest_build
use fpm_error, only : error_t, syntax_error, fatal_error
use fpm_strings, only : string_t
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
@@ -146,4 +146,4 @@ contains
end subroutine info
-end module fpm_manifest_build_config
+end module fpm_manifest_build
diff --git a/fpm/src/fpm/manifest/dependency.f90 b/fpm/src/fpm/manifest/dependency.f90
index a35beb6..26b76ee 100644
--- a/fpm/src/fpm/manifest/dependency.f90
+++ b/fpm/src/fpm/manifest/dependency.f90
@@ -30,11 +30,11 @@ module fpm_manifest_dependency
implicit none
private
- public :: dependency_t, new_dependency, new_dependencies
+ public :: dependency_config_t, new_dependency, new_dependencies
!> Configuration meta data for a dependency
- type :: dependency_t
+ type :: dependency_config_t
!> Name of the dependency
character(len=:), allocatable :: name
@@ -50,7 +50,7 @@ module fpm_manifest_dependency
!> Print information on this instance
procedure :: info
- end type dependency_t
+ end type dependency_config_t
contains
@@ -60,7 +60,7 @@ contains
subroutine new_dependency(self, table, error)
!> Instance of the dependency configuration
- type(dependency_t), intent(out) :: self
+ type(dependency_config_t), intent(out) :: self
!> Instance of the TOML data structure
type(toml_table), intent(inout) :: table
@@ -176,7 +176,7 @@ contains
subroutine new_dependencies(deps, table, error)
!> Instance of the dependency configuration
- type(dependency_t), allocatable, intent(out) :: deps(:)
+ type(dependency_config_t), allocatable, intent(out) :: deps(:)
!> Instance of the TOML data structure
type(toml_table), intent(inout) :: table
@@ -210,7 +210,7 @@ contains
subroutine info(self, unit, verbosity)
!> Instance of the dependency configuration
- class(dependency_t), intent(in) :: self
+ class(dependency_config_t), intent(in) :: self
!> Unit for IO
integer, intent(in) :: unit
diff --git a/fpm/src/fpm/manifest/executable.f90 b/fpm/src/fpm/manifest/executable.f90
index b34c409..be02974 100644
--- a/fpm/src/fpm/manifest/executable.f90
+++ b/fpm/src/fpm/manifest/executable.f90
@@ -11,18 +11,18 @@
!>[executable.dependencies]
!>```
module fpm_manifest_executable
- use fpm_manifest_dependency, only : dependency_t, new_dependencies
+ use fpm_manifest_dependency, only : dependency_config_t, new_dependencies
use fpm_error, only : error_t, syntax_error
use fpm_strings, only : string_t
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
implicit none
private
- public :: executable_t, new_executable
+ public :: executable_config_t, new_executable
!> Configuation meta data for an executable
- type :: executable_t
+ type :: executable_config_t
!> Name of the resulting executable
character(len=:), allocatable :: name
@@ -34,7 +34,7 @@ module fpm_manifest_executable
character(len=:), allocatable :: main
!> Dependency meta data for this executable
- type(dependency_t), allocatable :: dependency(:)
+ type(dependency_config_t), allocatable :: dependency(:)
!> Libraries to link against
type(string_t), allocatable :: link(:)
@@ -44,7 +44,7 @@ module fpm_manifest_executable
!> Print information on this instance
procedure :: info
- end type executable_t
+ end type executable_config_t
contains
@@ -54,7 +54,7 @@ contains
subroutine new_executable(self, table, error)
!> Instance of the executable configuration
- type(executable_t), intent(out) :: self
+ type(executable_config_t), intent(out) :: self
!> Instance of the TOML data structure
type(toml_table), intent(inout) :: table
@@ -136,7 +136,7 @@ contains
subroutine info(self, unit, verbosity)
!> Instance of the executable configuration
- class(executable_t), intent(in) :: self
+ class(executable_config_t), intent(in) :: self
!> Unit for IO
integer, intent(in) :: unit
diff --git a/fpm/src/fpm/manifest/library.f90 b/fpm/src/fpm/manifest/library.f90
index 965e0f8..6c4630d 100644
--- a/fpm/src/fpm/manifest/library.f90
+++ b/fpm/src/fpm/manifest/library.f90
@@ -13,11 +13,11 @@ module fpm_manifest_library
implicit none
private
- public :: library_t, new_library
+ public :: library_config_t, new_library
!> Configuration meta data for a library
- type :: library_t
+ type :: library_config_t
!> Source path prefix
character(len=:), allocatable :: source_dir
@@ -30,7 +30,7 @@ module fpm_manifest_library
!> Print information on this instance
procedure :: info
- end type library_t
+ end type library_config_t
contains
@@ -40,7 +40,7 @@ contains
subroutine new_library(self, table, error)
!> Instance of the library configuration
- type(library_t), intent(out) :: self
+ type(library_config_t), intent(out) :: self
!> Instance of the TOML data structure
type(toml_table), intent(inout) :: table
@@ -93,7 +93,7 @@ contains
subroutine info(self, unit, verbosity)
!> Instance of the library configuration
- class(library_t), intent(in) :: self
+ class(library_config_t), intent(in) :: self
!> Unit for IO
integer, intent(in) :: unit
diff --git a/fpm/src/fpm/manifest/package.f90 b/fpm/src/fpm/manifest/package.f90
index b55e6d6..64b0f82 100644
--- a/fpm/src/fpm/manifest/package.f90
+++ b/fpm/src/fpm/manifest/package.f90
@@ -28,11 +28,11 @@
!>[[ 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
- use fpm_manifest_test, only : test_t, new_test
+ use fpm_manifest_build, only: build_config_t, new_build_config
+ use fpm_manifest_dependency, only : dependency_config_t, new_dependencies
+ use fpm_manifest_executable, only : executable_config_t, new_executable
+ use fpm_manifest_library, only : library_config_t, new_library
+ use fpm_manifest_test, only : test_config_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
@@ -40,42 +40,42 @@ module fpm_manifest_package
implicit none
private
- public :: package_t, new_package
+ public :: package_config_t, new_package
!> Package meta data
- type :: package_t
+ type :: package_config_t
!> Name of the package
character(len=:), allocatable :: name
!> Build configuration data
- type(build_config_t) :: build_config
+ type(build_config_t) :: build
!> Package version
type(version_t) :: version
!> Library meta data
- type(library_t), allocatable :: library
+ type(library_config_t), allocatable :: library
!> Executable meta data
- type(executable_t), allocatable :: executable(:)
+ type(executable_config_t), allocatable :: executable(:)
!> Dependency meta data
- type(dependency_t), allocatable :: dependency(:)
+ type(dependency_config_t), allocatable :: dependency(:)
!> Development dependency meta data
- type(dependency_t), allocatable :: dev_dependency(:)
+ type(dependency_config_t), allocatable :: dev_dependency(:)
!> Test meta data
- type(test_t), allocatable :: test(:)
+ type(test_config_t), allocatable :: test(:)
contains
!> Print information on this instance
procedure :: info
- end type package_t
+ end type package_config_t
contains
@@ -85,7 +85,7 @@ contains
subroutine new_package(self, table, error)
!> Instance of the package configuration
- type(package_t), intent(out) :: self
+ type(package_config_t), intent(out) :: self
!> Instance of the TOML data structure
type(toml_table), intent(inout) :: table
@@ -112,7 +112,7 @@ contains
call fatal_error(error, "Type mismatch for build entry, must be a table")
return
end if
- call new_build_config(self%build_config, child, error)
+ call new_build_config(self%build, child, error)
if (allocated(error)) return
@@ -227,7 +227,7 @@ contains
subroutine info(self, unit, verbosity)
!> Instance of the package configuration
- class(package_t), intent(in) :: self
+ class(package_config_t), intent(in) :: self
!> Unit for IO
integer, intent(in) :: unit
@@ -252,7 +252,7 @@ contains
write(unit, fmt) "- name", self%name
end if
- call self%build_config%info(unit, pr - 1)
+ call self%build%info(unit, pr - 1)
if (allocated(self%library)) then
write(unit, fmt) "- target", "archive"
diff --git a/fpm/src/fpm/manifest/test.f90 b/fpm/src/fpm/manifest/test.f90
index cb7f666..bcacbd8 100644
--- a/fpm/src/fpm/manifest/test.f90
+++ b/fpm/src/fpm/manifest/test.f90
@@ -15,25 +15,25 @@
!>[test.dependencies]
!>```
module fpm_manifest_test
- use fpm_manifest_dependency, only : dependency_t, new_dependencies
- use fpm_manifest_executable, only : executable_t
+ use fpm_manifest_dependency, only : dependency_config_t, new_dependencies
+ use fpm_manifest_executable, only : executable_config_t
use fpm_error, only : error_t, syntax_error
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
implicit none
private
- public :: test_t, new_test
+ public :: test_config_t, new_test
!> Configuation meta data for an test
- type, extends(executable_t) :: test_t
+ type, extends(executable_config_t) :: test_config_t
contains
!> Print information on this instance
procedure :: info
- end type test_t
+ end type test_config_t
contains
@@ -43,7 +43,7 @@ contains
subroutine new_test(self, table, error)
!> Instance of the test configuration
- type(test_t), intent(out) :: self
+ type(test_config_t), intent(out) :: self
!> Instance of the TOML data structure
type(toml_table), intent(inout) :: table
@@ -125,7 +125,7 @@ contains
subroutine info(self, unit, verbosity)
!> Instance of the test configuration
- class(test_t), intent(in) :: self
+ class(test_config_t), intent(in) :: self
!> Unit for IO
integer, intent(in) :: unit
diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90
index dc6823f..50a7d25 100644
--- a/fpm/src/fpm_command_line.f90
+++ b/fpm/src/fpm_command_line.f90
@@ -2,7 +2,7 @@ module fpm_command_line
use fpm_environment, only : get_os_type, &
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD
-use M_CLI2, only : set_args, lget, unnamed, remaining, specified
+use M_CLI2, only : set_args, lget, sget, unnamed, remaining, specified
use fpm_strings, only : lower
use fpm_filesystem, only : basename, canon_path
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
@@ -39,6 +39,7 @@ end type
type, extends(fpm_build_settings) :: fpm_run_settings
character(len=ibug),allocatable :: name(:)
character(len=:),allocatable :: args
+ character(len=:),allocatable :: runner
end type
type, extends(fpm_run_settings) :: fpm_test_settings
@@ -53,10 +54,14 @@ character(len=ibug),allocatable :: names(:)
character(len=:), allocatable :: version_text(:)
character(len=:), allocatable :: help_new(:), help_fpm(:), help_run(:), &
- & help_test(:), help_build(:), help_usage(:), &
+ & help_test(:), help_build(:), help_usage(:), help_runner(:), &
& help_text(:), help_install(:), help_help(:), &
& help_list(:), help_list_dash(:), help_list_nodash(:)
+character(len=20),parameter :: manual(*)=[ character(len=20) ::&
+& ' ', 'fpm', 'new', 'build', 'run', &
+& 'test', 'runner', 'list', 'help', 'version' ]
+character(len=:), allocatable :: charbug
contains
subroutine get_command_line_settings(cmd_settings)
class(fpm_cmd_settings), allocatable, intent(out) :: cmd_settings
@@ -97,7 +102,7 @@ contains
select case(trim(cmdarg))
case('run')
- call set_args('--list F --release F --',help_run,version_text)
+ call set_args('--list F --release F --runner " " --',help_run,version_text)
if( size(unnamed) .gt. 1 )then
names=unnamed(2:)
@@ -107,7 +112,7 @@ contains
allocate(fpm_run_settings :: cmd_settings)
cmd_settings=fpm_run_settings( name=names, list=lget('list'), &
- & release=lget('release'), args=remaining )
+ & release=lget('release'), args=remaining ,runner=sget('runner') )
case('build')
call set_args( '--release F --list F --',help_build,version_text )
@@ -161,43 +166,44 @@ contains
& backfill=lget('backfill') )
endif
- case('help')
+ case('help','manual')
call set_args(' ',help_help,version_text)
if(size(unnamed).lt.2)then
- unnamed=['help', 'fpm ']
+ if(unnamed(1).eq.'help')then
+ unnamed=[' ', 'fpm']
+ else
+ unnamed=manual
+ endif
+ elseif(unnamed(2).eq.'manual')then
+ unnamed=manual
endif
widest=256
allocate(character(len=widest) :: help_text(0))
do i=2,size(unnamed)
select case(unnamed(i))
+ case(' ' )
+ case('fpm ' )
+ help_text=[character(len=widest) :: help_text, help_fpm]
+ case('new ' )
+ help_text=[character(len=widest) :: help_text, help_new]
case('build ' )
help_text=[character(len=widest) :: help_text, help_build]
case('run ' )
help_text=[character(len=widest) :: help_text, help_run]
- case('help ' )
- help_text=[character(len=widest) :: help_text, help_help]
case('test ' )
help_text=[character(len=widest) :: help_text, help_test]
- case('new ' )
- help_text=[character(len=widest) :: help_text, help_new]
- case('fpm ' )
- help_text=[character(len=widest) :: help_text, help_fpm]
+ case('runner' )
+ help_text=[character(len=widest) :: help_text, help_runner]
case('list ' )
help_text=[character(len=widest) :: help_text, help_list]
- case('version' )
- help_text=[character(len=widest) :: help_text, version_text]
- case('manual ' )
- help_text=[character(len=widest) :: help_text, help_fpm]
- help_text=[character(len=widest) :: help_text, help_new]
- help_text=[character(len=widest) :: help_text, help_build]
- help_text=[character(len=widest) :: help_text, help_run]
- help_text=[character(len=widest) :: help_text, help_test]
+ case('help ' )
help_text=[character(len=widest) :: help_text, help_help]
- help_text=[character(len=widest) :: help_text, help_list]
+ case('version' )
help_text=[character(len=widest) :: help_text, version_text]
case default
help_text=[character(len=widest) :: help_text, &
- & 'ERROR: unknown help topic "'//trim(unnamed(i))//'"']
+ & '<ERROR> unknown help topic "'//trim(unnamed(i))//'"']
+ !!& '<ERROR> unknown help topic "'//trim(unnamed(i)).'not found in:',manual]
end select
enddo
call printhelp(help_text)
@@ -213,7 +219,7 @@ contains
call printhelp(help_list_dash)
endif
case('test')
- call set_args('--list F --release F --',help_test,version_text)
+ call set_args('--list F --release F --runner " " --',help_test,version_text)
if( size(unnamed) .gt. 1 )then
names=unnamed(2:)
@@ -222,8 +228,9 @@ contains
endif
allocate(fpm_test_settings :: cmd_settings)
+ charbug=sget('runner')
cmd_settings=fpm_test_settings( name=names, list=lget('list'), &
- & release=lget('release'), args=remaining )
+ & release=lget('release'), args=remaining ,runner=charbug )
case default
@@ -296,11 +303,75 @@ contains
' help [NAME(s)] ', &
' new NAME [--lib|--src] [--app] [--test] [--backfill] ', &
' list [--list] ', &
- ' run [NAME(s)] [--release] [--list] [-- ARGS] ', &
- ' test [NAME(s)] [--release] [--list] [-- ARGS] ', &
+ ' run [NAME(s)] [--release] [--runner "CMD"] [--list] [-- ARGS] ', &
+ ' test [NAME(s)] [--release] [--runner "CMD"] [--list] [-- ARGS] ', &
' ']
help_usage=[character(len=80) :: &
'' ]
+ help_runner=[character(len=80) :: &
+ 'NAME ', &
+ ' --runner(1) - a shared option for specifying an application to launch ', &
+ ' executables. ', &
+ ' ', &
+ 'SYNOPSIS ', &
+ ' fpm run|test --runner CMD ... -- SUFFIX_OPTIONS ', &
+ ' ', &
+ 'DESCRIPTION ', &
+ ' The --runner option allows specifying a program to launch ', &
+ ' executables selected via the fpm(1) subcommands "run" and "test". This ', &
+ ' gives easy recourse to utilities such as debuggers and other tools ', &
+ ' that wrap other executables. ', &
+ ' ', &
+ ' These external commands are not part of fpm(1) itself as they vary ', &
+ ' from platform to platform or require independent installation. ', &
+ ' ', &
+ 'OPTION ', &
+ ' --runner ''CMD'' quoted command used to launch the fpm(1) executables. ', &
+ ' Available for both the "run" and "test" subcommands. ', &
+ ' ', &
+ ' -- SUFFIX_OPTIONS additional options to suffix the command CMD and executable ', &
+ ' file names with. ', &
+ 'EXAMPLES ', &
+ ' Use cases for ''fpm run|test --runner "CMD"'' include employing ', &
+ ' the following common GNU/Linux and Unix commands: ', &
+ ' ', &
+ ' INTERROGATE ', &
+ ' + nm - list symbols from object files ', &
+ ' + size - list section sizes and total size. ', &
+ ' + ldd - print shared object dependencies ', &
+ ' + ls - list directory contents ', &
+ ' + stat - display file or file system status ', &
+ ' + file - determine file type ', &
+ ' PERFORMANCE AND DEBUGGING ', &
+ ' + gdb - The GNU Debugger ', &
+ ' + valgrind - a suite of tools for debugging and profiling ', &
+ ' + time - time a simple command or give resource usage ', &
+ ' + timeout - run a command with a time limit ', &
+ ' COPY ', &
+ ' + install - copy files and set attributes ', &
+ ' + tar - an archiving utility ', &
+ ' ALTER ', &
+ ' + rm - remove files or directories ', &
+ ' + chmod - change permissions of a file ', &
+ ' + strip - remove unnecessary information from strippable files ', &
+ ' ', &
+ ' For example ', &
+ ' ', &
+ ' fpm test --runner gdb ', &
+ ' fpm run --runner "tar cvfz $HOME/bundle.tgz" ', &
+ ' fpm run --runner ldd ', &
+ ' fpm run --runner strip ', &
+ ' fpm run --runner ''cp -t /usr/local/bin'' ', &
+ ' ', &
+ ' # options after executable name can be specified after the -- option ', &
+ ' fpm --runner cp run -- /usr/local/bin/ ', &
+ ' # generates commands of the form "cp $FILENAME /usr/local/bin/" ', &
+ ' ', &
+ ' # bash(1) alias example: ', &
+ ' alias fpm-install="ffpm run --release --runner \ ', &
+ ' ''install -vbp -m 0711 -t ~/.local/bin''" ', &
+ ' fpm-install ', &
+ '' ]
help_fpm=[character(len=80) :: &
'NAME ', &
' fpm(1) - A Fortran package manager and build system ', &
@@ -334,10 +405,10 @@ contains
' new NAME [--lib|--src] [--app] [--test] [--backfill] ', &
' Create a new Fortran package directory ', &
' with sample files ', &
- ' run [NAME(s)] [--release] [--list] [-- ARGS] ', &
+ ' run [NAME(s)] [--release] [--list] [--runner "CMD"][-- ARGS] ', &
' Run the local package binaries. defaults to all ', &
' binaries for that release. ', &
- ' test [NAME(s)] [--release] [--list] [-- ARGS] ', &
+ ' test [NAME(s)] [--release] [--list] [--runner "CMD"] [-- ARGS] ', &
' Run the tests ', &
' help [NAME(s)] Alternate method for displaying subcommand help ', &
' list [--list] Display brief descriptions of all subcommands. ', &
@@ -350,6 +421,7 @@ contains
' optimization flags are used. ', &
' --list List candidates instead of building or running them. On ', &
' the fpm(1) command this shows a brief list of subcommands.', &
+ ' --runner CMD Provides a command to prefix program execution paths. ', &
' -- ARGS Arguments to pass to executables. ', &
' --help Show help text and exit. Valid for all subcommands. ', &
' --version Show version information and exit. Valid for all ', &
@@ -366,7 +438,10 @@ contains
' fpm run myprogram --release -- -x 10 -y 20 --title "my title" ', &
' ', &
'SEE ALSO ', &
- ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', &
+ ' + The fpm(1) home page is at https://github.com/fortran-lang/fpm ', &
+ ' + Registered fpm(1) packages are at https://fortran-lang.org/packages ', &
+ ' + The fpm(1) TOML file format is described at ', &
+ ' https://github.com/fortran-lang/fpm/blob/master/manifest-reference.md ', &
'']
help_list=[character(len=80) :: &
'NAME ', &
@@ -389,16 +464,13 @@ contains
' ', &
' fpm list ', &
' fpm --list ', &
- ' ', &
- 'SEE ALSO ', &
- ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', &
'' ]
help_run=[character(len=80) :: &
'NAME ', &
' run(1) - the fpm(1) subcommand to run project applications ', &
' ', &
'SYNOPSIS ', &
- ' fpm run [NAME(s)] [--release] [-- ARGS] ', &
+ ' fpm run [NAME(s)] [--release] [--runner "CMD"] [-- ARGS] ', &
' ', &
' fpm run --help|--version ', &
' ', &
@@ -412,12 +484,14 @@ contains
' --release selects the optimized build instead of the debug ', &
' build. ', &
' --list list candidates instead of building or running them ', &
+ ' --runner CMD A command to prefix the program execution paths with. ', &
+ ' see "fpm help runner" for further details. ', &
' -- ARGS optional arguments to pass to the program(s). ', &
' The same arguments are passed to all names ', &
' specified. ', &
' ', &
'EXAMPLES ', &
- ' run fpm(1) project applications ', &
+ ' fpm(1) "run" project applications ', &
' ', &
' # run default programs in /app or as specified in "fpm.toml" ', &
' fpm run ', &
@@ -428,8 +502,8 @@ contains
' # run production version of two applications ', &
' fpm run prg1 prg2 --release ', &
' ', &
- 'SEE ALSO ', &
- ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', &
+ ' # install executables in directory (assuming install(1) exists) ', &
+ ' fpm run --runner ''install -b -m 0711 -p -t /usr/local/bin'' ', &
'' ]
help_build=[character(len=80) :: &
'NAME ', &
@@ -468,9 +542,6 @@ contains
' ', &
' fpm build # build with debug options ', &
' fpm build --release # build with high optimization ', &
- ' ', &
- 'SEE ALSO ', &
- ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', &
'' ]
help_help=[character(len=80) :: &
@@ -479,6 +550,7 @@ contains
' ', &
'SYNOPSIS ', &
' fpm help [fpm] [new] [build] [run] [test] [help] [version] [manual] ', &
+ ' [runner] ', &
' ', &
'DESCRIPTION ', &
' The "fpm help" command is an alternative to the --help parameter ', &
@@ -502,8 +574,6 @@ contains
' fpm help new # display help for "new" subcommand ', &
' fpm help manual # All fpm(1) built-in documentation ', &
' ', &
- 'SEE ALSO ', &
- ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', &
'' ]
help_new=[character(len=80) :: &
'NAME ', &
@@ -578,18 +648,13 @@ contains
' fpm build ', &
' fpm run # run example application program ', &
' fpm test # run example test program ', &
- ' ', &
- 'SEE ALSO ', &
- ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', &
- ' ', &
- ' Registered packages are at https://fortran-lang.org/packages ', &
'' ]
help_test=[character(len=80) :: &
'NAME ', &
' test(1) - the fpm(1) subcommand to run project tests ', &
' ', &
'SYNOPSIS ', &
- ' fpm test [NAME(s)] [--release] [--list] [-- ARGS] ', &
+ ' fpm test [NAME(s)] [--release] [--list] [--runner "CMD"] [-- ARGS] ', &
' ', &
' fpm test --help|--version ', &
' ', &
@@ -603,6 +668,8 @@ contains
' --release selects the optimized build instead of the debug ', &
' build. ', &
' --list list candidates instead of building or running them ', &
+ ' --runner CMD A command to prefix the program execution paths with. ', &
+ ' see "fpm help runner" for further details. ', &
' -- ARGS optional arguments to pass to the test program(s). ', &
' The same arguments are passed to all test names ', &
' specified. ', &
@@ -617,9 +684,6 @@ contains
' fpm test mytest -- -x 10 -y 20 --title "my title line" ', &
' ', &
' fpm test tst1 tst2 --release # production version of two tests ', &
- ' ', &
- 'SEE ALSO ', &
- ' The fpm(1) home page at https://github.com/fortran-lang/fpm ', &
'' ]
help_install=[character(len=80) :: &
' fpm(1) subcommand "install" ', &
diff --git a/fpm/src/fpm_sources.f90 b/fpm/src/fpm_sources.f90
index fa5c6e7..5e42430 100644
--- a/fpm/src/fpm_sources.f90
+++ b/fpm/src/fpm_sources.f90
@@ -8,7 +8,7 @@ use fpm_model, only: srcfile_t, fpm_model_t, &
use fpm_filesystem, only: basename, canon_path, dirname, join_path, read_lines, list_files
use fpm_strings, only: lower, split, str_ends_with, string_t, operator(.in.)
-use fpm_manifest_executable, only: executable_t
+use fpm_manifest_executable, only: executable_config_t
implicit none
private
@@ -123,7 +123,7 @@ subroutine add_executable_sources(sources,executables,scope,auto_discover,error)
! in [[executable]] entries and apply any customisations
!
type(srcfile_t), allocatable, intent(inout), target :: sources(:)
- class(executable_t), intent(in) :: executables(:)
+ class(executable_config_t), intent(in) :: executables(:)
integer, intent(in) :: scope
logical, intent(in) :: auto_discover
type(error_t), allocatable, intent(out) :: error
@@ -189,7 +189,7 @@ subroutine get_executable_source_dirs(exe_dirs,executables)
! Build a list of unique source directories
! from executables specified in manifest
type(string_t), allocatable, intent(inout) :: exe_dirs(:)
- class(executable_t), intent(in) :: executables(:)
+ class(executable_config_t), intent(in) :: executables(:)
type(string_t) :: dirs_temp(size(executables))
diff --git a/fpm/test/fpm_test/test_manifest.f90 b/fpm/test/fpm_test/test_manifest.f90
index 1116a74..a81504d 100644
--- a/fpm/test/fpm_test/test_manifest.f90
+++ b/fpm/test/fpm_test/test_manifest.f90
@@ -36,9 +36,9 @@ contains
& new_unittest("executable-typeerror", test_executable_typeerror, should_fail=.true.), &
& new_unittest("executable-noname", test_executable_noname, should_fail=.true.), &
& new_unittest("executable-wrongkey", test_executable_wrongkey, should_fail=.true.), &
- & new_unittest("build-config-valid", test_build_config_valid), &
- & new_unittest("build-config-empty", test_build_config_empty), &
- & new_unittest("build-config-invalid-values", test_build_config_invalid_values, should_fail=.true.), &
+ & new_unittest("build-config-valid", test_build_valid), &
+ & new_unittest("build-config-empty", test_build_empty), &
+ & new_unittest("build-config-invalid-values", test_build_invalid_values, should_fail=.true.), &
& new_unittest("library-empty", test_library_empty), &
& new_unittest("library-wrongkey", test_library_wrongkey, should_fail=.true.), &
& new_unittest("package-simple", test_package_simple), &
@@ -65,7 +65,7 @@ contains
!> Error handling
type(error_t), allocatable, intent(out) :: error
- type(package_t) :: package
+ type(package_config_t) :: package
character(len=*), parameter :: manifest = 'fpm-valid-manifest.toml'
integer :: unit
@@ -143,7 +143,7 @@ contains
!> Error handling
type(error_t), allocatable, intent(out) :: error
- type(package_t) :: package
+ type(package_config_t) :: package
character(len=*), parameter :: manifest = 'fpm-invalid-manifest.toml'
integer :: unit
@@ -168,7 +168,7 @@ contains
!> Error handling
type(error_t), allocatable, intent(out) :: error
- type(package_t) :: package
+ type(package_config_t) :: package
allocate(package%library)
call default_library(package%library)
@@ -186,7 +186,7 @@ contains
!> Error handling
type(error_t), allocatable, intent(out) :: error
- type(package_t) :: package
+ type(package_config_t) :: package
character(len=*), parameter :: name = "default"
allocate(package%executable(1))
@@ -212,7 +212,7 @@ contains
type(error_t), allocatable, intent(out) :: error
type(toml_table) :: table
- type(dependency_t) :: dependency
+ type(dependency_config_t) :: dependency
call new_table(table)
table%key = "example"
@@ -232,7 +232,7 @@ contains
type(toml_table) :: table
integer :: stat
- type(dependency_t) :: dependency
+ type(dependency_config_t) :: dependency
call new_table(table)
table%key = 'example'
@@ -254,7 +254,7 @@ contains
type(toml_table) :: table
integer :: stat
- type(dependency_t) :: dependency
+ type(dependency_config_t) :: dependency
call new_table(table)
table%key = 'example'
@@ -275,7 +275,7 @@ contains
type(toml_table) :: table
integer :: stat
- type(dependency_t) :: dependency
+ type(dependency_config_t) :: dependency
call new_table(table)
table%key = 'example'
@@ -297,7 +297,7 @@ contains
type(toml_table) :: table
integer :: stat
- type(dependency_t) :: dependency
+ type(dependency_config_t) :: dependency
call new_table(table)
table%key = 'example'
@@ -320,7 +320,7 @@ contains
type(toml_table) :: table
integer :: stat
- type(dependency_t) :: dependency
+ type(dependency_config_t) :: dependency
call new_table(table)
table%key = 'example'
@@ -340,7 +340,7 @@ contains
type(error_t), allocatable, intent(out) :: error
type(toml_table) :: table
- type(dependency_t), allocatable :: dependencies(:)
+ type(dependency_config_t), allocatable :: dependencies(:)
call new_table(table)
@@ -365,7 +365,7 @@ contains
type(toml_table) :: table
type(toml_array), pointer :: children
integer :: stat
- type(dependency_t), allocatable :: dependencies(:)
+ type(dependency_config_t), allocatable :: dependencies(:)
call new_table(table)
call add_array(table, 'dep1', children, stat)
@@ -384,7 +384,7 @@ contains
type(error_t), allocatable, intent(out) :: error
type(toml_table) :: table
- type(executable_t) :: executable
+ type(executable_config_t) :: executable
call new_table(table)
@@ -404,7 +404,7 @@ contains
type(toml_table) :: table
type(toml_table), pointer :: child
integer :: stat
- type(executable_t) :: executable
+ type(executable_config_t) :: executable
call new_table(table)
call add_table(table, 'name', child, stat)
@@ -425,7 +425,7 @@ contains
type(toml_table) :: table
type(toml_table), pointer :: child
integer :: stat
- type(executable_t) :: executable
+ type(executable_config_t) :: executable
call new_table(table)
call add_table(table, 'dependencies', child, stat)
@@ -446,7 +446,7 @@ contains
type(toml_table) :: table
type(toml_table), pointer :: child
integer :: stat
- type(executable_t) :: executable
+ type(executable_config_t) :: executable
call new_table(table)
call add_table(table, 'wrong-field', child, stat)
@@ -457,12 +457,12 @@ contains
!> Try to read values from the [build] table
- subroutine test_build_config_valid(error)
+ subroutine test_build_valid(error)
!> Error handling
type(error_t), allocatable, intent(out) :: error
- type(package_t) :: package
+ type(package_config_t) :: package
character(:), allocatable :: temp_file
integer :: unit
@@ -480,26 +480,26 @@ contains
if (allocated(error)) return
- if (package%build_config%auto_executables) then
+ if (package%build%auto_executables) then
call test_failed(error, "Wong value of 'auto-executables' read, expecting .false.")
return
end if
- if (package%build_config%auto_tests) then
+ if (package%build%auto_tests) then
call test_failed(error, "Wong value of 'auto-tests' read, expecting .false.")
return
end if
- end subroutine test_build_config_valid
+ end subroutine test_build_valid
!> Try to read values from an empty [build] table
- subroutine test_build_config_empty(error)
+ subroutine test_build_empty(error)
!> Error handling
type(error_t), allocatable, intent(out) :: error
- type(package_t) :: package
+ type(package_config_t) :: package
character(:), allocatable :: temp_file
integer :: unit
@@ -516,26 +516,26 @@ contains
if (allocated(error)) return
- if (.not.package%build_config%auto_executables) then
+ if (.not.package%build%auto_executables) then
call test_failed(error, "Wong default value of 'auto-executables' read, expecting .true.")
return
end if
- if (.not.package%build_config%auto_tests) then
+ if (.not.package%build%auto_tests) then
call test_failed(error, "Wong default value of 'auto-tests' read, expecting .true.")
return
end if
- end subroutine test_build_config_empty
+ end subroutine test_build_empty
!> Try to read values from a [build] table with invalid values
- subroutine test_build_config_invalid_values(error)
+ subroutine test_build_invalid_values(error)
!> Error handling
type(error_t), allocatable, intent(out) :: error
- type(package_t) :: package
+ type(package_config_t) :: package
character(:), allocatable :: temp_file
integer :: unit
@@ -550,7 +550,7 @@ contains
call get_package_data(package, temp_file, error)
- end subroutine test_build_config_invalid_values
+ end subroutine test_build_invalid_values
!> Libraries can be created from empty tables
@@ -562,7 +562,7 @@ contains
type(error_t), allocatable, intent(out) :: error
type(toml_table) :: table
- type(library_t) :: library
+ type(library_config_t) :: library
call new_table(table)
@@ -587,7 +587,7 @@ contains
type(toml_table) :: table
type(toml_table), pointer :: child
integer :: stat
- type(library_t) :: library
+ type(library_config_t) :: library
call new_table(table)
call add_table(table, 'not-allowed', child, stat)
@@ -610,7 +610,7 @@ contains
type(toml_table), pointer :: child, child2
type(toml_array), pointer :: children
integer :: stat
- type(package_t) :: package
+ type(package_config_t) :: package
call new_table(table)
call set_value(table, 'name', '"example"', stat)
@@ -645,7 +645,7 @@ contains
type(error_t), allocatable, intent(out) :: error
type(toml_table) :: table
- type(package_t) :: package
+ type(package_config_t) :: package
call new_table(table)
@@ -665,7 +665,7 @@ contains
type(toml_table) :: table
type(toml_array), pointer :: child
integer :: stat
- type(package_t) :: package
+ type(package_config_t) :: package
call new_table(table)
call add_array(table, "name", child, stat)
@@ -686,7 +686,7 @@ contains
type(toml_table) :: table
type(toml_table), pointer :: child
integer :: stat
- type(package_t) :: package
+ type(package_config_t) :: package
call new_table(table)
call add_table(table, "library", child, stat)
@@ -709,7 +709,7 @@ contains
type(toml_table) :: table
type(toml_array), pointer :: children, children2
integer :: stat
- type(package_t) :: package
+ type(package_config_t) :: package
call new_table(table)
call set_value(table, 'name', '"example"', stat)
@@ -732,7 +732,7 @@ contains
type(toml_table) :: table
type(toml_array), pointer :: children, children2
integer :: stat
- type(package_t) :: package
+ type(package_config_t) :: package
call new_table(table)
call set_value(table, 'name', '"example"', stat)
@@ -755,7 +755,7 @@ contains
type(toml_table) :: table
type(toml_table), pointer :: child
integer :: stat
- type(test_t) :: test
+ type(test_config_t) :: test
call new_table(table)
call set_value(table, 'name', '"example"', stat)
@@ -781,7 +781,7 @@ contains
type(error_t), allocatable, intent(out) :: error
type(toml_table) :: table
- type(test_t) :: test
+ type(test_config_t) :: test
call new_table(table)
@@ -801,7 +801,7 @@ contains
type(toml_table) :: table
type(toml_table), pointer :: child
integer :: stat
- type(test_t) :: test
+ type(test_config_t) :: test
call new_table(table)
call add_table(table, 'name', child, stat)
@@ -822,7 +822,7 @@ contains
type(toml_table) :: table
type(toml_table), pointer :: child
integer :: stat
- type(test_t) :: test
+ type(test_config_t) :: test
call new_table(table)
call add_table(table, 'dependencies', child, stat)
@@ -843,7 +843,7 @@ contains
type(toml_table) :: table
type(toml_table), pointer :: child
integer :: stat
- type(test_t) :: test
+ type(test_config_t) :: test
call new_table(table)
call add_table(table, 'not-supported', child, stat)
@@ -855,7 +855,7 @@ contains
!> Test link options
subroutine test_link_string(error)
- use fpm_manifest_build_config
+ use fpm_manifest_build
use fpm_toml, only : set_value, toml_table
!> Error handling
@@ -875,7 +875,7 @@ contains
!> Test link options
subroutine test_link_array(error)
- use fpm_manifest_build_config
+ use fpm_manifest_build
use fpm_toml, only : add_array, set_value, toml_table, toml_array
!> Error handling
@@ -898,7 +898,7 @@ contains
!> Test link options
subroutine test_invalid_link(error)
- use fpm_manifest_build_config
+ use fpm_manifest_build
use fpm_toml, only : add_table, toml_table
!> Error handling
diff --git a/manifest-reference.md b/manifest-reference.md
index 63a533f..f1394cb 100644
--- a/manifest-reference.md
+++ b/manifest-reference.md
@@ -131,7 +131,7 @@ copyright = "Copyright 2020 Jane Doe"
## Project description
-The decription provides a short summary on the project.
+The description provides a short summary on the project.
It should be plain text and not using any markup formatting.
*Example:*
@@ -184,7 +184,7 @@ Library targets are exported and useable for other projects.
Defines the exported library target of the project.
A library is generated if the source directory is found in a project.
-The default source directory is ``src`` but can be modifed in the *library* section using the *source-dir* entry.
+The default source directory is ``src`` but can be modified in the *library* section using the *source-dir* entry.
Paths for the source directory are given relative to the project root and use ``/`` as path separator on all platforms.
*Example:*
@@ -199,7 +199,7 @@ source-dir = "lib"
> Supported in Bootstrap fpm only
Projects with custom build scripts can specify those in the *build-script* entry.
-The custom build script will be executeted when the library build step is reached.
+The custom build script will be executed when the library build step is reached.
*Example:*