Skip to content

Commit d569a89

Browse files
authored
Merge pull request #225 from LKedward/refactor-sources
Refactor backend for static libraries
2 parents 277828d + 9f200c3 commit d569a89

File tree

6 files changed

+585
-307
lines changed

6 files changed

+585
-307
lines changed

fpm/src/fpm.f90

Lines changed: 9 additions & 8 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
@@ -225,16 +225,17 @@ subroutine build_model(model, settings, package, error)
225225
return
226226
end if
227227

228+
call targets_from_sources(model,model%sources)
229+
228230
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) )
231+
do i=1,size(model%targets)
232+
write(stderr,*) model%targets(i)%ptr%output_file
232233
enddo
233234
stop
234-
else
235-
call resolve_module_dependencies(model%sources,error)
236235
endif
237236

237+
call resolve_module_dependencies(model%targets,error)
238+
238239
end subroutine build_model
239240

240241

fpm/src/fpm_backend.f90

Lines changed: 65 additions & 89 deletions
Original file line numberDiff line numberDiff line change
@@ -4,10 +4,10 @@ module fpm_backend
44

55
use fpm_environment, only: run, get_os_type, OS_WINDOWS
66
use fpm_filesystem, only: basename, dirname, join_path, exists, mkdir
7-
use fpm_model, only: fpm_model_t, srcfile_t, FPM_UNIT_MODULE, &
7+
use fpm_model, only: fpm_model_t, srcfile_t, build_target_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, FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
1111

1212
use fpm_strings, only: split
1313

@@ -32,127 +32,103 @@ subroutine build_package(model)
3232
call mkdir(join_path(model%output_directory,model%package_name))
3333
end if
3434

35-
linking = ""
36-
do i=1,size(model%sources)
37-
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
42-
43-
call build_source(model,model%sources(i),linking)
44-
45-
end if
46-
47-
end do
48-
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
35+
if (model%targets(1)%ptr%target_type == FPM_TARGET_ARCHIVE) then
36+
linking = " "//model%targets(1)%ptr%output_file
37+
else
38+
linking = " "
5639
end if
5740

58-
do i=1,size(model%sources)
59-
60-
if (model%sources(i)%unit_type == FPM_UNIT_PROGRAM) then
61-
62-
base = basename(model%sources(i)%file_name,suffix=.false.)
63-
64-
if (model%sources(i)%unit_scope == FPM_SCOPE_TEST) then
65-
subdir = 'test'
66-
else
67-
subdir = 'app'
68-
end if
69-
70-
call run("gfortran -c " // model%sources(i)%file_name // ' '//model%fortran_compile_flags &
71-
// " -o " // join_path(model%output_directory,subdir,base) // ".o")
72-
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) )
76-
77-
end if
41+
linking = linking//" "//model%link_flags
7842

43+
do i=1,size(model%targets)
44+
45+
call build_target(model,model%targets(i)%ptr,linking)
46+
7947
end do
8048

8149
end subroutine build_package
8250

8351

8452

85-
recursive subroutine build_source(model,source_file,linking)
53+
recursive subroutine build_target(model,target,linking)
8654
! Compile Fortran source, called recursively on it dependents
8755
!
8856
type(fpm_model_t), intent(in) :: model
89-
type(srcfile_t), intent(inout) :: source_file
90-
character(:), allocatable, intent(inout) :: linking
57+
type(build_target_t), intent(inout) :: target
58+
character(:), allocatable, intent(in) :: linking
9159

92-
integer :: i
93-
character(:), allocatable :: object_file
60+
integer :: i, j
61+
type(build_target_t), pointer :: exe_obj
62+
character(:), allocatable :: objs
9463

95-
if (source_file%built) then
64+
if (target%built) then
9665
return
9766
end if
9867

99-
if (source_file%touched) then
100-
write(*,*) '(!) Circular dependency found with: ',source_file%file_name
68+
if (target%touched) then
69+
write(*,*) '(!) Circular dependency found with: ',target%output_file
10170
stop
10271
else
103-
source_file%touched = .true.
72+
target%touched = .true.
10473
end if
10574

106-
do i=1,size(source_file%file_dependencies)
75+
objs = " "
76+
77+
do i=1,size(target%dependencies)
10778

108-
if (associated(source_file%file_dependencies(i)%ptr)) then
109-
call build_source(model,source_file%file_dependencies(i)%ptr,linking)
79+
if (associated(target%dependencies(i)%ptr)) then
80+
call build_target(model,target%dependencies(i)%ptr,linking)
11081
end if
11182

112-
end do
83+
if (target%target_type == FPM_TARGET_ARCHIVE ) then
11384

114-
object_file = get_object_name(model,source_file%file_name)
115-
116-
if (.not.exists(dirname(object_file))) then
117-
call mkdir(dirname(object_file))
118-
end if
85+
! Construct object list for archive
86+
objs = objs//" "//target%dependencies(i)%ptr%output_file
11987

120-
call run("gfortran -c " // source_file%file_name // model%fortran_compile_flags &
121-
// " -o " // object_file)
122-
linking = linking // " " // object_file
88+
else if (target%target_type == FPM_TARGET_EXECUTABLE .and. &
89+
target%dependencies(i)%ptr%target_type == FPM_TARGET_OBJECT) then
12390

124-
source_file%built = .true.
91+
exe_obj => target%dependencies(i)%ptr
92+
93+
! Construct object list for executable
94+
objs = " "//exe_obj%output_file
95+
96+
! Include non-library object dependencies
97+
do j=1,size(exe_obj%dependencies)
12598

126-
end subroutine build_source
99+
if (allocated(exe_obj%dependencies(j)%ptr%source)) then
100+
if (exe_obj%dependencies(j)%ptr%source%unit_scope == exe_obj%source%unit_scope) then
101+
objs = objs//" "//exe_obj%dependencies(j)%ptr%output_file
102+
end if
103+
end if
127104

105+
end do
128106

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
107+
end if
138108

139-
integer :: i
140-
character(1) :: filesep
109+
end do
110+
111+
if (.not.exists(dirname(target%output_file))) then
112+
call mkdir(dirname(target%output_file))
113+
end if
141114

142-
select case(get_os_type())
143-
case (OS_WINDOWS)
144-
filesep = '\'
145-
case default
146-
filesep = '/'
147-
end select
115+
select case(target%target_type)
116+
117+
case (FPM_TARGET_OBJECT)
118+
call run("gfortran -c " // target%source%file_name // model%fortran_compile_flags &
119+
// " -o " // target%output_file)
148120

149-
! Exclude first directory level from path
150-
object_file = source_file_name(index(source_file_name,filesep)+1:)
121+
case (FPM_TARGET_EXECUTABLE)
122+
call run("gfortran " // objs // model%fortran_compile_flags &
123+
//linking// " -o " // target%output_file)
124+
125+
case (FPM_TARGET_ARCHIVE)
126+
call run("ar -rs " // target%output_file // objs)
127+
128+
end select
151129

152-
! Construct full target path
153-
object_file = join_path(model%output_directory, model%package_name, &
154-
object_file//'.o')
130+
target%built = .true.
155131

156-
end function get_object_name
132+
end subroutine build_target
157133

158134
end module fpm_backend

fpm/src/fpm_model.f90

Lines changed: 28 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,18 +51,34 @@ 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
6278
type(srcfile_t), allocatable :: sources(:)
63-
! Array of sources with module-dependencies resolved
79+
! Array of sources
80+
type(build_target_ptr), allocatable :: targets(:)
81+
! Array of targets with module-dependencies resolved
6482
character(:), allocatable :: fortran_compiler
6583
! Command line name to invoke fortran compiler
6684
character(:), allocatable :: fortran_compile_flags

0 commit comments

Comments
 (0)