Skip to content

Commit ad9ebad

Browse files
authored
Merge pull request #193 from LKedward/local-depends
Local path and remote git dependencies
2 parents 49de89e + eebe0ff commit ad9ebad

File tree

9 files changed

+309
-89
lines changed

9 files changed

+309
-89
lines changed

ci/run_tests.bat

Lines changed: 25 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,7 @@ if errorlevel 1 exit 1
1515
build\gfortran_debug\app\fpm
1616
if errorlevel 1 exit 1
1717

18+
1819
cd ..\test\example_packages\hello_world
1920
if errorlevel 1 exit 1
2021

@@ -25,6 +26,30 @@ if errorlevel 1 exit 1
2526
if errorlevel 1 exit 1
2627

2728

29+
cd ..\hello_fpm
30+
if errorlevel 1 exit 1
31+
32+
..\..\..\fpm\build\gfortran_debug\app\fpm build
33+
if errorlevel 1 exit 1
34+
35+
.\build\gfortran_debug\app\hello_fpm
36+
if errorlevel 1 exit 1
37+
38+
39+
cd ..\circular_test
40+
if errorlevel 1 exit 1
41+
42+
..\..\..\fpm\build\gfortran_debug\app\fpm build
43+
if errorlevel 1 exit 1
44+
45+
46+
cd ..\circular_example
47+
if errorlevel 1 exit 1
48+
49+
..\..\..\fpm\build\gfortran_debug\app\fpm build
50+
if errorlevel 1 exit 1
51+
52+
2853
cd ..\hello_complex
2954
if errorlevel 1 exit 1
3055

ci/run_tests.sh

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,16 @@ cd ../test/example_packages/hello_world
1212
../../../fpm/build/gfortran_debug/app/fpm build
1313
./build/gfortran_debug/app/hello_world
1414

15+
cd ../hello_fpm
16+
../../../fpm/build/gfortran_debug/app/fpm build
17+
./build/gfortran_debug/app/hello_fpm
18+
19+
cd ../circular_test
20+
../../../fpm/build/gfortran_debug/app/fpm build
21+
22+
cd ../circular_example
23+
../../../fpm/build/gfortran_debug/app/fpm build
24+
1525
cd ../hello_complex
1626
../../../fpm/build/gfortran_debug/app/fpm build
1727
./build/gfortran_debug/app/say_Hello

fpm/src/fpm.f90

Lines changed: 132 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
module fpm
2-
3-
use fpm_strings, only: string_t, str_ends_with
2+
use fpm_strings, only: string_t, str_ends_with, operator(.in.)
43
use fpm_backend, only: build_package
54
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
65
fpm_run_settings, fpm_install_settings, fpm_test_settings
@@ -14,16 +13,134 @@ module fpm
1413
resolve_module_dependencies
1514
use fpm_manifest, only : get_package_data, default_executable, &
1615
default_library, package_t, default_test
17-
use fpm_error, only : error_t
16+
use fpm_error, only : error_t, fatal_error
1817
use fpm_manifest_test, only : test_t
19-
use,intrinsic :: iso_fortran_env, only : stderr=>error_unit
18+
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
19+
& stdout=>output_unit, &
20+
& stderr=>error_unit
21+
use fpm_manifest_dependency, only: dependency_t
2022
implicit none
2123
private
2224
public :: cmd_build, cmd_install, cmd_run, cmd_test
2325

2426
contains
2527

2628

29+
recursive subroutine add_libsources_from_package(sources,package_list,package, &
30+
package_root,dev_depends,error)
31+
! Discover library sources in a package, recursively including dependencies
32+
!
33+
type(srcfile_t), allocatable, intent(inout), target :: sources(:)
34+
type(string_t), allocatable, intent(inout) :: package_list(:)
35+
type(package_t), intent(in) :: package
36+
character(*), intent(in) :: package_root
37+
logical, intent(in) :: dev_depends
38+
type(error_t), allocatable, intent(out) :: error
39+
40+
! Add package library sources
41+
if (allocated(package%library)) then
42+
43+
call add_sources_from_dir(sources, join_path(package_root,package%library%source_dir), &
44+
FPM_SCOPE_LIB, error=error)
45+
46+
if (allocated(error)) then
47+
return
48+
end if
49+
50+
end if
51+
52+
! Add library sources from dependencies
53+
if (allocated(package%dependency)) then
54+
55+
call add_dependencies(package%dependency)
56+
57+
if (allocated(error)) then
58+
return
59+
end if
60+
61+
end if
62+
63+
! Add library sources from dev-dependencies
64+
if (dev_depends .and. allocated(package%dev_dependency)) then
65+
66+
call add_dependencies(package%dev_dependency)
67+
68+
if (allocated(error)) then
69+
return
70+
end if
71+
72+
end if
73+
74+
contains
75+
76+
subroutine add_dependencies(dependency_list)
77+
type(dependency_t), intent(in) :: dependency_list(:)
78+
79+
integer :: i
80+
type(string_t) :: dep_name
81+
type(package_t) :: dependency
82+
83+
character(:), allocatable :: dependency_path
84+
85+
do i=1,size(dependency_list)
86+
87+
if (dependency_list(i)%name .in. package_list) then
88+
cycle
89+
end if
90+
91+
if (allocated(dependency_list(i)%git)) then
92+
93+
dependency_path = join_path('build','dependencies',dependency_list(i)%name)
94+
95+
if (.not.exists(join_path(dependency_path,'fpm.toml'))) then
96+
call dependency_list(i)%git%checkout(dependency_path, error)
97+
if (allocated(error)) return
98+
end if
99+
100+
else if (allocated(dependency_list(i)%path)) then
101+
102+
dependency_path = join_path(package_root,dependency_list(i)%path)
103+
104+
end if
105+
106+
call get_package_data(dependency, &
107+
join_path(dependency_path,"fpm.toml"), error)
108+
109+
if (allocated(error)) then
110+
error%message = 'Error while parsing manifest for dependency package at:'//&
111+
new_line('a')//join_path(dependency_path,"fpm.toml")//&
112+
new_line('a')//error%message
113+
return
114+
end if
115+
116+
if (.not.allocated(dependency%library) .and. &
117+
exists(join_path(dependency_path,"src"))) then
118+
allocate(dependency%library)
119+
dependency%library%source_dir = "src"
120+
end if
121+
122+
123+
call add_libsources_from_package(sources,package_list,dependency, &
124+
package_root=dependency_path, &
125+
dev_depends=.false., error=error)
126+
127+
if (allocated(error)) then
128+
error%message = 'Error while processing sources for dependency package "'//&
129+
new_line('a')//dependency%name//'"'//&
130+
new_line('a')//error%message
131+
return
132+
end if
133+
134+
dep_name%s = dependency_list(i)%name
135+
package_list = [package_list, dep_name]
136+
137+
end do
138+
139+
end subroutine add_dependencies
140+
141+
end subroutine add_libsources_from_package
142+
143+
27144
subroutine build_model(model, settings, package, error)
28145
! Constructs a valid fpm model from command line settings and toml manifest
29146
!
@@ -33,8 +150,13 @@ subroutine build_model(model, settings, package, error)
33150
type(error_t), allocatable, intent(out) :: error
34151
integer :: i
35152

153+
type(string_t), allocatable :: package_list(:)
154+
36155
model%package_name = package%name
37156

157+
allocate(package_list(1))
158+
package_list(1)%s = package%name
159+
38160
! #TODO: Choose flags and output directory based on cli settings & manifest inputs
39161
model%fortran_compiler = 'gfortran'
40162

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

97219
endif
98220

99-
if (allocated(package%library)) then
100-
101-
call add_sources_from_dir(model%sources, package%library%source_dir, &
102-
FPM_SCOPE_LIB, error=error)
103-
104-
if (allocated(error)) then
105-
return
106-
endif
107-
221+
! Add library sources, including local dependencies
222+
call add_libsources_from_package(model%sources,package_list,package, &
223+
package_root='.',dev_depends=.true.,error=error)
224+
if (allocated(error)) then
225+
return
226+
end if
108227

109-
endif
110228
if(settings%list)then
111229
do i=1,size(model%sources)
112230
write(stderr,'(*(g0,1x))')'fpm::build<INFO>:file expected at',model%sources(i)%file_name, &

fpm/src/fpm/git.f90

Lines changed: 52 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
!> Implementation for interacting with git repositories.
22
module fpm_git
3+
use fpm_error, only: error_t, fatal_error
34
implicit none
45

56
public :: git_target_t
@@ -43,6 +44,9 @@ module fpm_git
4344

4445
contains
4546

47+
!> Fetch and checkout in local directory
48+
procedure :: checkout
49+
4650
!> Show information on instance
4751
procedure :: info
4852

@@ -124,6 +128,54 @@ function git_target_tag(url, tag) result(self)
124128
end function git_target_tag
125129

126130

131+
subroutine checkout(self,local_path, error)
132+
133+
!> Instance of the git target
134+
class(git_target_t), intent(in) :: self
135+
136+
!> Local path to checkout in
137+
character(*), intent(in) :: local_path
138+
139+
!> Error
140+
type(error_t), allocatable, intent(out) :: error
141+
142+
!> git object ref
143+
character(:), allocatable :: object
144+
145+
!> Stat for execute_command_line
146+
integer :: stat
147+
148+
if (allocated(self%object)) then
149+
object = self%object
150+
else
151+
object = 'HEAD'
152+
end if
153+
154+
call execute_command_line("git init "//local_path, exitstat=stat)
155+
156+
if (stat /= 0) then
157+
call fatal_error(error,'Error while initiating git repository for remote dependency')
158+
return
159+
end if
160+
161+
call execute_command_line("git -C "//local_path//" fetch "//self%url//&
162+
" "//object, exitstat=stat)
163+
164+
if (stat /= 0) then
165+
call fatal_error(error,'Error while fetching git repository for remote dependency')
166+
return
167+
end if
168+
169+
call execute_command_line("git -C "//local_path//" checkout -qf FETCH_HEAD", exitstat=stat)
170+
171+
if (stat /= 0) then
172+
call fatal_error(error,'Error while checking out git repository for remote dependency')
173+
return
174+
end if
175+
176+
end subroutine checkout
177+
178+
127179
!> Show information on git target
128180
subroutine info(self, unit, verbosity)
129181

fpm/src/fpm_backend.f90

Lines changed: 5 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@ module fpm_backend
33
! Implements the native fpm build backend
44

55
use fpm_environment, only: run, get_os_type, OS_WINDOWS
6-
use fpm_filesystem, only: basename, join_path, exists, mkdir
6+
use fpm_filesystem, only: basename, dirname, join_path, exists, mkdir
77
use fpm_model, only: fpm_model_t, srcfile_t, FPM_UNIT_MODULE, &
88
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, &
99
FPM_UNIT_CSOURCE, FPM_UNIT_PROGRAM, &
@@ -113,6 +113,10 @@ recursive subroutine build_source(model,source_file,linking)
113113

114114
object_file = get_object_name(model,source_file%file_name)
115115

116+
if (.not.exists(dirname(object_file))) then
117+
call mkdir(dirname(object_file))
118+
end if
119+
116120
call run("gfortran -c " // source_file%file_name // model%fortran_compile_flags &
117121
// " -o " // object_file)
118122
linking = linking // " " // object_file
@@ -145,13 +149,6 @@ function get_object_name(model,source_file_name) result(object_file)
145149
! Exclude first directory level from path
146150
object_file = source_file_name(index(source_file_name,filesep)+1:)
147151

148-
! Convert remaining directory separators to underscores
149-
i = index(object_file,filesep)
150-
do while(i > 0)
151-
object_file(i:i) = '_'
152-
i = index(object_file,filesep)
153-
end do
154-
155152
! Construct full target path
156153
object_file = join_path(model%output_directory, model%package_name, &
157154
object_file//'.o')

0 commit comments

Comments
 (0)