aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorLKedward <laurence.kedward@bristol.ac.uk>2020-09-05 15:03:24 +0100
committerLKedward <laurence.kedward@bristol.ac.uk>2020-09-05 15:03:24 +0100
commit82146dec39b21b8cad6402508f748a67f914110d (patch)
tree1f10f3d1a6ef2067a963b86c845611df58d55579
parent03f79c6d74798dac0c4e5c260c4a700c167cbd53 (diff)
downloadfpm-82146dec39b21b8cad6402508f748a67f914110d.tar.gz
fpm-82146dec39b21b8cad6402508f748a67f914110d.zip
Use manifest data for library and executables
Locations
-rw-r--r--fpm/src/fpm.f9024
-rw-r--r--fpm/src/fpm_backend.f902
-rw-r--r--fpm/src/fpm_model.f9030
-rw-r--r--fpm/src/fpm_sources.f90158
4 files changed, 149 insertions, 65 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90
index 86f9983..def32dd 100644
--- a/fpm/src/fpm.f90
+++ b/fpm/src/fpm.f90
@@ -20,6 +20,7 @@ contains
subroutine cmd_build(settings)
type(fpm_build_settings), intent(in) :: settings
type(package_t) :: package
+type(fpm_model_t) :: model
type(error_t), allocatable :: error
type(string_t), allocatable :: files(:)
character(:), allocatable :: basename, linking
@@ -46,27 +47,10 @@ if (.not.(allocated(package%library) .or. allocated(package%executable))) then
error stop 1
end if
-linking = ""
-if (allocated(package%library)) then
- call list_files(package%library%source_dir, files)
- do i = 1, size(files)
- if (str_ends_with(files(i)%s, ".f90")) then
- n = len(files(i)%s)
- basename = files(i)%s
- call run("gfortran -c " // package%library%source_dir // "/" // &
- & basename // " -o " // basename // ".o")
- linking = linking // " " // basename // ".o"
- end if
- end do
-end if
+call build_model(model, settings, package)
+
+call build_package(model)
-do i = 1, size(package%executable)
- basename = package%executable(i)%main
- call run("gfortran -c " // package%executable(i)%source_dir // "/" // &
- & basename // " -o " // basename // ".o")
- call run("gfortran " // basename // ".o " // linking // " -o " // &
- & package%executable(i)%name)
-end do
end subroutine
subroutine cmd_install()
diff --git a/fpm/src/fpm_backend.f90 b/fpm/src/fpm_backend.f90
index 07cd646..5a16193 100644
--- a/fpm/src/fpm_backend.f90
+++ b/fpm/src/fpm_backend.f90
@@ -54,7 +54,7 @@ subroutine build_package(model)
call run("gfortran " // model%output_directory // '/' // basename // ".o "// &
linking //" " //model%link_flags // " -o " // model%output_directory &
- // '/' // model%package_name)
+ // '/' // model%sources(i)%exe_name)
end if
diff --git a/fpm/src/fpm_model.f90 b/fpm/src/fpm_model.f90
index 12078b0..307033d 100644
--- a/fpm/src/fpm_model.f90
+++ b/fpm/src/fpm_model.f90
@@ -4,8 +4,10 @@ module fpm_model
use fpm_command_line, only: fpm_build_settings
use fpm_filesystem, only: exists
-use fpm_manifest, only: package_t
-use fpm_sources, only: resolve_dependencies, scan_sources, srcfile_t
+use fpm_manifest, only: package_t, default_library, default_executable
+use fpm_manifest_executable, only: executable_t
+use fpm_sources, only: resolve_module_dependencies, add_sources_from_dir, &
+ add_executable_sources, srcfile_t
use fpm_strings, only: string_t
implicit none
@@ -30,18 +32,14 @@ end type fpm_model_t
contains
-subroutine build_model(model, settings, manifest)
+subroutine build_model(model, settings, package)
! Constructs a valid fpm model from command line settings and toml manifest
!
type(fpm_model_t), intent(out) :: model
type(fpm_build_settings), intent(in) :: settings
- type(package_t), intent(in) :: manifest
+ type(package_t), intent(in) :: package
- if (exists("src/fpm.f90")) then
- model%package_name = "fpm"
- else
- model%package_name = "hello_world"
- end if
+ model%package_name = package%name
! #TODO: Choose flags and output directory based on cli settings & manifest inputs
model%fortran_compiler = 'gfortran'
@@ -51,9 +49,19 @@ subroutine build_model(model, settings, manifest)
'-J'//model%output_directory
model%link_flags = ''
- call scan_sources(model%sources,[string_t('app'),string_t('src')])
+ ! Add sources from executable directories
+ if (allocated(package%executable)) then
+ call add_executable_sources(model%sources, package%executable)
+ end if
+ if (allocated(package%test)) then
+ call add_executable_sources(model%sources, package%test)
+ end if
+
+ if (allocated(package%library)) then
+ call add_sources_from_dir(model%sources,package%library%source_dir)
+ end if
- call resolve_dependencies(model%sources)
+ call resolve_module_dependencies(model%sources)
end subroutine build_model
diff --git a/fpm/src/fpm_sources.f90 b/fpm/src/fpm_sources.f90
index ab0f68a..bf6124a 100644
--- a/fpm/src/fpm_sources.f90
+++ b/fpm/src/fpm_sources.f90
@@ -1,11 +1,12 @@
module fpm_sources
use fpm_filesystem, only: read_lines, list_files
use fpm_strings, only: lower, split, str_ends_with, string_t
+use fpm_manifest_executable, only: executable_t
implicit none
private
public :: srcfile_ptr, srcfile_t
-public :: scan_sources, resolve_dependencies
+public :: add_sources_from_dir, add_executable_sources, resolve_module_dependencies
public :: FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, &
FPM_UNIT_CHEADER
@@ -32,6 +33,8 @@ type srcfile_t
! and it's metadata
character(:), allocatable :: file_name
! File path relative to cwd
+ character(:), allocatable :: exe_name
+ ! Name of executable for FPM_UNIT_PROGRAM
type(string_t), allocatable :: modules_provided(:)
! Modules provided by this source file (lowerstring)
integer :: unit_type = FPM_UNIT_UNKNOWN
@@ -50,62 +53,151 @@ end type srcfile_t
contains
-subroutine scan_sources(sources,directories)
- ! Enumerate Fortran sources and resolve file
- ! dependencies
+subroutine add_sources_from_dir(sources,directory,with_executables)
+ ! Enumerate sources in a directory
!
- type(srcfile_t), allocatable, intent(out), target :: sources(:)
- type(string_t), intent(in) :: directories(:)
+ type(srcfile_t), allocatable, intent(inout), target :: sources(:)
+ character(*), intent(in) :: directory
+ logical, intent(in), optional :: with_executables
integer :: i, j
- logical, allocatable :: is_source(:)
- type(string_t), allocatable :: dir_files(:)
+ logical, allocatable :: is_source(:), exclude_source(:)
type(string_t), allocatable :: file_names(:)
type(string_t), allocatable :: src_file_names(:)
+ type(srcfile_t), allocatable :: dir_sources(:)
- ! Scan directories for sources
- allocate(file_names(0))
- do i=1,size(directories)
+ character(:), allocatable :: basename
+ character(:), allocatable :: file_parts(:)
- call list_files(directories(i)%s, dir_files)
- file_names = [file_names,(string_t(directories(i)%s//'/'//dir_files(j)%s),j=1,size(dir_files))]
-
- end do
+ ! Scan directory for sources
+ call list_files(directory, file_names)
+ file_names = [(string_t(directory//'/'//file_names(j)%s),j=1,size(file_names))]
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))]
src_file_names = pack(file_names,is_source)
- allocate(sources(size(src_file_names)))
+ allocate(dir_sources(size(src_file_names)))
+ allocate(exclude_source(size(src_file_names)))
do i = 1, size(src_file_names)
if (str_ends_with(lower(src_file_names(i)%s), ".f90")) then
- sources(i) = parse_f_source(src_file_names(i)%s)
+ dir_sources(i) = parse_f_source(src_file_names(i)%s)
end if
if (str_ends_with(lower(src_file_names(i)%s), ".c") .or. &
str_ends_with(lower(src_file_names(i)%s), ".h")) then
- sources(i) = parse_c_source(src_file_names(i)%s)
+ dir_sources(i) = parse_c_source(src_file_names(i)%s)
end if
+ ! 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. &
+ present(with_executables)) then
+ if (with_executables) then
+
+ exclude_source(i) = .false.
+ call split(src_file_names(i)%s,file_parts,delimiters='\/.')
+ basename = file_parts(size(file_parts)-1)
+
+ dir_sources(i)%exe_name = basename
+
+ end if
+ end if
+
+ 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_sources_from_dir
+
+
+subroutine add_executable_sources(sources,executables)
+ ! Add sources from executable directories specified in manifest
+ ! Only allow executables that are explicitly specified in manifest
+ !
+ type(srcfile_t), allocatable, intent(inout), target :: sources(:)
+ class(executable_t), intent(in), optional :: executables(:)
+
+ integer :: i, j
+
+ type(string_t), allocatable :: exe_dirs(:)
+ logical, allocatable :: exclude_source(:)
+ type(srcfile_t), allocatable :: dir_sources(:)
+
+ character(:), allocatable :: basename
+ character(:), allocatable :: file_parts(:)
+
+ 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.)
+ 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)
+
+ call split(dir_sources(i)%file_name,file_parts,delimiters='\/')
+ basename = file_parts(size(file_parts))
+
+ do j=1,size(executables)
+ if (executables(j)%main == basename) then
+ exclude_source(i) = .false.
+ dir_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
+
+
+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(:)
+
+ type(string_t) :: dirs_temp(size(executables))
+
+ integer :: i, j, n
+
+ n = 0
+ do i=1,size(executables)
+ if (.not.any([(dirs_temp(j)%s==executables(i)%source_dir, &
+ j=1,n)])) then
+
+ n = n + 1
+ dirs_temp(n)%s = executables(i)%source_dir
+
+ end if
end do
- ! do i=1,size(sources)
- ! write(*,*) 'Filename: "',sources(i)%file_name,'"'
- ! do j=1,size(sources(i)%modules_provided)
- ! write(*,*) ' Provides: "',sources(i)%modules_provided(j)%s,'"'
- ! end do
- ! do j=1,size(sources(i)%modules_used)
- ! write(*,*) ' Uses: "',sources(i)%modules_used(j)%s,'"'
- ! end do
- ! do j=1,size(sources(i)%include_dependencies)
- ! write(*,*) ' Includes: "',sources(i)%include_dependencies(j)%s,'"'
- ! end do
- ! end do
+ if (.not.allocated(exe_dirs)) then
+ exe_dirs = dirs_temp(1:n)
+ else
+ exe_dirs = [exe_dirs,dirs_temp(1:n)]
+ end if
-end subroutine scan_sources
+end subroutine get_executable_source_dirs
function parse_f_source(f_filename) result(f_source)
@@ -364,7 +456,7 @@ function parse_c_source(c_filename) result(c_source)
end function parse_c_source
-subroutine resolve_dependencies(sources)
+subroutine resolve_module_dependencies(sources)
! After enumerating all source files: resolve file dependencies
! by searching on module names
!
@@ -392,7 +484,7 @@ subroutine resolve_dependencies(sources)
end do
-end subroutine resolve_dependencies
+end subroutine resolve_module_dependencies
function find_module_dependency(sources,module_name) result(src_ptr)
type(srcfile_t), intent(in), target :: sources(:)