Skip to content

Commit d958be1

Browse files
committed
Add: manifest library entry for include-dir
1 parent 79d7fb6 commit d958be1

File tree

3 files changed

+22
-3
lines changed

3 files changed

+22
-3
lines changed

fpm/src/fpm/manifest.f90

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,7 @@ module fpm_manifest
1616
use fpm_error, only : error_t, fatal_error, file_not_found_error
1717
use fpm_toml, only : toml_table, read_package_file
1818
use fpm_manifest_test, only : test_config_t
19-
use fpm_filesystem, only: join_path, exists, dirname
19+
use fpm_filesystem, only: join_path, exists, dirname, is_dir
2020
implicit none
2121
private
2222

@@ -35,6 +35,7 @@ subroutine default_library(self)
3535
type(library_config_t), intent(out) :: self
3636

3737
self%source_dir = "src"
38+
self%include_dir = "include"
3839

3940
end subroutine default_library
4041

@@ -140,7 +141,9 @@ subroutine package_defaults(package, root, error)
140141

141142
! Populate library in case we find the default src directory
142143
if (.not.allocated(package%library) .and. &
143-
& exists(join_path(root, "src"))) then
144+
& (is_dir(join_path(root, "src")) .or. &
145+
& is_dir(join_path(root, "include")))) then
146+
144147
allocate(package%library)
145148
call default_library(package%library)
146149
end if

fpm/src/fpm/manifest/library.f90

Lines changed: 9 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@
55
!>```toml
66
!>[library]
77
!>source-dir = "path"
8+
!>include-dir = "path"
89
!>build-script = "file"
910
!>```
1011
module fpm_manifest_library
@@ -22,6 +23,9 @@ module fpm_manifest_library
2223
!> Source path prefix
2324
character(len=:), allocatable :: source_dir
2425

26+
!> Include path prefix
27+
character(len=:), allocatable :: include_dir
28+
2529
!> Alternative build script to be invoked
2630
character(len=:), allocatable :: build_script
2731

@@ -52,6 +56,7 @@ subroutine new_library(self, table, error)
5256
if (allocated(error)) return
5357

5458
call get_value(table, "source-dir", self%source_dir, "src")
59+
call get_value(table, "include-dir", self%include_dir, "include")
5560
call get_value(table, "build-script", self%build_script)
5661

5762
end subroutine new_library
@@ -80,7 +85,7 @@ subroutine check(table, error)
8085
call syntax_error(error, "Key "//list(ikey)%key//" is not allowed in library")
8186
exit
8287

83-
case("source-dir", "build-script")
88+
case("source-dir", "include-dir", "build-script")
8489
continue
8590

8691
end select
@@ -116,6 +121,9 @@ subroutine info(self, unit, verbosity)
116121
if (allocated(self%source_dir)) then
117122
write(unit, fmt) "- source directory", self%source_dir
118123
end if
124+
if (allocated(self%include_dir)) then
125+
write(unit, fmt) "- include directory", self%include_dir
126+
end if
119127
if (allocated(self%build_script)) then
120128
write(unit, fmt) "- custom build", self%build_script
121129
end if

fpm/test/fpm_test/test_manifest.f90

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -183,6 +183,10 @@ subroutine test_default_library(error)
183183
& "Default library source-dir")
184184
if (allocated(error)) return
185185

186+
call check_string(error, package%library%include_dir, "include", &
187+
& "Default library include-dir")
188+
if (allocated(error)) return
189+
186190
end subroutine test_default_library
187191

188192

@@ -579,6 +583,10 @@ subroutine test_library_empty(error)
579583
& "Default library source-dir")
580584
if (allocated(error)) return
581585

586+
call check_string(error, library%include_dir, "include", &
587+
& "Default library include-dir")
588+
if (allocated(error)) return
589+
582590
end subroutine test_library_empty
583591

584592

0 commit comments

Comments
 (0)