1
1
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 .)
4
3
use fpm_backend, only: build_package
5
4
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
6
5
fpm_run_settings, fpm_install_settings, fpm_test_settings
@@ -14,16 +13,134 @@ module fpm
14
13
resolve_module_dependencies
15
14
use fpm_manifest, only : get_package_data, default_executable, &
16
15
default_library, package_t, default_test
17
- use fpm_error, only : error_t
16
+ use fpm_error, only : error_t, fatal_error
18
17
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
20
22
implicit none
21
23
private
22
24
public :: cmd_build, cmd_install, cmd_run, cmd_test
23
25
24
26
contains
25
27
26
28
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
+
27
144
subroutine build_model (model , settings , package , error )
28
145
! Constructs a valid fpm model from command line settings and toml manifest
29
146
!
@@ -33,8 +150,13 @@ subroutine build_model(model, settings, package, error)
33
150
type (error_t), allocatable , intent (out ) :: error
34
151
integer :: i
35
152
153
+ type (string_t), allocatable :: package_list(:)
154
+
36
155
model% package_name = package% name
37
156
157
+ allocate (package_list(1 ))
158
+ package_list(1 )% s = package% name
159
+
38
160
! #TODO: Choose flags and output directory based on cli settings & manifest inputs
39
161
model% fortran_compiler = ' gfortran'
40
162
@@ -96,17 +218,13 @@ subroutine build_model(model, settings, package, error)
96
218
97
219
endif
98
220
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
108
227
109
- endif
110
228
if (settings% list)then
111
229
do i= 1 ,size (model% sources)
112
230
write (stderr,' (*(g0,1x))' )' fpm::build<INFO>:file expected at' ,model% sources(i)% file_name, &
0 commit comments