Skip to content

Commit 8096ba7

Browse files
committed
Intermediate: separate out build targets from sources
A new module and type for build targets. List of build targets is generated from the list of sources.
1 parent 436573b commit 8096ba7

File tree

6 files changed

+549
-321
lines changed

6 files changed

+549
-321
lines changed

fpm/src/fpm.f90

Lines changed: 16 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -5,12 +5,12 @@ module fpm
55
fpm_run_settings, fpm_install_settings, fpm_test_settings
66
use fpm_environment, only: run
77
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename
8-
use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t, &
8+
use fpm_model, only: fpm_model_t, srcfile_t, build_target_t, &
99
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
1010
FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST
1111

12-
use fpm_sources, only: add_executable_sources, add_sources_from_dir, &
13-
resolve_module_dependencies
12+
use fpm_sources, only: add_executable_sources, add_sources_from_dir
13+
use fpm_targets, only: targets_from_sources, resolve_module_dependencies
1414
use fpm_manifest, only : get_package_data, default_executable, &
1515
default_library, package_t, default_test
1616
use fpm_error, only : error_t, fatal_error
@@ -150,6 +150,7 @@ subroutine build_model(model, settings, package, error)
150150
type(error_t), allocatable, intent(out) :: error
151151
integer :: i
152152

153+
type(srcfile_t), allocatable :: sources(:)
153154
type(string_t), allocatable :: package_list(:)
154155

155156
model%package_name = package%name
@@ -180,7 +181,7 @@ subroutine build_model(model, settings, package, error)
180181

181182
! Add sources from executable directories
182183
if (is_dir('app') .and. package%build_config%auto_executables) then
183-
call add_sources_from_dir(model%sources,'app', FPM_SCOPE_APP, &
184+
call add_sources_from_dir(sources,'app', FPM_SCOPE_APP, &
184185
with_executables=.true., error=error)
185186

186187
if (allocated(error)) then
@@ -189,7 +190,7 @@ subroutine build_model(model, settings, package, error)
189190

190191
end if
191192
if (is_dir('test') .and. package%build_config%auto_tests) then
192-
call add_sources_from_dir(model%sources,'test', FPM_SCOPE_TEST, &
193+
call add_sources_from_dir(sources,'test', FPM_SCOPE_TEST, &
193194
with_executables=.true., error=error)
194195

195196
if (allocated(error)) then
@@ -198,7 +199,7 @@ subroutine build_model(model, settings, package, error)
198199

199200
end if
200201
if (allocated(package%executable)) then
201-
call add_executable_sources(model%sources, package%executable, FPM_SCOPE_APP, &
202+
call add_executable_sources(sources, package%executable, FPM_SCOPE_APP, &
202203
auto_discover=package%build_config%auto_executables, &
203204
error=error)
204205

@@ -208,7 +209,7 @@ subroutine build_model(model, settings, package, error)
208209

209210
end if
210211
if (allocated(package%test)) then
211-
call add_executable_sources(model%sources, package%test, FPM_SCOPE_TEST, &
212+
call add_executable_sources(sources, package%test, FPM_SCOPE_TEST, &
212213
auto_discover=package%build_config%auto_tests, &
213214
error=error)
214215

@@ -219,20 +220,23 @@ subroutine build_model(model, settings, package, error)
219220
endif
220221

221222
! Add library sources, including local dependencies
222-
call add_libsources_from_package(model%sources,package_list,package, &
223+
call add_libsources_from_package(sources,package_list,package, &
223224
package_root='.',dev_depends=.true.,error=error)
224225
if (allocated(error)) then
225226
return
226227
end if
227228

228229
if(settings%list)then
229-
do i=1,size(model%sources)
230-
write(stderr,'(*(g0,1x))')'fpm::build<INFO>:file expected at',model%sources(i)%file_name, &
231-
& merge('exists ','does not exist',exists(model%sources(i)%file_name) )
230+
do i=1,size(sources)
231+
write(stderr,'(*(g0,1x))')'fpm::build<INFO>:file expected at',sources(i)%file_name, &
232+
& merge('exists ','does not exist',exists(sources(i)%file_name) )
232233
enddo
233234
stop
234235
else
235-
call resolve_module_dependencies(model%sources,error)
236+
237+
call targets_from_sources(model%targets,sources,model%package_name)
238+
239+
call resolve_module_dependencies(model%targets,error)
236240
endif
237241

238242
end subroutine build_model

fpm/src/fpm_backend.f90

Lines changed: 68 additions & 98 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ module fpm_backend
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, &
10-
FPM_SCOPE_TEST
10+
FPM_SCOPE_TEST, build_target_t
1111

1212
use fpm_strings, only: split
1313

@@ -22,137 +22,107 @@ module fpm_backend
2222
subroutine build_package(model)
2323
type(fpm_model_t), intent(inout) :: model
2424

25-
integer :: i
26-
character(:), allocatable :: base, linking, subdir
25+
! integer :: i
26+
! character(:), allocatable :: base, linking, subdir
2727

28-
if (.not.exists(model%output_directory)) then
29-
call mkdir(model%output_directory)
30-
end if
31-
if (.not.exists(join_path(model%output_directory,model%package_name))) then
32-
call mkdir(join_path(model%output_directory,model%package_name))
33-
end if
28+
! if (.not.exists(model%output_directory)) then
29+
! call mkdir(model%output_directory)
30+
! end if
31+
! if (.not.exists(join_path(model%output_directory,model%package_name))) then
32+
! call mkdir(join_path(model%output_directory,model%package_name))
33+
! end if
3434

35-
linking = ""
36-
do i=1,size(model%sources)
35+
! linking = ""
36+
! do i=1,size(model%targets)
3737

38-
if (model%sources(i)%unit_type == FPM_UNIT_MODULE .or. &
39-
model%sources(i)%unit_type == FPM_UNIT_SUBMODULE .or. &
40-
model%sources(i)%unit_type == FPM_UNIT_SUBPROGRAM .or. &
41-
model%sources(i)%unit_type == FPM_UNIT_CSOURCE) then
38+
! ! if (model%sources(i)%unit_type == FPM_UNIT_MODULE .or. &
39+
! ! model%sources(i)%unit_type == FPM_UNIT_SUBMODULE .or. &
40+
! ! model%sources(i)%unit_type == FPM_UNIT_SUBPROGRAM .or. &
41+
! ! model%sources(i)%unit_type == FPM_UNIT_CSOURCE) then
4242

43-
call build_source(model,model%sources(i),linking)
43+
! call build_source(model,model%sources(i),linking)
4444

45-
end if
45+
! ! end if
4646

47-
end do
47+
! end do
4848

49-
if (any([(model%sources(i)%unit_type == FPM_UNIT_PROGRAM,i=1,size(model%sources))])) then
50-
if (.not.exists(join_path(model%output_directory,'test'))) then
51-
call mkdir(join_path(model%output_directory,'test'))
52-
end if
53-
if (.not.exists(join_path(model%output_directory,'app'))) then
54-
call mkdir(join_path(model%output_directory,'app'))
55-
end if
56-
end if
49+
! if (any([(model%sources(i)%unit_type == FPM_UNIT_PROGRAM,i=1,size(model%sources))])) then
50+
! if (.not.exists(join_path(model%output_directory,'test'))) then
51+
! call mkdir(join_path(model%output_directory,'test'))
52+
! end if
53+
! if (.not.exists(join_path(model%output_directory,'app'))) then
54+
! call mkdir(join_path(model%output_directory,'app'))
55+
! end if
56+
! end if
5757

58-
do i=1,size(model%sources)
58+
! do i=1,size(model%sources)
5959

60-
if (model%sources(i)%unit_type == FPM_UNIT_PROGRAM) then
60+
! if (model%sources(i)%unit_type == FPM_UNIT_PROGRAM) then
6161

62-
base = basename(model%sources(i)%file_name,suffix=.false.)
62+
! base = basename(model%sources(i)%file_name,suffix=.false.)
6363

64-
if (model%sources(i)%unit_scope == FPM_SCOPE_TEST) then
65-
subdir = 'test'
66-
else
67-
subdir = 'app'
68-
end if
64+
! if (model%sources(i)%unit_scope == FPM_SCOPE_TEST) then
65+
! subdir = 'test'
66+
! else
67+
! subdir = 'app'
68+
! end if
6969

70-
call run("gfortran -c " // model%sources(i)%file_name // ' '//model%fortran_compile_flags &
71-
// " -o " // join_path(model%output_directory,subdir,base) // ".o")
70+
! call run("gfortran -c " // model%sources(i)%file_name // ' '//model%fortran_compile_flags &
71+
! // " -o " // join_path(model%output_directory,subdir,base) // ".o")
7272

73-
call run("gfortran " // join_path(model%output_directory, subdir, base) // ".o "// &
74-
linking //" " //model%link_flags // " -o " // &
75-
join_path(model%output_directory,subdir,model%sources(i)%exe_name) )
73+
! call run("gfortran " // join_path(model%output_directory, subdir, base) // ".o "// &
74+
! linking //" " //model%link_flags // " -o " // &
75+
! join_path(model%output_directory,subdir,model%sources(i)%exe_name) )
7676

77-
end if
77+
! end if
7878

79-
end do
79+
! end do
8080

8181
end subroutine build_package
8282

8383

8484

85-
recursive subroutine build_source(model,source_file,linking)
85+
recursive subroutine build_target(model,target,linking)
8686
! Compile Fortran source, called recursively on it dependents
8787
!
8888
type(fpm_model_t), intent(in) :: model
89-
type(srcfile_t), intent(inout) :: source_file
89+
type(build_target_t), intent(inout) :: target
9090
character(:), allocatable, intent(inout) :: linking
9191

92-
integer :: i
93-
character(:), allocatable :: object_file
92+
! integer :: i
93+
! character(:), allocatable :: object_file
9494

95-
if (source_file%built) then
96-
return
97-
end if
95+
! if (source_file%built) then
96+
! return
97+
! end if
9898

99-
if (source_file%touched) then
100-
write(*,*) '(!) Circular dependency found with: ',source_file%file_name
101-
stop
102-
else
103-
source_file%touched = .true.
104-
end if
99+
! if (source_file%touched) then
100+
! write(*,*) '(!) Circular dependency found with: ',source_file%file_name
101+
! stop
102+
! else
103+
! source_file%touched = .true.
104+
! end if
105105

106-
do i=1,size(source_file%file_dependencies)
106+
! do i=1,size(source_file%file_dependencies)
107107

108-
if (associated(source_file%file_dependencies(i)%ptr)) then
109-
call build_source(model,source_file%file_dependencies(i)%ptr,linking)
110-
end if
108+
! if (associated(source_file%file_dependencies(i)%ptr)) then
109+
! call build_source(model,source_file%file_dependencies(i)%ptr,linking)
110+
! end if
111111

112-
end do
112+
! end do
113113

114-
object_file = get_object_name(model,source_file%file_name)
114+
! 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
116+
! if (.not.exists(dirname(object_file))) then
117+
! call mkdir(dirname(object_file))
118+
! end if
119119

120-
call run("gfortran -c " // source_file%file_name // model%fortran_compile_flags &
121-
// " -o " // object_file)
122-
linking = linking // " " // object_file
120+
! call run("gfortran -c " // source_file%file_name // model%fortran_compile_flags &
121+
! // " -o " // object_file)
122+
! linking = linking // " " // object_file
123123

124-
source_file%built = .true.
124+
! source_file%built = .true.
125125

126-
end subroutine build_source
127-
128-
129-
function get_object_name(model,source_file_name) result(object_file)
130-
! Generate object target path from source name and model params
131-
!
132-
! src/test.f90 -> <output-dir>/<package-name>/test.o
133-
! src/subdir/test.f90 -> <output-dir>/<package-name>/subdir_test.o
134-
!
135-
type(fpm_model_t), intent(in) :: model
136-
character(*), intent(in) :: source_file_name
137-
character(:), allocatable :: object_file
138-
139-
integer :: i
140-
character(1) :: filesep
141-
142-
select case(get_os_type())
143-
case (OS_WINDOWS)
144-
filesep = '\'
145-
case default
146-
filesep = '/'
147-
end select
148-
149-
! Exclude first directory level from path
150-
object_file = source_file_name(index(source_file_name,filesep)+1:)
151-
152-
! Construct full target path
153-
object_file = join_path(model%output_directory, model%package_name, &
154-
object_file//'.o')
155-
156-
end function get_object_name
126+
end subroutine build_target
157127

158128
end module fpm_backend

fpm/src/fpm_model.f90

Lines changed: 26 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -4,12 +4,14 @@ module fpm_model
44
implicit none
55

66
private
7-
public :: srcfile_ptr, srcfile_t, fpm_model_t
7+
public :: fpm_model_t, srcfile_t, build_target_t, build_target_ptr
88

99
public :: FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
1010
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, &
1111
FPM_UNIT_CHEADER, FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
12-
FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST
12+
FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST, &
13+
FPM_TARGET_UNKNOWN, FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE, &
14+
FPM_TARGET_OBJECT
1315

1416
integer, parameter :: FPM_UNIT_UNKNOWN = -1
1517
integer, parameter :: FPM_UNIT_PROGRAM = 1
@@ -25,10 +27,10 @@ module fpm_model
2527
integer, parameter :: FPM_SCOPE_APP = 3
2628
integer, parameter :: FPM_SCOPE_TEST = 4
2729

28-
type srcfile_ptr
29-
! For constructing arrays of src_file pointers
30-
type(srcfile_t), pointer :: ptr => null()
31-
end type srcfile_ptr
30+
integer, parameter :: FPM_TARGET_UNKNOWN = -1
31+
integer, parameter :: FPM_TARGET_EXECUTABLE = 1
32+
integer, parameter :: FPM_TARGET_ARCHIVE = 2
33+
integer, parameter :: FPM_TARGET_OBJECT = 3
3234

3335
type srcfile_t
3436
! Type for encapsulating a source file
@@ -49,17 +51,31 @@ module fpm_model
4951
! Modules USEd by this source file (lowerstring)
5052
type(string_t), allocatable :: include_dependencies(:)
5153
! Files INCLUDEd by this source file
52-
type(srcfile_ptr), allocatable :: file_dependencies(:)
53-
! Resolved source file dependencies
54+
end type srcfile_t
55+
56+
type build_target_ptr
57+
! For constructing arrays of build_target_t pointers
58+
type(build_target_t), pointer :: ptr => null()
59+
end type build_target_ptr
60+
61+
type build_target_t
62+
character(:), allocatable :: output_file
63+
! File path of build target object relative to cwd
64+
type(srcfile_t), allocatable :: source
65+
! Primary source for this build target
66+
type(build_target_ptr), allocatable :: dependencies(:)
67+
! Resolved build dependencies
68+
integer :: target_type = FPM_TARGET_UNKNOWN
5469

5570
logical :: built = .false.
5671
logical :: touched = .false.
57-
end type srcfile_t
72+
73+
end type build_target_t
5874

5975
type :: fpm_model_t
6076
character(:), allocatable :: package_name
6177
! Name of package
62-
type(srcfile_t), allocatable :: sources(:)
78+
type(build_target_ptr), allocatable :: targets(:)
6379
! Array of sources with module-dependencies resolved
6480
character(:), allocatable :: fortran_compiler
6581
! Command line name to invoke fortran compiler

0 commit comments

Comments
 (0)