Skip to content

Commit 0a5c3f1

Browse files
authored
Merge pull request #322 from LKedward/refactor-model-sources
Group sources by package in the model
2 parents 0a86ff3 + f3072a1 commit 0a5c3f1

File tree

4 files changed

+156
-111
lines changed

4 files changed

+156
-111
lines changed

fpm/src/fpm.f90

Lines changed: 12 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,6 @@ subroutine build_model(model, settings, package, error)
3838
type(fpm_build_settings), intent(in) :: settings
3939
type(package_config_t), intent(in) :: package
4040
type(error_t), allocatable, intent(out) :: error
41-
type(string_t), allocatable :: package_list(:)
4241

4342
integer :: i
4443
type(package_config_t) :: dependency
@@ -61,10 +60,6 @@ subroutine build_model(model, settings, package, error)
6160
call model%deps%add(package, error)
6261
if (allocated(error)) return
6362

64-
allocate(package_list(1))
65-
package_list(1)%s = package%name
66-
67-
6863
if(settings%compiler.eq.'')then
6964
model%fortran_compiler = 'gfortran'
7065
else
@@ -77,9 +72,11 @@ subroutine build_model(model, settings, package, error)
7772

7873
model%link_flags = ''
7974

75+
allocate(model%packages(model%deps%ndep))
76+
8077
! Add sources from executable directories
8178
if (is_dir('app') .and. package%build%auto_executables) then
82-
call add_sources_from_dir(model%sources,'app', FPM_SCOPE_APP, &
79+
call add_sources_from_dir(model%packages(1)%sources,'app', FPM_SCOPE_APP, &
8380
with_executables=.true., error=error)
8481

8582
if (allocated(error)) then
@@ -88,7 +85,7 @@ subroutine build_model(model, settings, package, error)
8885

8986
end if
9087
if (is_dir('example') .and. package%build%auto_examples) then
91-
call add_sources_from_dir(model%sources,'example', FPM_SCOPE_EXAMPLE, &
88+
call add_sources_from_dir(model%packages(1)%sources,'example', FPM_SCOPE_EXAMPLE, &
9289
with_executables=.true., error=error)
9390

9491
if (allocated(error)) then
@@ -97,7 +94,7 @@ subroutine build_model(model, settings, package, error)
9794

9895
end if
9996
if (is_dir('test') .and. package%build%auto_tests) then
100-
call add_sources_from_dir(model%sources,'test', FPM_SCOPE_TEST, &
97+
call add_sources_from_dir(model%packages(1)%sources,'test', FPM_SCOPE_TEST, &
10198
with_executables=.true., error=error)
10299

103100
if (allocated(error)) then
@@ -106,7 +103,7 @@ subroutine build_model(model, settings, package, error)
106103

107104
end if
108105
if (allocated(package%executable)) then
109-
call add_executable_sources(model%sources, package%executable, FPM_SCOPE_APP, &
106+
call add_executable_sources(model%packages(1)%sources, package%executable, FPM_SCOPE_APP, &
110107
auto_discover=package%build%auto_executables, &
111108
error=error)
112109

@@ -116,7 +113,7 @@ subroutine build_model(model, settings, package, error)
116113

117114
end if
118115
if (allocated(package%example)) then
119-
call add_executable_sources(model%sources, package%example, FPM_SCOPE_EXAMPLE, &
116+
call add_executable_sources(model%packages(1)%sources, package%example, FPM_SCOPE_EXAMPLE, &
120117
auto_discover=package%build%auto_examples, &
121118
error=error)
122119

@@ -126,7 +123,7 @@ subroutine build_model(model, settings, package, error)
126123

127124
end if
128125
if (allocated(package%test)) then
129-
call add_executable_sources(model%sources, package%test, FPM_SCOPE_TEST, &
126+
call add_executable_sources(model%packages(1)%sources, package%test, FPM_SCOPE_TEST, &
130127
auto_discover=package%build%auto_tests, &
131128
error=error)
132129

@@ -144,9 +141,11 @@ subroutine build_model(model, settings, package, error)
144141
apply_defaults=.true.)
145142
if (allocated(error)) exit
146143

144+
model%packages(i)%name = dependency%name
145+
147146
if (allocated(dependency%library)) then
148147
lib_dir = join_path(dep%proj_dir, dependency%library%source_dir)
149-
call add_sources_from_dir(model%sources, lib_dir, FPM_SCOPE_LIB, &
148+
call add_sources_from_dir(model%packages(i)%sources, lib_dir, FPM_SCOPE_LIB, &
150149
error=error)
151150
if (allocated(error)) exit
152151
end if
@@ -158,7 +157,7 @@ subroutine build_model(model, settings, package, error)
158157
end do
159158
if (allocated(error)) return
160159

161-
call targets_from_sources(model,model%sources)
160+
call targets_from_sources(model)
162161

163162
do i = 1, size(model%link_libraries)
164163
model%link_flags = model%link_flags // " -l" // model%link_libraries(i)%s

fpm/src/fpm_model.f90

Lines changed: 46 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -112,6 +112,18 @@ module fpm_model
112112
end type srcfile_t
113113

114114

115+
!> Type for describing a single package
116+
type package_t
117+
118+
!> Name of package
119+
character(:), allocatable :: name
120+
121+
!> Array of sources
122+
type(srcfile_t), allocatable :: sources(:)
123+
124+
end type package_t
125+
126+
115127
!> Wrapper type for constructing arrays of `[[build_target_t]]` pointers
116128
type build_target_ptr
117129

@@ -159,15 +171,15 @@ module fpm_model
159171
end type build_target_t
160172

161173

162-
!> Type describing everything required to build a package
163-
!> and its dependencies.
174+
!> Type describing everything required to build
175+
!> the root package and its dependencies.
164176
type :: fpm_model_t
165177

166-
!> Name of package
178+
!> Name of root package
167179
character(:), allocatable :: package_name
168180

169-
!> Array of sources
170-
type(srcfile_t), allocatable :: sources(:)
181+
!> Array of packages (including the root package)
182+
type(package_t), allocatable :: packages(:)
171183

172184
!> Array of targets with module-dependencies resolved
173185
type(build_target_ptr), allocatable :: targets(:)
@@ -268,7 +280,7 @@ function info_build_target(t) result(s)
268280
end if
269281
!end type build_target_t
270282
s = s // ")"
271-
end function
283+
end function info_build_target
272284

273285
function info_build_target_short(t) result(s)
274286
! Prints a shortened representation of build_target_t
@@ -278,7 +290,26 @@ function info_build_target_short(t) result(s)
278290
s = "build_target_t("
279291
s = s // 'output_file="' // t%output_file // '"'
280292
s = s // ", ...)"
281-
end function
293+
end function info_build_target_short
294+
295+
function info_package(p) result(s)
296+
! Returns representation of package_t
297+
type(package_t), intent(in) :: p
298+
character(:), allocatable :: s
299+
300+
integer :: i
301+
302+
s = s // 'package_t('
303+
s = s // 'name="' // p%name //'"'
304+
s = s // ', sources=['
305+
do i = 1, size(p%sources)
306+
s = s // info_srcfile(p%sources(i))
307+
if (i < size(p%sources)) s = s // ", "
308+
end do
309+
s = s // "]"
310+
s = s // ")"
311+
312+
end function info_package
282313

283314
function info_srcfile(source) result(s)
284315
type(srcfile_t), intent(in) :: source
@@ -360,7 +391,7 @@ function info_srcfile(source) result(s)
360391
s = s // ", digest=" // str(source%digest)
361392
!end type srcfile_t
362393
s = s // ")"
363-
end function
394+
end function info_srcfile
364395

365396
function info_srcfile_short(source) result(s)
366397
! Prints a shortened version of srcfile_t
@@ -370,7 +401,7 @@ function info_srcfile_short(source) result(s)
370401
s = "srcfile_t("
371402
s = s // 'file_name="' // source%file_name // '"'
372403
s = s // ", ...)"
373-
end function
404+
end function info_srcfile_short
374405

375406
function info_model(model) result(s)
376407
type(fpm_model_t), intent(in) :: model
@@ -381,10 +412,10 @@ function info_model(model) result(s)
381412
! character(:), allocatable :: package_name
382413
s = s // 'package_name="' // model%package_name // '"'
383414
! type(srcfile_t), allocatable :: sources(:)
384-
s = s // ", sources=["
385-
do i = 1, size(model%sources)
386-
s = s // info_srcfile(model%sources(i))
387-
if (i < size(model%sources)) s = s // ", "
415+
s = s // ", packages=["
416+
do i = 1, size(model%packages)
417+
s = s // info_package(model%packages(i))
418+
if (i < size(model%packages)) s = s // ", "
388419
end do
389420
s = s // "]"
390421
! type(build_target_ptr), allocatable :: targets(:)
@@ -417,12 +448,12 @@ function info_model(model) result(s)
417448
s = s // ", deps=dependency_tree_t(...)"
418449
!end type fpm_model_t
419450
s = s // ")"
420-
end function
451+
end function info_model
421452

422453
subroutine show_model(model)
423454
! Prints a human readable representation of the Model
424455
type(fpm_model_t), intent(in) :: model
425456
print *, info_model(model)
426-
end subroutine
457+
end subroutine show_model
427458

428459
end module fpm_model

fpm/src/fpm_targets.f90

Lines changed: 49 additions & 42 deletions
Original file line numberDiff line numberDiff line change
@@ -53,15 +53,12 @@ module fpm_targets
5353
!>
5454
!> @note Inter-object dependencies based on modules used and provided are generated separately
5555
!> in `[[resolve_module_dependencies]]` after all targets have been enumerated.
56-
subroutine targets_from_sources(model,sources)
56+
subroutine targets_from_sources(model)
5757

5858
!> The package model within which to construct the target list
5959
type(fpm_model_t), intent(inout), target :: model
6060

61-
!> The list of sources from which to construct the target list
62-
type(srcfile_t), intent(in) :: sources(:)
63-
64-
integer :: i
61+
integer :: i, j
6562
character(:), allocatable :: xsuffix, exe_dir
6663
type(build_target_t), pointer :: dep
6764
logical :: with_lib
@@ -72,61 +69,71 @@ subroutine targets_from_sources(model,sources)
7269
xsuffix = ''
7370
end if
7471

75-
with_lib = any([(sources(i)%unit_scope == FPM_SCOPE_LIB,i=1,size(sources))])
72+
with_lib = any([((model%packages(j)%sources(i)%unit_scope == FPM_SCOPE_LIB, &
73+
i=1,size(model%packages(j)%sources)), &
74+
j=1,size(model%packages))])
7675

7776
if (with_lib) call add_target(model%targets,type = FPM_TARGET_ARCHIVE,&
7877
output_file = join_path(model%output_directory,&
7978
model%package_name,'lib'//model%package_name//'.a'))
8079

81-
do i=1,size(sources)
80+
do j=1,size(model%packages)
8281

83-
select case (sources(i)%unit_type)
84-
case (FPM_UNIT_MODULE,FPM_UNIT_SUBMODULE,FPM_UNIT_SUBPROGRAM,FPM_UNIT_CSOURCE)
82+
associate(sources=>model%packages(j)%sources)
8583

86-
call add_target(model%targets,source = sources(i), &
87-
type = FPM_TARGET_OBJECT,&
88-
output_file = get_object_name(sources(i)))
89-
90-
if (with_lib .and. sources(i)%unit_scope == FPM_SCOPE_LIB) then
91-
! Archive depends on object
92-
call add_dependency(model%targets(1)%ptr, model%targets(size(model%targets))%ptr)
93-
end if
84+
do i=1,size(sources)
85+
86+
select case (sources(i)%unit_type)
87+
case (FPM_UNIT_MODULE,FPM_UNIT_SUBMODULE,FPM_UNIT_SUBPROGRAM,FPM_UNIT_CSOURCE)
88+
89+
call add_target(model%targets,source = sources(i), &
90+
type = FPM_TARGET_OBJECT,&
91+
output_file = get_object_name(sources(i)))
92+
93+
if (with_lib .and. sources(i)%unit_scope == FPM_SCOPE_LIB) then
94+
! Archive depends on object
95+
call add_dependency(model%targets(1)%ptr, model%targets(size(model%targets))%ptr)
96+
end if
9497

95-
case (FPM_UNIT_PROGRAM)
98+
case (FPM_UNIT_PROGRAM)
9699

97-
call add_target(model%targets,type = FPM_TARGET_OBJECT,&
98-
output_file = get_object_name(sources(i)), &
99-
source = sources(i) &
100-
)
101-
102-
if (sources(i)%unit_scope == FPM_SCOPE_APP) then
100+
call add_target(model%targets,type = FPM_TARGET_OBJECT,&
101+
output_file = get_object_name(sources(i)), &
102+
source = sources(i) &
103+
)
104+
105+
if (sources(i)%unit_scope == FPM_SCOPE_APP) then
103106

104-
exe_dir = 'app'
107+
exe_dir = 'app'
105108

106-
else if (sources(i)%unit_scope == FPM_SCOPE_EXAMPLE) then
109+
else if (sources(i)%unit_scope == FPM_SCOPE_EXAMPLE) then
107110

108-
exe_dir = 'example'
111+
exe_dir = 'example'
109112

110-
else
113+
else
111114

112-
exe_dir = 'test'
115+
exe_dir = 'test'
113116

114-
end if
117+
end if
115118

116-
call add_target(model%targets,type = FPM_TARGET_EXECUTABLE,&
117-
link_libraries = sources(i)%link_libraries, &
118-
output_file = join_path(model%output_directory,exe_dir, &
119-
sources(i)%exe_name//xsuffix))
119+
call add_target(model%targets,type = FPM_TARGET_EXECUTABLE,&
120+
link_libraries = sources(i)%link_libraries, &
121+
output_file = join_path(model%output_directory,exe_dir, &
122+
sources(i)%exe_name//xsuffix))
120123

121-
! Executable depends on object
122-
call add_dependency(model%targets(size(model%targets))%ptr, model%targets(size(model%targets)-1)%ptr)
124+
! Executable depends on object
125+
call add_dependency(model%targets(size(model%targets))%ptr, model%targets(size(model%targets)-1)%ptr)
123126

124-
if (with_lib) then
125-
! Executable depends on library
126-
call add_dependency(model%targets(size(model%targets))%ptr, model%targets(1)%ptr)
127-
end if
128-
129-
end select
127+
if (with_lib) then
128+
! Executable depends on library
129+
call add_dependency(model%targets(size(model%targets))%ptr, model%targets(1)%ptr)
130+
end if
131+
132+
end select
133+
134+
end do
135+
136+
end associate
130137

131138
end do
132139

0 commit comments

Comments
 (0)