diff options
24 files changed, 269 insertions, 85 deletions
@@ -5,20 +5,20 @@ Its key goal is to improve the user experience of Fortran programmers. It does so by making it easier to build your Fortran program or library, run the executables, tests, and examples, and distribute it as a dependency to other Fortran projects. -Fpm's user interface is modeled after [Rust's Cargo](https://crates.io/), +Fpm's user interface is modeled after [Rust's Cargo](https://doc.rust-lang.org/cargo/), so if you're familiar with that tool, you will feel at home with fpm. Fpm's long term vision is to nurture and grow the ecosystem of modern Fortran applications and libraries. Fpm is an early prototype and is evolving rapidly. You can use it to build and package your Fortran projects, as well as to use -existing fpm packages as dependencies. +[existing fpm packages](https://github.com/fortran-lang/fpm-registry) as dependencies. Fpm's behavior and user interface may change as it evolves, however as fpm matures and we enter production, we will aim to stay backwards compatible. Please follow the [issues](https://github.com/fortran-lang/fpm/issues) to contribute and/or stay up to date with the development. Before opening a bug report or a feature suggestion, please read our -[Contributor Guide](CONTRIBUTING.md). +[Contributor Guide](CONTRIBUTING.md). You can also discuss your ideas and queries with the community in [fpm discussions](https://github.com/fortran-lang/fpm/discussions), or more broadly on [Fortran-Lang Discourse](https://fortran-lang.discourse.group/) Fortran Package Manager is not to be confused with [Jordan Sissel's fpm](https://github.com/jordansissel/fpm), a more general, diff --git a/ci/run_tests.bat b/ci/run_tests.bat index f5b57c1..e010e9f 100755 --- a/ci/run_tests.bat +++ b/ci/run_tests.bat @@ -187,4 +187,28 @@ if errorlevel 1 exit 1 %fpm_path% run --target gomp_test if errorlevel 1 exit 1 + +cd ..\fortran_includes +if errorlevel 1 exit 1 + +del /q /f build +%fpm_path% build +if errorlevel 1 exit 1 + + +cd ..\c_includes +if errorlevel 1 exit 1 + +del /q /f build +%fpm_path% build +if errorlevel 1 exit 1 + + +cd ..\c_header_only +if errorlevel 1 exit 1 + +del /q /f build +%fpm_path% build +if errorlevel 1 exit 1 + cd ..\.. diff --git a/ci/run_tests.sh b/ci/run_tests.sh index bca70cc..647c57a 100755 --- a/ci/run_tests.sh +++ b/ci/run_tests.sh @@ -89,5 +89,14 @@ cd ../link_executable "${f_fpm_path}" build "${f_fpm_path}" run --target gomp_test +cd ../fortran_includes +"${f_fpm_path}" build + +cd ../c_includes +"${f_fpm_path}" build + +cd ../c_header_only +"${f_fpm_path}" build + # Cleanup rm -rf ./*/build diff --git a/example_packages/README.md b/example_packages/README.md index 667b9a3..b556dcb 100644 --- a/example_packages/README.md +++ b/example_packages/README.md @@ -7,8 +7,11 @@ the features demonstrated in each package and which versions of fpm are supporte | Name | Features | Bootstrap (Haskell) fpm | fpm | |---------------------|---------------------------------------------------------------|:-----------------------:|:---:| | auto_discovery_off | Default layout with auto-discovery disabled | N | Y | +| c_header_only | C header-only library | N | Y | +| c_includes | C library with c include directory and dependency includes | N | Y | | circular_example | Local path dependency; circular dependency | Y | Y | | circular_test | Local path dependency; circular dependency | Y | Y | +| fortran_includes | Fortran library with explicit include directory | Y | N | | hello_complex | Non-standard directory layout; multiple tests and executables | Y | Y | | hello_complex_2 | Auto-discovery of tests and executables with modules | N | Y | | hello_fpm | App-only; local path dependency | Y | Y | diff --git a/example_packages/c_header_only/.gitignore b/example_packages/c_header_only/.gitignore new file mode 100644 index 0000000..a007fea --- /dev/null +++ b/example_packages/c_header_only/.gitignore @@ -0,0 +1 @@ +build/* diff --git a/example_packages/c_header_only/fpm.toml b/example_packages/c_header_only/fpm.toml new file mode 100644 index 0000000..372fe0e --- /dev/null +++ b/example_packages/c_header_only/fpm.toml @@ -0,0 +1 @@ +name = "c_header_only" diff --git a/example_packages/c_header_only/include/c_header.h b/example_packages/c_header_only/include/c_header.h new file mode 100644 index 0000000..ec88a4b --- /dev/null +++ b/example_packages/c_header_only/include/c_header.h @@ -0,0 +1 @@ +int printf ( const char * format, ... ); diff --git a/example_packages/c_includes/.gitignore b/example_packages/c_includes/.gitignore new file mode 100644 index 0000000..a007fea --- /dev/null +++ b/example_packages/c_includes/.gitignore @@ -0,0 +1 @@ +build/* diff --git a/example_packages/c_includes/fpm.toml b/example_packages/c_includes/fpm.toml new file mode 100644 index 0000000..46918d6 --- /dev/null +++ b/example_packages/c_includes/fpm.toml @@ -0,0 +1,4 @@ +name = "c_includes" + +[dependencies] +c_header_only = { path = "../c_header_only"} diff --git a/example_packages/c_includes/include/lib.h b/example_packages/c_includes/include/lib.h new file mode 100644 index 0000000..4f29282 --- /dev/null +++ b/example_packages/c_includes/include/lib.h @@ -0,0 +1,4 @@ +// Include from "c_header_only" dependency +#include "c_header.h" + +int test(const int a); diff --git a/example_packages/c_includes/src/lib.c b/example_packages/c_includes/src/lib.c new file mode 100644 index 0000000..2339822 --- /dev/null +++ b/example_packages/c_includes/src/lib.c @@ -0,0 +1,7 @@ +#include "lib.h" + +int test(const int a){ + + return printf("input: %d\n", a); + +}
\ No newline at end of file diff --git a/example_packages/fortran_includes/.gitignore b/example_packages/fortran_includes/.gitignore new file mode 100644 index 0000000..a007fea --- /dev/null +++ b/example_packages/fortran_includes/.gitignore @@ -0,0 +1 @@ +build/* diff --git a/example_packages/fortran_includes/fpm.toml b/example_packages/fortran_includes/fpm.toml new file mode 100644 index 0000000..8557b72 --- /dev/null +++ b/example_packages/fortran_includes/fpm.toml @@ -0,0 +1,4 @@ +name = "fortran_includes" + +[library] +include-dir = "inc" diff --git a/example_packages/fortran_includes/inc/parameters.f90 b/example_packages/fortran_includes/inc/parameters.f90 new file mode 100644 index 0000000..e9e1af5 --- /dev/null +++ b/example_packages/fortran_includes/inc/parameters.f90 @@ -0,0 +1 @@ +integer, parameter :: dp = kind(0.d0)
\ No newline at end of file diff --git a/example_packages/fortran_includes/src/lib.f90 b/example_packages/fortran_includes/src/lib.f90 new file mode 100644 index 0000000..a27a001 --- /dev/null +++ b/example_packages/fortran_includes/src/lib.f90 @@ -0,0 +1,14 @@ +module test_mod + implicit none + + include "parameters.f90" + + contains + + subroutine test_sub(a) + real(dp), intent(in) :: a + + write(*,*) 'a: ', a + end subroutine test_sub + +end module test_mod
\ No newline at end of file diff --git a/example_packages/link_executable/include/test.f90 b/example_packages/link_executable/include/test.f90 new file mode 100644 index 0000000..5413cbc --- /dev/null +++ b/example_packages/link_executable/include/test.f90 @@ -0,0 +1 @@ +real, parameter :: a = 2.0 diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90 index d0acaf5..a84bebf 100644 --- a/fpm/src/fpm.f90 +++ b/fpm/src/fpm.f90 @@ -1,5 +1,5 @@ module fpm -use fpm_strings, only: string_t, operator(.in.), glob, join +use fpm_strings, only: string_t, operator(.in.), glob, join, string_cat use fpm_backend, only: build_package use fpm_command_line, only: fpm_build_settings, fpm_new_settings, & fpm_run_settings, fpm_install_settings, fpm_test_settings @@ -39,17 +39,14 @@ subroutine build_model(model, settings, package, error) type(package_config_t), intent(in) :: package type(error_t), allocatable, intent(out) :: error - integer :: i + integer :: i, j type(package_config_t) :: dependency character(len=:), allocatable :: manifest, lib_dir - - if(settings%verbose)then - write(*,*)'<INFO>BUILD_NAME:',settings%build_name - write(*,*)'<INFO>COMPILER: ',settings%compiler - endif + type(string_t) :: include_dir model%package_name = package%name + allocate(model%include_dirs(0)) allocate(model%link_libraries(0)) call new_dependency_tree(model%deps, cache=join_path("build", "cache.toml")) @@ -73,9 +70,6 @@ subroutine build_model(model, settings, package, error) & join_path(model%output_directory,model%package_name), & & model%fortran_compile_flags) model%fortran_compile_flags = settings%flag // model%fortran_compile_flags - if(settings%verbose)then - write(*,*)'<INFO>COMPILER OPTIONS: ', model%fortran_compile_flags - endif allocate(model%packages(model%deps%ndep)) @@ -147,12 +141,28 @@ subroutine build_model(model, settings, package, error) if (allocated(error)) exit model%packages(i)%name = dependency%name + if (.not.allocated(model%packages(i)%sources)) allocate(model%packages(i)%sources(0)) if (allocated(dependency%library)) then - lib_dir = join_path(dep%proj_dir, dependency%library%source_dir) - call add_sources_from_dir(model%packages(i)%sources, lib_dir, FPM_SCOPE_LIB, & - error=error) - if (allocated(error)) exit + + if (allocated(dependency%library%source_dir)) then + lib_dir = join_path(dep%proj_dir, dependency%library%source_dir) + if (is_dir(lib_dir)) then + call add_sources_from_dir(model%packages(i)%sources, lib_dir, FPM_SCOPE_LIB, & + error=error) + if (allocated(error)) exit + end if + end if + + if (allocated(dependency%library%include_dir)) then + do j=1,size(dependency%library%include_dir) + include_dir%s = join_path(dep%proj_dir, dependency%library%include_dir(j)%s) + if (is_dir(include_dir%s)) then + model%include_dirs = [model%include_dirs, include_dir] + end if + end do + end if + end if if (allocated(dependency%build%link)) then @@ -162,6 +172,13 @@ subroutine build_model(model, settings, package, error) end do if (allocated(error)) return + if (settings%verbose) then + write(*,*)'<INFO> BUILD_NAME: ',settings%build_name + write(*,*)'<INFO> COMPILER: ',settings%compiler + write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags + write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']' + end if + end subroutine build_model diff --git a/fpm/src/fpm/manifest.f90 b/fpm/src/fpm/manifest.f90 index 5a8f595..4170b91 100644 --- a/fpm/src/fpm/manifest.f90 +++ b/fpm/src/fpm/manifest.f90 @@ -16,7 +16,8 @@ module fpm_manifest 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_config_t - use fpm_filesystem, only: join_path, exists, dirname + use fpm_filesystem, only: join_path, exists, dirname, is_dir + use fpm_strings, only: string_t implicit none private @@ -35,6 +36,7 @@ contains type(library_config_t), intent(out) :: self self%source_dir = "src" + self%include_dir = [string_t("include")] end subroutine default_library @@ -140,7 +142,9 @@ contains ! Populate library in case we find the default src directory if (.not.allocated(package%library) .and. & - & exists(join_path(root, "src"))) then + & (is_dir(join_path(root, "src")) .or. & + & is_dir(join_path(root, "include")))) then + allocate(package%library) call default_library(package%library) end if diff --git a/fpm/src/fpm/manifest/library.f90 b/fpm/src/fpm/manifest/library.f90 index 6c4630d..c8ce049 100644 --- a/fpm/src/fpm/manifest/library.f90 +++ b/fpm/src/fpm/manifest/library.f90 @@ -5,10 +5,12 @@ !>```toml !>[library] !>source-dir = "path" +!>include-dir = ["path1","path2"] !>build-script = "file" !>``` module fpm_manifest_library use fpm_error, only : error_t, syntax_error + use fpm_strings, only: string_t, string_cat use fpm_toml, only : toml_table, toml_key, toml_stat, get_value implicit none private @@ -22,6 +24,9 @@ module fpm_manifest_library !> Source path prefix character(len=:), allocatable :: source_dir + !> Include path prefix + type(string_t), allocatable :: include_dir(:) + !> Alternative build script to be invoked character(len=:), allocatable :: build_script @@ -54,6 +59,14 @@ contains call get_value(table, "source-dir", self%source_dir, "src") call get_value(table, "build-script", self%build_script) + call get_value(table, "include-dir", self%include_dir, error) + if (allocated(error)) return + + ! Set default value of include-dir if not found in manifest + if (.not.allocated(self%include_dir)) then + self%include_dir = [string_t("include")] + end if + end subroutine new_library @@ -80,7 +93,7 @@ contains call syntax_error(error, "Key "//list(ikey)%key//" is not allowed in library") exit - case("source-dir", "build-script") + case("source-dir", "include-dir", "build-script") continue end select @@ -116,6 +129,9 @@ contains if (allocated(self%source_dir)) then write(unit, fmt) "- source directory", self%source_dir end if + if (allocated(self%include_dir)) then + write(unit, fmt) "- include directory", string_cat(self%include_dir,",") + end if if (allocated(self%build_script)) then write(unit, fmt) "- custom build", self%build_script end if diff --git a/fpm/src/fpm_model.f90 b/fpm/src/fpm_model.f90 index 072ac5f..bfb0115 100644 --- a/fpm/src/fpm_model.f90 +++ b/fpm/src/fpm_model.f90 @@ -123,6 +123,9 @@ type :: fpm_model_t !> Base directory for build character(:), allocatable :: output_directory + !> Include directories + type(string_t), allocatable :: include_dirs(:) + !> Native libraries to link against type(string_t), allocatable :: link_libraries(:) diff --git a/fpm/src/fpm_strings.f90 b/fpm/src/fpm_strings.f90 index e074ad8..3d7d7b1 100644 --- a/fpm/src/fpm_strings.f90 +++ b/fpm/src/fpm_strings.f90 @@ -66,6 +66,10 @@ interface str module procedure str_int, str_int64, str_logical end interface +interface string_t + module procedure new_string_t +end interface string_t + contains !> test if a CHARACTER string ends with a specified suffix @@ -193,6 +197,15 @@ elemental pure function lower(str,begin,end) result (string) end function lower +!> Helper function to generate a new string_t instance +!> (Required due to the allocatable component) +function new_string_t(s) result(string) + character(*), intent(in) :: s + type(string_t) :: string + + string%s = s + +end function new_string_t !> Check if array of TYPE(STRING_T) matches a particular CHARACTER string !! @@ -418,12 +431,13 @@ end subroutine resize_string !>AUTHOR: John S. Urban !!LICENSE: Public Domain -!!## NAME -!! join(3f) - [fpm_strings:EDITING] append CHARACTER variable array into +!> +!!##NAME +!! join(3f) - [M_strings:EDITING] append CHARACTER variable array into !! a single CHARACTER variable with specified separator !! (LICENSE:PD) !! -!!## SYNOPSIS +!!##SYNOPSIS !! !! pure function join(str,sep,trm,left,right,start,end) result (string) !! @@ -436,13 +450,13 @@ end subroutine resize_string !! character(len=*),intent(in),optional :: end !! character(len=:),allocatable :: string !! -!!## DESCRIPTION +!!##DESCRIPTION !! JOIN(3f) appends the elements of a CHARACTER array into a single !! CHARACTER variable, with elements 1 to N joined from left to right. !! By default each element is trimmed of trailing spaces and the !! default separator is a null string. !! -!!## OPTIONS +!!##OPTIONS !! STR(:) array of CHARACTER variables to be joined !! SEP separator string to place between each variable. defaults !! to a null string. @@ -453,81 +467,75 @@ end subroutine resize_string !! TRM option to trim each element of STR of trailing !! spaces. Defaults to .TRUE. !! -!!## RESULT +!!##RESULT !! STRING CHARACTER variable composed of all of the elements of STR() !! appended together with the optional separator SEP placed !! between the elements. !! -!!## EXAMPLE +!!##EXAMPLE !! !! Sample program: -!!```fortran -!! program demo_join -!! use fpm_strings, only: join -!! implicit none -!! character(len=:),allocatable :: s(:) -!! character(len=:),allocatable :: out -!! integer :: i -!! s=[character(len=10) :: 'United',' we',' stand,', & -!! & ' divided',' we fall.'] -!! out=join(s) -!! write(*,'(a)') out -!! write(*,'(a)') join(s,trm=.false.) -!! write(*,'(a)') (join(s,trm=.false.,sep='|'),i=1,3) -!! write(*,'(a)') join(s,sep='<>') -!! write(*,'(a)') join(s,sep=';',left='[',right=']') -!! write(*,'(a)') join(s,left='[',right=']') -!! write(*,'(a)') join(s,left='>>') -!! end program demo_join -!!```fortran !! -!! Expected output: +!! program demo_join +!! use M_strings, only: join +!! implicit none +!! character(len=:),allocatable :: s(:) +!! character(len=:),allocatable :: out +!! integer :: i +!! s=[character(len=10) :: 'United',' we',' stand,', & +!! & ' divided',' we fall.'] +!! out=join(s) +!! write(*,'(a)') out +!! write(*,'(a)') join(s,trm=.false.) +!! write(*,'(a)') (join(s,trm=.false.,sep='|'),i=1,3) +!! write(*,'(a)') join(s,sep='<>') +!! write(*,'(a)') join(s,sep=';',left='[',right=']') +!! write(*,'(a)') join(s,left='[',right=']') +!! write(*,'(a)') join(s,left='>>') +!! end program demo_join !! -!! United we stand, divided we fall. -!! United we stand, divided we fall. -!! United | we | stand, | divided | we fall. -!! United | we | stand, | divided | we fall. -!! United | we | stand, | divided | we fall. -!! United<> we<> stand,<> divided<> we fall. -!! [United];[ we];[ stand,];[ divided];[ we fall.] -!! [United][ we][ stand,][ divided][ we fall.] -!! >>United>> we>> stand,>> divided>> we fall. +!! Expected output: !! +!! United we stand, divided we fall. +!! United we stand, divided we fall. +!! United | we | stand, | divided | we fall. +!! United | we | stand, | divided | we fall. +!! United | we | stand, | divided | we fall. +!! United<> we<> stand,<> divided<> we fall. +!! [United];[ we];[ stand,];[ divided];[ we fall.] +!! [United][ we][ stand,][ divided][ we fall.] +!! >>United>> we>> stand,>> divided>> we fall. pure function join(str,sep,trm,left,right,start,end) result (string) -! @(#)join(3f): append an array of character variables with specified separator into a single CHARACTER variable +! @(#)M_strings::join(3f): merge string array into a single CHARACTER value adding specified separators, caps, prefix and suffix character(len=*),intent(in) :: str(:) -character(len=*),intent(in),optional :: sep -character(len=*),intent(in),optional :: right -character(len=*),intent(in),optional :: left -character(len=*),intent(in),optional :: start -character(len=*),intent(in),optional :: end +character(len=*),intent(in),optional :: sep, right, left, start, end logical,intent(in),optional :: trm +character(len=:),allocatable :: sep_local, left_local, right_local character(len=:),allocatable :: string -integer :: i logical :: trm_local -character(len=:),allocatable :: sep_local -character(len=:),allocatable :: left_local -character(len=:),allocatable :: right_local - - if(present(sep))then ; sep_local=sep ; else ; sep_local='' ; endif - if(present(trm))then ; trm_local=trm ; else ; trm_local=.true. ; endif - if(present(left))then ; left_local=left ; else ; left_local='' ; endif - if(present(right))then ; right_local=right ; else ; right_local='' ; endif - +integer :: i + if(present(sep))then ; sep_local=sep ; else ; sep_local='' ; endif + if(present(trm))then ; trm_local=trm ; else ; trm_local=.true. ; endif + if(present(left))then ; left_local=left ; else ; left_local='' ; endif + if(present(right))then ; right_local=right ; else ; right_local='' ; endif string='' - do i = 1,size(str)-1 + if(size(str).eq.0)then + string=string//left_local//right_local + else + do i = 1,size(str)-1 + if(trm_local)then + string=string//left_local//trim(str(i))//right_local//sep_local + else + string=string//left_local//str(i)//right_local//sep_local + endif + enddo if(trm_local)then - string=string//left_local//trim(str(i))//right_local//sep_local + string=string//left_local//trim(str(i))//right_local else - string=string//left_local//str(i)//right_local//sep_local + string=string//left_local//str(i)//right_local endif - enddo - if(trm_local)then - string=string//left_local//trim(str(i))//right_local - else - string=string//left_local//str(i)//right_local endif if(present(start))string=start//string if(present(end))string=string//end diff --git a/fpm/src/fpm_targets.f90 b/fpm/src/fpm_targets.f90 index 026d349..02bb600 100644 --- a/fpm/src/fpm_targets.f90 +++ b/fpm/src/fpm_targets.f90 @@ -156,11 +156,20 @@ subroutine build_target_list(targets,model) !> The package model from which to construct the target list type(fpm_model_t), intent(inout), target :: model - integer :: i, j + integer :: i, j, n_source character(:), allocatable :: xsuffix, exe_dir type(build_target_t), pointer :: dep logical :: with_lib + ! Check for empty build (e.g. header-only lib) + n_source = sum([(size(model%packages(j)%sources), & + j=1,size(model%packages))]) + + if (n_source < 1) then + allocate(targets(0)) + return + end if + if (get_os_type() == OS_WINDOWS) then xsuffix = '.exe' else @@ -433,6 +442,9 @@ subroutine resolve_target_linking(targets, model) integer :: i character(:), allocatable :: global_link_flags + character(:), allocatable :: global_compile_flags + + if (size(targets) == 0) return if (targets(1)%ptr%target_type == FPM_TARGET_ARCHIVE) then global_link_flags = targets(1)%ptr%output_file @@ -440,17 +452,26 @@ subroutine resolve_target_linking(targets, model) allocate(character(0) :: global_link_flags) end if + global_compile_flags = model%fortran_compile_flags + if (allocated(model%link_libraries)) then if (size(model%link_libraries) > 0) then global_link_flags = global_link_flags // " -l" // string_cat(model%link_libraries," -l") end if end if + if (allocated(model%include_dirs)) then + if (size(model%include_dirs) > 0) then + global_compile_flags = global_compile_flags // & + & " -I" // string_cat(model%include_dirs," -I") + end if + end if + do i=1,size(targets) associate(target => targets(i)%ptr) - target%compile_flags = model%fortran_compile_flags + target%compile_flags = global_compile_flags allocate(target%link_objects(0)) diff --git a/fpm/test/fpm_test/test_manifest.f90 b/fpm/test/fpm_test/test_manifest.f90 index 925eaf3..94e5e07 100644 --- a/fpm/test/fpm_test/test_manifest.f90 +++ b/fpm/test/fpm_test/test_manifest.f90 @@ -4,6 +4,7 @@ module test_manifest use testsuite, only : new_unittest, unittest_t, error_t, test_failed, & & check_string use fpm_manifest + use fpm_strings, only: operator(.in.) implicit none private @@ -183,6 +184,16 @@ contains & "Default library source-dir") if (allocated(error)) return + if (.not.allocated(package%library%include_dir)) then + call test_failed(error,"Default include-dir list not allocated") + return + end if + + if (.not.("include".in.package%library%include_dir)) then + call test_failed(error,"'include' not in default include-dir list") + return + end if + end subroutine test_default_library @@ -579,6 +590,16 @@ contains & "Default library source-dir") if (allocated(error)) return + if (.not.allocated(library%include_dir)) then + call test_failed(error,"Default include-dir list not allocated") + return + end if + + if (.not.("include".in.library%include_dir)) then + call test_failed(error,"'include' not in default include-dir list") + return + end if + end subroutine test_library_empty diff --git a/manifest-reference.md b/manifest-reference.md index 8e9f65d..b40eef8 100644 --- a/manifest-reference.md +++ b/manifest-reference.md @@ -188,17 +188,35 @@ Library targets are exported and useable for other projects. ### Library configuration 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 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. +A library is generated if the source directory or include directory is found in a project. +The default source and include directories are ``src`` and ``include``; these can be modified in the *library* section using the *source-dir* and *include-dir* entries. +Paths for the source and include directories are given relative to the project root and use ``/`` as path separator on all platforms. *Example:* ```toml [library] source-dir = "lib" +include-dir = "inc" +``` + +#### Include directory + +> Supported in Fortran fpm only + +Projects which use the Fortran `include` statement or C preprocessor `#include` statement, can use the *include-dir* key to specify search directories for the included files. +*include-dir* can contain one or more directories, where multiple directories are specified using a list of strings. +Include directories from all project dependencies are passed to the compiler using the appropriate compiler flag. + +*Example:* + +```toml +[library] +include-dir = ["include", "third_party/include"] ``` +> *include-dir* does not currently allow using pre-built module `.mod` files + #### Custom build script > Supported in Bootstrap fpm only |