Skip to content
Merged
Show file tree
Hide file tree
Changes from all 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
25 changes: 25 additions & 0 deletions ci/run_tests.bat
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ if errorlevel 1 exit 1
build\gfortran_debug\app\fpm
if errorlevel 1 exit 1


cd ..\test\example_packages\hello_world
if errorlevel 1 exit 1

Expand All @@ -25,6 +26,30 @@ if errorlevel 1 exit 1
if errorlevel 1 exit 1


cd ..\hello_fpm
if errorlevel 1 exit 1

..\..\..\fpm\build\gfortran_debug\app\fpm build
if errorlevel 1 exit 1

.\build\gfortran_debug\app\hello_fpm
if errorlevel 1 exit 1


cd ..\circular_test
if errorlevel 1 exit 1

..\..\..\fpm\build\gfortran_debug\app\fpm build
if errorlevel 1 exit 1


cd ..\circular_example
if errorlevel 1 exit 1

..\..\..\fpm\build\gfortran_debug\app\fpm build
if errorlevel 1 exit 1


cd ..\hello_complex
if errorlevel 1 exit 1

Expand Down
10 changes: 10 additions & 0 deletions ci/run_tests.sh
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,16 @@ cd ../test/example_packages/hello_world
../../../fpm/build/gfortran_debug/app/fpm build
./build/gfortran_debug/app/hello_world

cd ../hello_fpm
../../../fpm/build/gfortran_debug/app/fpm build
./build/gfortran_debug/app/hello_fpm

cd ../circular_test
../../../fpm/build/gfortran_debug/app/fpm build

cd ../circular_example
../../../fpm/build/gfortran_debug/app/fpm build

cd ../hello_complex
../../../fpm/build/gfortran_debug/app/fpm build
./build/gfortran_debug/app/say_Hello
Expand Down
146 changes: 132 additions & 14 deletions fpm/src/fpm.f90
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
module fpm

use fpm_strings, only: string_t, str_ends_with
use fpm_strings, only: string_t, str_ends_with, operator(.in.)
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
Expand All @@ -14,16 +13,134 @@ module fpm
resolve_module_dependencies
use fpm_manifest, only : get_package_data, default_executable, &
default_library, package_t, default_test
use fpm_error, only : error_t
use fpm_error, only : error_t, fatal_error
use fpm_manifest_test, only : test_t
use,intrinsic :: iso_fortran_env, only : stderr=>error_unit
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
& stdout=>output_unit, &
& stderr=>error_unit
use fpm_manifest_dependency, only: dependency_t
implicit none
private
public :: cmd_build, cmd_install, cmd_run, cmd_test

contains


recursive subroutine add_libsources_from_package(sources,package_list,package, &
package_root,dev_depends,error)
! Discover library sources in a package, recursively including dependencies
!
type(srcfile_t), allocatable, intent(inout), target :: sources(:)
type(string_t), allocatable, intent(inout) :: package_list(:)
type(package_t), intent(in) :: package
character(*), intent(in) :: package_root
logical, intent(in) :: dev_depends
type(error_t), allocatable, intent(out) :: error

! Add package library sources
if (allocated(package%library)) then

call add_sources_from_dir(sources, join_path(package_root,package%library%source_dir), &
FPM_SCOPE_LIB, error=error)

if (allocated(error)) then
return
end if

end if

! Add library sources from dependencies
if (allocated(package%dependency)) then

call add_dependencies(package%dependency)

if (allocated(error)) then
return
end if

end if

! Add library sources from dev-dependencies
if (dev_depends .and. allocated(package%dev_dependency)) then

call add_dependencies(package%dev_dependency)

if (allocated(error)) then
return
end if

end if

contains

subroutine add_dependencies(dependency_list)
type(dependency_t), intent(in) :: 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
cycle
end if

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

dependency_path = join_path('build','dependencies',dependency_list(i)%name)

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

else if (allocated(dependency_list(i)%path)) then

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

end if

call get_package_data(dependency, &
join_path(dependency_path,"fpm.toml"), error)

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

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=.false., 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_dependencies

end subroutine add_libsources_from_package


subroutine build_model(model, settings, package, error)
! Constructs a valid fpm model from command line settings and toml manifest
!
Expand All @@ -33,8 +150,13 @@ subroutine build_model(model, settings, package, error)
type(error_t), allocatable, intent(out) :: error
integer :: i

type(string_t), allocatable :: package_list(:)

model%package_name = package%name

allocate(package_list(1))
package_list(1)%s = package%name

! #TODO: Choose flags and output directory based on cli settings & manifest inputs
model%fortran_compiler = 'gfortran'

Expand Down Expand Up @@ -96,17 +218,13 @@ subroutine build_model(model, settings, package, error)

endif

if (allocated(package%library)) then

call add_sources_from_dir(model%sources, package%library%source_dir, &
FPM_SCOPE_LIB, error=error)

if (allocated(error)) then
return
endif

! Add library sources, including local dependencies
call add_libsources_from_package(model%sources,package_list,package, &
package_root='.',dev_depends=.true.,error=error)
if (allocated(error)) then
return
end if

endif
if(settings%list)then
do i=1,size(model%sources)
write(stderr,'(*(g0,1x))')'fpm::build<INFO>:file expected at',model%sources(i)%file_name, &
Expand Down
52 changes: 52 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,54 @@ 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

!> git object ref
character(:), allocatable :: object

!> Stat for execute_command_line
integer :: stat

if (allocated(self%object)) then
object = self%object
else
object = 'HEAD'
end if

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//&
" "//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
13 changes: 5 additions & 8 deletions fpm/src/fpm_backend.f90
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ module fpm_backend
! Implements the native fpm build backend

use fpm_environment, only: run, get_os_type, OS_WINDOWS
use fpm_filesystem, only: basename, join_path, exists, mkdir
use fpm_filesystem, only: basename, dirname, 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, &
Expand Down Expand Up @@ -113,6 +113,10 @@ recursive subroutine build_source(model,source_file,linking)

object_file = get_object_name(model,source_file%file_name)

if (.not.exists(dirname(object_file))) then
call mkdir(dirname(object_file))
end if

call run("gfortran -c " // source_file%file_name // model%fortran_compile_flags &
// " -o " // object_file)
linking = linking // " " // object_file
Expand Down Expand Up @@ -145,13 +149,6 @@ function get_object_name(model,source_file_name) result(object_file)
! Exclude first directory level from path
object_file = source_file_name(index(source_file_name,filesep)+1:)

! Convert remaining directory separators to underscores
i = index(object_file,filesep)
do while(i > 0)
object_file(i:i) = '_'
i = index(object_file,filesep)
end do

! Construct full target path
object_file = join_path(model%output_directory, model%package_name, &
object_file//'.o')
Expand Down
Loading