aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--fpm/src/fpm.f9043
-rw-r--r--fpm/src/fpm_backend.f906
-rw-r--r--fpm/src/fpm_filesystem.f9017
-rw-r--r--fpm/src/fpm_model.f9011
-rw-r--r--fpm/src/fpm_sources.f90101
5 files changed, 122 insertions, 56 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90
index b57a713..0047ed4 100644
--- a/fpm/src/fpm.f90
+++ b/fpm/src/fpm.f90
@@ -4,8 +4,11 @@ use fpm_strings, only: string_t, str_ends_with
use fpm_backend, only: build_package
use fpm_command_line, only: fpm_build_settings
use fpm_environment, only: run, get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
-use fpm_filesystem, only: join_path, number_of_rows, list_files, exists
-use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t
+use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists
+use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t, &
+ FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
+ FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST
+
use fpm_sources, only: add_executable_sources, add_sources_from_dir, &
resolve_module_dependencies
use fpm_manifest, only : get_package_data, default_executable, &
@@ -37,20 +40,36 @@ subroutine build_model(model, settings, package, error)
model%link_flags = ''
! Add sources from executable directories
- if (allocated(package%executable)) then
+ if (is_dir('app')) then
+ call add_sources_from_dir(model%sources,'app', FPM_SCOPE_APP, &
+ with_executables=.true., error=error)
+ if (allocated(error)) then
+ return
+ end if
+
+ end if
+ if (is_dir('test')) then
+ call add_sources_from_dir(model%sources,'test', FPM_SCOPE_TEST, &
+ with_executables=.true., error=error)
+
+ if (allocated(error)) then
+ return
+ end if
+
+ end if
+ if (allocated(package%executable)) then
call add_executable_sources(model%sources, package%executable, &
- is_test=.false., error=error)
-
+ FPM_SCOPE_APP, error=error)
+
if (allocated(error)) then
return
end if
end if
if (allocated(package%test)) then
-
call add_executable_sources(model%sources, package%test, &
- is_test=.true., error=error)
+ FPM_SCOPE_TEST, error=error)
if (allocated(error)) then
return
@@ -59,9 +78,8 @@ subroutine build_model(model, settings, package, error)
end if
if (allocated(package%library)) then
-
- call add_sources_from_dir(model%sources,package%library%source_dir, &
- error=error)
+ call add_sources_from_dir(model%sources, package%library%source_dir, &
+ FPM_SCOPE_LIB, error=error)
if (allocated(error)) then
return
@@ -90,8 +108,9 @@ if (.not.allocated(package%library) .and. exists("src")) then
call default_library(package%library)
end if
-! Populate executable in case we find the default app directory
-if (.not.allocated(package%executable) .and. exists("app")) then
+! 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
diff --git a/fpm/src/fpm_backend.f90 b/fpm/src/fpm_backend.f90
index 65d6dae..40460d7 100644
--- a/fpm/src/fpm_backend.f90
+++ b/fpm/src/fpm_backend.f90
@@ -6,7 +6,9 @@ use fpm_environment, only: run, get_os_type, OS_WINDOWS
use fpm_filesystem, only: basename, join_path, exists, mkdir
use fpm_model, only: fpm_model_t, srcfile_t, FPM_UNIT_MODULE, &
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, &
- FPM_UNIT_CSOURCE, FPM_UNIT_PROGRAM
+ FPM_UNIT_CSOURCE, FPM_UNIT_PROGRAM, &
+ FPM_SCOPE_TEST
+
use fpm_strings, only: split
implicit none
@@ -59,7 +61,7 @@ subroutine build_package(model)
base = basename(model%sources(i)%file_name,suffix=.false.)
- if (model%sources(i)%is_test) then
+ if (model%sources(i)%unit_scope == FPM_SCOPE_TEST) then
subdir = 'test'
else
subdir = 'app'
diff --git a/fpm/src/fpm_filesystem.f90 b/fpm/src/fpm_filesystem.f90
index 488a202..91baba1 100644
--- a/fpm/src/fpm_filesystem.f90
+++ b/fpm/src/fpm_filesystem.f90
@@ -5,8 +5,8 @@ module fpm_filesystem
use fpm_strings, only: f_string, string_t, split
implicit none
private
- public :: basename, join_path, number_of_rows, read_lines, list_files, &
- mkdir, exists, get_temp_filename, windows_path
+ public :: basename, dirname, is_dir, join_path, number_of_rows, read_lines, list_files,&
+ mkdir, exists, get_temp_filename, windows_path
integer, parameter :: LINE_BUFFER_LEN = 1000
@@ -40,6 +40,19 @@ function basename(path,suffix) result (base)
end function basename
+function dirname(path) result (dir)
+ ! Extract dirname from path
+ !
+ character(*), intent(In) :: path
+ character(:), allocatable :: dir
+
+ character(:), allocatable :: file_parts(:)
+
+ dir = path(1:scan(path,'/\',back=.true.))
+
+end function dirname
+
+
logical function is_dir(dir)
character(*), intent(in) :: dir
integer :: stat
diff --git a/fpm/src/fpm_model.f90 b/fpm/src/fpm_model.f90
index 702ba6f..36086df 100644
--- a/fpm/src/fpm_model.f90
+++ b/fpm/src/fpm_model.f90
@@ -8,7 +8,8 @@ public :: srcfile_ptr, srcfile_t, fpm_model_t
public :: FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, &
- FPM_UNIT_CHEADER
+ FPM_UNIT_CHEADER, FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
+ FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST
integer, parameter :: FPM_UNIT_UNKNOWN = -1
integer, parameter :: FPM_UNIT_PROGRAM = 1
@@ -18,6 +19,12 @@ integer, parameter :: FPM_UNIT_SUBPROGRAM = 4
integer, parameter :: FPM_UNIT_CSOURCE = 5
integer, parameter :: FPM_UNIT_CHEADER = 6
+integer, parameter :: FPM_SCOPE_UNKNOWN = -1
+integer, parameter :: FPM_SCOPE_LIB = 1
+integer, parameter :: FPM_SCOPE_DEP = 2
+integer, parameter :: FPM_SCOPE_APP = 3
+integer, parameter :: FPM_SCOPE_TEST = 4
+
type srcfile_ptr
! For constructing arrays of src_file pointers
type(srcfile_t), pointer :: ptr => null()
@@ -30,6 +37,8 @@ type srcfile_t
! File path relative to cwd
character(:), allocatable :: exe_name
! Name of executable for FPM_UNIT_PROGRAM
+ integer :: unit_scope = FPM_SCOPE_UNKNOWN
+ ! app/test/lib/dependency
logical :: is_test = .false.
! Is executable a test?
type(string_t), allocatable :: modules_provided(:)
diff --git a/fpm/src/fpm_sources.f90 b/fpm/src/fpm_sources.f90
index ead4ed3..72fcf5b 100644
--- a/fpm/src/fpm_sources.f90
+++ b/fpm/src/fpm_sources.f90
@@ -3,8 +3,10 @@ use fpm_error, only: error_t, file_parse_error
use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t, &
FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, &
- FPM_UNIT_CSOURCE, FPM_UNIT_CHEADER
-use fpm_filesystem, only: basename, read_lines, list_files
+ FPM_UNIT_CSOURCE, FPM_UNIT_CHEADER, FPM_SCOPE_UNKNOWN, &
+ FPM_SCOPE_LIB, FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST
+
+use fpm_filesystem, only: basename, dirname, read_lines, list_files
use fpm_strings, only: lower, split, str_ends_with, string_t, operator(.in.)
use fpm_manifest_executable, only: executable_t
implicit none
@@ -22,11 +24,12 @@ character(15), parameter :: INTRINSIC_MODULE_NAMES(*) = &
contains
-subroutine add_sources_from_dir(sources,directory,with_executables,error)
+subroutine add_sources_from_dir(sources,directory,scope,with_executables,error)
! Enumerate sources in a directory
!
type(srcfile_t), allocatable, intent(inout), target :: sources(:)
character(*), intent(in) :: directory
+ integer, intent(in) :: scope
logical, intent(in), optional :: with_executables
type(error_t), allocatable, intent(out) :: error
@@ -34,14 +37,25 @@ subroutine add_sources_from_dir(sources,directory,with_executables,error)
logical, allocatable :: is_source(:), exclude_source(:)
type(string_t), allocatable :: file_names(:)
type(string_t), allocatable :: src_file_names(:)
+ type(string_t), allocatable :: existing_src_files(:)
type(srcfile_t), allocatable :: dir_sources(:)
! Scan directory for sources
call list_files(directory, file_names,recurse=.true.)
- is_source = [(str_ends_with(lower(file_names(i)%s), ".f90") .or. &
- str_ends_with(lower(file_names(i)%s), ".c") .or. &
- str_ends_with(lower(file_names(i)%s), ".h"),i=1,size(file_names))]
+ if (allocated(sources)) then
+ allocate(existing_src_files(size(sources)))
+ do i=1,size(sources)
+ existing_src_files(i)%s = sources(i)%file_name
+ end do
+ else
+ allocate(existing_src_files(0))
+ end if
+
+ is_source = [(.not.(file_names(i)%s .in. existing_src_files) .and. &
+ (str_ends_with(lower(file_names(i)%s), ".f90") .or. &
+ str_ends_with(lower(file_names(i)%s), ".c") .or. &
+ str_ends_with(lower(file_names(i)%s), ".h") ),i=1,size(file_names))]
src_file_names = pack(file_names,is_source)
allocate(dir_sources(size(src_file_names)))
@@ -70,6 +84,8 @@ subroutine add_sources_from_dir(sources,directory,with_executables,error)
end if
+ dir_sources(i)%unit_scope = scope
+
! Exclude executables unless specified otherwise
exclude_source(i) = (dir_sources(i)%unit_type == FPM_UNIT_PROGRAM)
if (dir_sources(i)%unit_type == FPM_UNIT_PROGRAM .and. &
@@ -93,59 +109,43 @@ subroutine add_sources_from_dir(sources,directory,with_executables,error)
end subroutine add_sources_from_dir
-subroutine add_executable_sources(sources,executables,is_test,error)
- ! Add sources from executable directories specified in manifest
- ! Only allow executables that are explicitly specified in manifest
- !
+subroutine add_executable_sources(sources,executables,scope,error)
+ ! Include sources from any directories specified
+ ! in [[executable]] entries and apply any customisations
+ !
type(srcfile_t), allocatable, intent(inout), target :: sources(:)
class(executable_t), intent(in) :: executables(:)
- logical, intent(in) :: is_test
+ integer, intent(in) :: scope
type(error_t), allocatable, intent(out) :: error
integer :: i, j
type(string_t), allocatable :: exe_dirs(:)
- logical, allocatable :: exclude_source(:)
- type(srcfile_t), allocatable :: dir_sources(:)
call get_executable_source_dirs(exe_dirs,executables)
do i=1,size(exe_dirs)
-
- call add_sources_from_dir(dir_sources,exe_dirs(i)%s, &
- with_executables=.true.,error=error)
+ call add_sources_from_dir(sources,exe_dirs(i)%s, &
+ scope, with_executables=.true.,error=error)
if (allocated(error)) then
return
end if
-
end do
- allocate(exclude_source(size(dir_sources)))
-
- do i = 1, size(dir_sources)
-
- ! Only allow executables in 'executables' list
- exclude_source(i) = (dir_sources(i)%unit_type == FPM_UNIT_PROGRAM)
+ do i = 1, size(sources)
do j=1,size(executables)
- if (basename(dir_sources(i)%file_name,suffix=.true.) == &
+ if (basename(sources(i)%file_name,suffix=.true.) == &
executables(j)%main) then
- exclude_source(i) = .false.
- dir_sources(i)%exe_name = executables(j)%name
- dir_sources(i)%is_test = is_test
+
+ sources(i)%exe_name = executables(j)%name
exit
end if
end do
end do
- if (.not.allocated(sources)) then
- sources = pack(dir_sources,.not.exclude_source)
- else
- sources = [sources, pack(dir_sources,.not.exclude_source)]
- end if
-
end subroutine add_executable_sources
@@ -571,14 +571,21 @@ subroutine resolve_module_dependencies(sources)
! Dependency satisfied in same file, skip
cycle
end if
-
- dep%ptr => find_module_dependency(sources,sources(i)%modules_used(j)%s)
+
+ if (sources(i)%unit_type == FPM_UNIT_PROGRAM) then
+ dep%ptr => &
+ find_module_dependency(sources,sources(i)%modules_used(j)%s, &
+ include_dir = dirname(sources(i)%file_name))
+ else
+ dep%ptr => &
+ find_module_dependency(sources,sources(i)%modules_used(j)%s)
+ end if
if (.not.associated(dep%ptr)) then
write(*,*) '(!) Unable to find source for module dependency: ', &
sources(i)%modules_used(j)%s
write(*,*) ' for file ',sources(i)%file_name
- ! stop
+ error stop
end if
n_depend = n_depend + 1
@@ -599,9 +606,15 @@ subroutine resolve_module_dependencies(sources)
end subroutine resolve_module_dependencies
-function find_module_dependency(sources,module_name) result(src_ptr)
+function find_module_dependency(sources,module_name,include_dir) result(src_ptr)
+ ! Find a module dependency in the library or a dependency library
+ !
+ ! 'include_dir' specifies an allowable non-library search directory
+ ! (Used for executable dependencies)
+ !
type(srcfile_t), intent(in), target :: sources(:)
character(*), intent(in) :: module_name
+ character(*), intent(in), optional :: include_dir
type(srcfile_t), pointer :: src_ptr
integer :: k, l
@@ -613,8 +626,18 @@ function find_module_dependency(sources,module_name) result(src_ptr)
do l=1,size(sources(k)%modules_provided)
if (module_name == sources(k)%modules_provided(l)%s) then
- src_ptr => sources(k)
- exit
+ select case(sources(k)%unit_scope)
+ case (FPM_SCOPE_LIB, FPM_SCOPE_DEP)
+ src_ptr => sources(k)
+ exit
+ case default
+ if (present(include_dir)) then
+ if (dirname(sources(k)%file_name) == include_dir) then
+ src_ptr => sources(k)
+ exit
+ end if
+ end if
+ end select
end if
end do