Skip to content
Merged
Show file tree
Hide file tree
Changes from 6 commits
Commits
Show all changes
22 commits
Select commit Hold shift + click to select a range
3f6c74f
Update: to enable local path dependencies
LKedward Sep 27, 2020
d9dc4b4
Enable fpm CI tests for local path dependency demos
LKedward Sep 27, 2020
c6a9646
Add: support for local dev-depenencies
LKedward Sep 27, 2020
6f8a446
Add: circular_example demo to fpm CI scripts
LKedward Sep 27, 2020
72dab19
Minor fix: to local dependency relative path
LKedward Sep 27, 2020
64a0f72
Retain source file structure in object files
LKedward Sep 27, 2020
71554f6
Merge remote-tracking branch 'upstream/master' into local-depends
LKedward Oct 3, 2020
1fb2c20
Update: hello_complex_2 to expose link bug
LKedward Oct 3, 2020
4ef3025
Fix: duplication of app modules
LKedward Oct 3, 2020
48dd8bc
Update: source parsing test - include statement
LKedward Oct 3, 2020
bdaac5c
Fix: include statement parsing
LKedward Oct 3, 2020
5027275
Merge branch 'fix-duplicate-discovery' into local-depends
LKedward Oct 3, 2020
22ea5a6
Add: support for remote git dependencies
LKedward Oct 3, 2020
b6ec6b1
Fix: duplication of app modules
LKedward Oct 3, 2020
7ca0ba2
Update: source parsing test - include statement
LKedward Oct 3, 2020
10d835a
Fix: include statement parsing
LKedward Oct 3, 2020
a48c13f
Merge branch 'fix-duplicate-discovery' into local-depends
LKedward Oct 3, 2020
9b790fb
Update: use default git object = 'HEAD' for checkout
LKedward Oct 3, 2020
3207fd5
Merge remote-tracking branch 'upstream/master' into local-depends
LKedward Oct 3, 2020
501be36
Update fpm/src/fpm.f90
LKedward Oct 4, 2020
24b115e
Don't pull dev dependencies of dependencies.
LKedward Oct 4, 2020
eebe0ff
Merge branch 'master' into local-depends
LKedward Oct 17, 2020
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
76 changes: 41 additions & 35 deletions fpm/src/fpm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -53,7 +53,7 @@ recursive subroutine add_libsources_from_package(sources,package_list,package, &
! Add library sources from dependencies
if (allocated(package%dependency)) then

call add_local_dependencies(package%dependency)
call add_dependencies(package%dependency)

if (allocated(error)) then
return
Expand All @@ -64,7 +64,7 @@ recursive subroutine add_libsources_from_package(sources,package_list,package, &
! Add library sources from dev-dependencies
if (dev_depends .and. allocated(package%dev_dependency)) then

call add_local_dependencies(package%dev_dependency)
call add_dependencies(package%dev_dependency)

if (allocated(error)) then
return
Expand All @@ -74,13 +74,15 @@ recursive subroutine add_libsources_from_package(sources,package_list,package, &

contains

subroutine add_local_dependencies(dependency_list)
subroutine add_dependencies(dependency_list)
type(dependency_t) :: dependency_list(:)

integer :: i
type(string_t) :: dep_name
type(package_t) :: dependency

character(:), allocatable :: dependency_path

do i=1,size(dependency_list)

if (dependency_list(i)%name .in. package_list) then
Expand All @@ -89,49 +91,53 @@ subroutine add_local_dependencies(dependency_list)

if (allocated(dependency_list(i)%git)) then

call fatal_error(error,'Remote dependencies not implemented')
return
dependency_path = join_path('build','dependencies',dependency_list(i)%name)

end if

if (allocated(dependency_list(i)%path)) then
if (.not.exists(join_path(dependency_path,'fpm.toml'))) then
call dependency_list(i)%git%checkout(dependency_path, error)
if (allocated(error)) return
end if

call get_package_data(dependency, &
join_path(package_root,dependency_list(i)%path,"fpm.toml"), error)
else if (allocated(dependency_list(i)%path)) then

dependency_path = join_path(package_root,dependency_list(i)%path)

if (allocated(error)) then
error%message = 'Error while parsing manifest for dependency package at:'//&
new_line('a')//join_path(package_root,dependency_list(i)%path,"fpm.toml")//&
new_line('a')//error%message
return
end if
end if

if (.not.allocated(dependency%library) .and. &
exists(join_path(package_root,dependency_list(i)%path,"src"))) then
allocate(dependency%library)
dependency%library%source_dir = "src"
end if
call get_package_data(dependency, &
join_path(dependency_path,"fpm.toml"), error)


call add_libsources_from_package(sources,package_list,dependency, &
package_root=join_path(package_root,dependency_list(i)%path), &
dev_depends=dev_depends, error=error)

if (allocated(error)) then
error%message = 'Error while processing sources for dependency package "'//&
new_line('a')//dependency%name//'"'//&
new_line('a')//error%message
return
end if
if (allocated(error)) then
error%message = 'Error while parsing manifest for dependency package at:'//&
new_line('a')//join_path(dependency_path,"fpm.toml")//&
new_line('a')//error%message
return
end if

dep_name%s = dependency_list(i)%name
package_list = [package_list, dep_name]
if (.not.allocated(dependency%library) .and. &
exists(join_path(dependency_path,"src"))) then
allocate(dependency%library)
dependency%library%source_dir = "src"
end if


call add_libsources_from_package(sources,package_list,dependency, &
package_root=dependency_path, &
dev_depends=dev_depends, error=error)

if (allocated(error)) then
error%message = 'Error while processing sources for dependency package "'//&
new_line('a')//dependency%name//'"'//&
new_line('a')//error%message
return
end if

dep_name%s = dependency_list(i)%name
package_list = [package_list, dep_name]

end do

end subroutine add_local_dependencies
end subroutine add_dependencies

end subroutine add_libsources_from_package

Expand Down
43 changes: 43 additions & 0 deletions fpm/src/fpm/git.f90
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
!> Implementation for interacting with git repositories.
module fpm_git
use fpm_error, only: error_t, fatal_error
implicit none

public :: git_target_t
Expand Down Expand Up @@ -43,6 +44,9 @@ module fpm_git

contains

!> Fetch and checkout in local directory
procedure :: checkout

!> Show information on instance
procedure :: info

Expand Down Expand Up @@ -124,6 +128,45 @@ function git_target_tag(url, tag) result(self)
end function git_target_tag


subroutine checkout(self,local_path, error)

!> Instance of the git target
class(git_target_t), intent(in) :: self

!> Local path to checkout in
character(*), intent(in) :: local_path

!> Error
type(error_t), allocatable, intent(out) :: error

!> Stat for execute_command_line
integer :: stat

call execute_command_line("git init "//local_path, exitstat=stat)

if (stat /= 0) then
call fatal_error(error,'Error while initiating git repository for remote dependency')
return
end if

call execute_command_line("git -C "//local_path//" fetch "//self%url//&
" "//self%object, exitstat=stat)

if (stat /= 0) then
call fatal_error(error,'Error while fetching git repository for remote dependency')
return
end if

call execute_command_line("git -C "//local_path//" checkout -qf FETCH_HEAD", exitstat=stat)

if (stat /= 0) then
call fatal_error(error,'Error while checking out git repository for remote dependency')
return
end if

end subroutine checkout


!> Show information on git target
subroutine info(self, unit, verbosity)

Expand Down
134 changes: 74 additions & 60 deletions fpm/src/fpm_sources.f90
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ module fpm_sources
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, canon_path, dirname, read_lines, list_files
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
implicit none
Expand All @@ -24,6 +24,33 @@ module fpm_sources

contains

function parse_source(source_file_path,error) result(source)
character(*), intent(in) :: source_file_path
type(error_t), allocatable, intent(out) :: error
type(srcfile_t) :: source

if (str_ends_with(lower(source_file_path), ".f90")) then

source = parse_f_source(source_file_path, error)

if (source%unit_type == FPM_UNIT_PROGRAM) then
source%exe_name = basename(source_file_path,suffix=.false.)
end if

else if (str_ends_with(lower(source_file_path), ".c") .or. &
str_ends_with(lower(source_file_path), ".h")) then

source = parse_c_source(source_file_path,error)

end if

if (allocated(error)) then
return
end if

end function parse_source


subroutine add_sources_from_dir(sources,directory,scope,with_executables,error)
! Enumerate sources in a directory
!
Expand All @@ -33,7 +60,7 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,error)
logical, intent(in), optional :: with_executables
type(error_t), allocatable, intent(out) :: error

integer :: i, j
integer :: i
logical, allocatable :: is_source(:), exclude_source(:)
type(string_t), allocatable :: file_names(:)
type(string_t), allocatable :: src_file_names(:)
Expand Down Expand Up @@ -63,26 +90,8 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,error)

do i = 1, size(src_file_names)

if (str_ends_with(lower(src_file_names(i)%s), ".f90")) then

dir_sources(i) = parse_f_source(src_file_names(i)%s, error)

if (allocated(error)) then
return
end if

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

dir_sources(i) = parse_c_source(src_file_names(i)%s,error)

if (allocated(error)) then
return
end if

end if
dir_sources(i) = parse_source(src_file_names(i)%s,error)
if (allocated(error)) return

dir_sources(i)%unit_scope = scope

Expand All @@ -93,7 +102,6 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,error)
if (with_executables) then

exclude_source(i) = .false.
dir_sources(i)%exe_name = basename(src_file_names(i)%s,suffix=.false.)

end if
end if
Expand Down Expand Up @@ -122,49 +130,50 @@ subroutine add_executable_sources(sources,executables,scope,auto_discover,error)
integer :: i, j

type(string_t), allocatable :: exe_dirs(:)
logical, allocatable :: include_source(:)
type(srcfile_t), allocatable :: dir_sources(:)
type(srcfile_t) :: exe_source

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, &
scope, with_executables=.true.,error=error)
call add_sources_from_dir(sources,exe_dirs(i)%s, &
scope, with_executables=auto_discover,error=error)

if (allocated(error)) then
return
end if
end do

allocate(include_source(size(dir_sources)))
exe_loop: do i=1,size(executables)

do i = 1, size(dir_sources)

! Include source by default if not a program or if auto_discover is enabled
include_source(i) = (dir_sources(i)%unit_type /= FPM_UNIT_PROGRAM) .or. &
auto_discover
! Check if executable already discovered automatically
! and apply any overrides
do j=1,size(sources)

! Always include sources specified in fpm.toml
do j=1,size(executables)

if (basename(dir_sources(i)%file_name,suffix=.true.) == executables(j)%main .and.&
canon_path(dirname(dir_sources(i)%file_name)) == &
canon_path(executables(j)%source_dir) ) then
if (basename(sources(j)%file_name,suffix=.true.) == executables(i)%main .and.&
canon_path(dirname(sources(j)%file_name)) == &
canon_path(executables(i)%source_dir) ) then

include_source(i) = .true.
dir_sources(i)%exe_name = executables(j)%name
exit
sources(j)%exe_name = executables(i)%name
cycle exe_loop

end if

end do

end do
! Add if not already discovered (auto_discovery off)
exe_source = parse_source(join_path(executables(i)%source_dir,executables(i)%main),error)
exe_source%exe_name = executables(i)%name
exe_source%unit_scope = scope

if (allocated(error)) return

if (.not.allocated(sources)) then
sources = pack(dir_sources,include_source)
else
sources = [sources, pack(dir_sources,include_source)]
end if
if (.not.allocated(sources)) then
sources = [exe_source]
else
sources = [sources, exe_source]
end if

end do exe_loop

end subroutine add_executable_sources

Expand Down Expand Up @@ -291,21 +300,26 @@ function parse_f_source(f_filename,error) result(f_source)
end if

! Process 'INCLUDE' statements
if (index(adjustl(lower(file_lines(i)%s)),'include') == 1) then

n_include = n_include + 1
ic = index(adjustl(lower(file_lines(i)%s)),'include')
if ( ic == 1 ) then
ic = index(lower(file_lines(i)%s),'include')
if (index(adjustl(file_lines(i)%s(ic+7:)),'"') == 1 .or. &
index(adjustl(file_lines(i)%s(ic+7:)),"'") == 1 ) then

if (pass == 2) then
f_source%include_dependencies(n_include)%s = &
& split_n(file_lines(i)%s,n=2,delims="'"//'"',stat=stat)
if (stat /= 0) then
call file_parse_error(error,f_filename, &
'unable to find include file name',i, &
file_lines(i)%s)
return

n_include = n_include + 1

if (pass == 2) then
f_source%include_dependencies(n_include)%s = &
& split_n(file_lines(i)%s,n=2,delims="'"//'"',stat=stat)
if (stat /= 0) then
call file_parse_error(error,f_filename, &
'unable to find include file name',i, &
file_lines(i)%s)
return
end if
end if
end if

end if

! Extract name of module if is module
Expand Down
Loading