Skip to content

Commit 11bebfc

Browse files
committed
Get backend working with new model targets structure
1 parent 8096ba7 commit 11bebfc

File tree

4 files changed

+206
-189
lines changed

4 files changed

+206
-189
lines changed

fpm/src/fpm.f90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -170,12 +170,12 @@ subroutine build_model(model, settings, package, error)
170170
& -fmax-errors=1 &
171171
& -ffast-math &
172172
& -funroll-loops ' // &
173-
& '-J'//join_path(model%output_directory,model%package_name)
173+
& '-J'//join_path(model%output_directory,'lib')
174174
else
175175
model%output_directory = 'build/gfortran_debug'
176176
model%fortran_compile_flags = ' -Wall -Wextra -Wimplicit-interface -fPIC -fmax-errors=1 -g '// &
177177
'-fbounds-check -fcheck-array-temporaries -fbacktrace '// &
178-
'-J'//join_path(model%output_directory,model%package_name)
178+
'-J'//join_path(model%output_directory,'lib')
179179
endif
180180
model%link_flags = ''
181181

@@ -234,7 +234,7 @@ subroutine build_model(model, settings, package, error)
234234
stop
235235
else
236236

237-
call targets_from_sources(model%targets,sources,model%package_name)
237+
call targets_from_sources(model,sources)
238238

239239
call resolve_module_dependencies(model%targets,error)
240240
endif

fpm/src/fpm_backend.f90

Lines changed: 66 additions & 77 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, build_target_t
10+
FPM_SCOPE_TEST, FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
1111

1212
use fpm_strings, only: split
1313

@@ -22,61 +22,28 @@ 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
3431

35-
! linking = ""
36-
! do i=1,size(model%targets)
32+
if (.not.exists(join_path(model%output_directory,'lib'))) then
33+
call mkdir(join_path(model%output_directory,'lib'))
34+
end if
3735

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)
36+
if (model%targets(1)%ptr%target_type == FPM_TARGET_ARCHIVE) then
37+
linking = ' -l'//model%package_name//" -L"//join_path(model%output_directory,'lib')
38+
else
39+
linking = " "
40+
end if
4441

45-
! ! end if
42+
do i=1,size(model%targets)
43+
44+
call build_target(model,model%targets(i)%ptr,linking)
4645

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
56-
! end if
57-
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
78-
79-
! end do
46+
end do
8047

8148
end subroutine build_package
8249

@@ -87,41 +54,63 @@ recursive subroutine build_target(model,target,linking)
8754
!
8855
type(fpm_model_t), intent(in) :: model
8956
type(build_target_t), intent(inout) :: target
90-
character(:), allocatable, intent(inout) :: linking
57+
character(:), allocatable, intent(in) :: linking
58+
59+
integer :: i
60+
character(:), allocatable :: objs
61+
62+
if (target%built) then
63+
return
64+
end if
65+
66+
if (target%touched) then
67+
write(*,*) '(!) Circular dependency found with: ',target%output_file
68+
stop
69+
else
70+
target%touched = .true.
71+
end if
72+
73+
objs = " "
9174

92-
! integer :: i
93-
! character(:), allocatable :: object_file
75+
do i=1,size(target%dependencies)
9476

95-
! if (source_file%built) then
96-
! return
97-
! end if
77+
if (associated(target%dependencies(i)%ptr)) then
78+
call build_target(model,target%dependencies(i)%ptr,linking)
79+
end if
9880

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
81+
if (target%target_type == FPM_TARGET_ARCHIVE ) then
10582

106-
! do i=1,size(source_file%file_dependencies)
83+
objs = objs//" "//target%dependencies(i)%ptr%output_file
10784

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
85+
else if (target%target_type == FPM_TARGET_EXECUTABLE .and. &
86+
target%dependencies(i)%ptr%target_type == FPM_TARGET_OBJECT) then
11187

112-
! end do
88+
objs = " "//target%dependencies(i)%ptr%output_file
11389

114-
! object_file = get_object_name(model,source_file%file_name)
90+
end if
91+
92+
end do
11593

116-
! if (.not.exists(dirname(object_file))) then
117-
! call mkdir(dirname(object_file))
118-
! end if
94+
if (.not.exists(dirname(target%output_file))) then
95+
call mkdir(dirname(target%output_file))
96+
end if
97+
98+
select case(target%target_type)
99+
100+
case (FPM_TARGET_OBJECT)
101+
call run("gfortran -c " // target%source%file_name // model%fortran_compile_flags &
102+
// " -o " // target%output_file)
103+
104+
case (FPM_TARGET_EXECUTABLE)
105+
call run("gfortran " // objs // model%fortran_compile_flags &
106+
//linking// " -o " // target%output_file)
107+
108+
case (FPM_TARGET_ARCHIVE)
109+
call run("ar -rs " // target%output_file // objs)
119110

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

124-
! source_file%built = .true.
113+
target%built = .true.
125114

126115
end subroutine build_target
127116

fpm/src/fpm_targets.f90

Lines changed: 66 additions & 54 deletions
Original file line numberDiff line numberDiff line change
@@ -1,68 +1,113 @@
11
module fpm_targets
22
use fpm_error, only: error_t, fatal_error
3-
use fpm_model!, only: srcfile_t, build_target_t, FPM_UNIT_PROGRAM, &
4-
! FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE, FPM_TARGET_OBJECT
3+
use fpm_model
54
use fpm_environment, only: get_os_type, OS_WINDOWS
6-
use fpm_filesystem, only: dirname, join_path
5+
use fpm_filesystem, only: dirname, join_path, canon_path
76
use fpm_strings, only: operator(.in.)
87
implicit none
98

109
contains
1110

12-
subroutine targets_from_sources(targets,sources,package_name)
13-
type(build_target_ptr), allocatable, intent(out), target :: targets(:)
11+
subroutine targets_from_sources(model,sources)
12+
type(fpm_model_t), intent(inout), target :: model
1413
type(srcfile_t), intent(in) :: sources(:)
15-
character(*), intent(in) :: package_name
1614

1715
integer :: i
1816
type(build_target_t), pointer :: dep
1917
logical :: with_lib
2018

2119
with_lib = any([(sources(i)%unit_scope == FPM_SCOPE_LIB,i=1,size(sources))])
2220

23-
if (with_lib) call add_target(targets,type = FPM_TARGET_ARCHIVE,&
24-
output_file = package_name//'.a')
21+
if (with_lib) call add_target(model%targets,type = FPM_TARGET_ARCHIVE,&
22+
output_file = join_path(model%output_directory,&
23+
'lib','lib'//model%package_name//'.a'))
2524

2625
do i=1,size(sources)
2726

2827
select case (sources(i)%unit_type)
2928
case (FPM_UNIT_MODULE,FPM_UNIT_SUBMODULE,FPM_UNIT_SUBPROGRAM,FPM_UNIT_CSOURCE)
3029

31-
call add_target(targets,source = sources(i), &
30+
call add_target(model%targets,source = sources(i), &
3231
type = FPM_TARGET_OBJECT,&
33-
output_file = get_object_name(sources(i)%file_name))
32+
output_file = get_object_name(sources(i)))
3433

3534
if (with_lib .and. sources(i)%unit_scope == FPM_SCOPE_LIB) then
3635
! Archive depends on object
37-
call add_dependency(targets(1)%ptr, targets(size(targets))%ptr)
36+
call add_dependency(model%targets(1)%ptr, model%targets(size(model%targets))%ptr)
3837
end if
3938

4039
case (FPM_UNIT_PROGRAM)
4140

42-
call add_target(targets,type = FPM_TARGET_OBJECT,&
43-
output_file = get_object_name(sources(i)%file_name), &
41+
call add_target(model%targets,type = FPM_TARGET_OBJECT,&
42+
output_file = get_object_name(sources(i)), &
4443
source = sources(i) &
4544
)
46-
47-
call add_target(targets,type = FPM_TARGET_EXECUTABLE,&
48-
output_file = join_path('app',sources(i)%exe_name))
49-
45+
46+
if (sources(i)%unit_scope == FPM_SCOPE_APP) then
47+
call add_target(model%targets,type = FPM_TARGET_EXECUTABLE,&
48+
output_file = join_path(model%output_directory,'app',sources(i)%exe_name))
49+
else
50+
call add_target(model%targets,type = FPM_TARGET_EXECUTABLE,&
51+
output_file = join_path(model%output_directory,'test',sources(i)%exe_name))
52+
53+
end if
5054

5155
! Executable depends on object
52-
call add_dependency(targets(size(targets))%ptr, targets(size(targets)-1)%ptr)
56+
call add_dependency(model%targets(size(model%targets))%ptr, model%targets(size(model%targets)-1)%ptr)
5357

5458
if (with_lib) then
5559
! Executable depends on library
56-
call add_dependency(targets(size(targets))%ptr, targets(1)%ptr)
60+
call add_dependency(model%targets(size(model%targets))%ptr, model%targets(1)%ptr)
5761
end if
5862

5963
end select
6064

6165
end do
6266

67+
contains
68+
69+
function get_object_name(source) result(object_file)
70+
! Generate object target path from source name and model params
71+
!
72+
!
73+
type(srcfile_t), intent(in) :: source
74+
character(:), allocatable :: object_file
75+
76+
integer :: i
77+
character(1), parameter :: filesep = '/'
78+
character(:), allocatable :: dir
79+
80+
object_file = canon_path(source%file_name)
81+
82+
! Ignore first directory level
83+
object_file = object_file(index(object_file,filesep)+1:)
84+
85+
! Convert any remaining directory separators to underscores
86+
i = index(object_file,filesep)
87+
do while(i > 0)
88+
object_file(i:i) = '_'
89+
i = index(object_file,filesep)
90+
end do
91+
92+
select case(source%unit_scope)
93+
94+
case (FPM_SCOPE_APP)
95+
object_file = join_path(model%output_directory,'app',object_file)//'.o'
96+
97+
case (FPM_SCOPE_TEST)
98+
object_file = join_path(model%output_directory,'test',object_file)//'.o'
99+
100+
case default
101+
object_file = join_path(model%output_directory,'lib',object_file)//'.o'
102+
103+
end select
104+
105+
end function get_object_name
106+
63107
end subroutine targets_from_sources
64108

65109

110+
!> Add new target to target list
66111
subroutine add_target(targets,type,output_file,source)
67112
type(build_target_ptr), allocatable, intent(inout) :: targets(:)
68113
integer, intent(in) :: type
@@ -84,49 +129,16 @@ subroutine add_target(targets,type,output_file,source)
84129
end subroutine add_target
85130

86131

132+
!> Add pointer to dependeny in target%dependencies
87133
subroutine add_dependency(target, dependency)
88134
type(build_target_t), intent(inout) :: target
89135
type(build_target_t) , intent(in), target :: dependency
90136

91-
type(build_target_ptr) :: depend
92-
93-
depend%ptr => dependency
94-
95-
! if (.not.allocated(target%dependencies)) then
96-
! allocate(target%dependencies(0))
97-
! end if
98-
99-
target%dependencies = [target%dependencies, depend]
100-
! target%dependencies(size(target%dependencies))%ptr => dependency
137+
target%dependencies = [target%dependencies, build_target_ptr(dependency)]
101138

102139
end subroutine add_dependency
103140

104141

105-
function get_object_name(source_file_name) result(object_file)
106-
! Generate object target path from source name and model params
107-
!
108-
! src/test.f90 -> <output-dir>/<package-name>/test.o
109-
! src/subdir/test.f90 -> <output-dir>/<package-name>/subdir_test.o
110-
!
111-
character(*), intent(in) :: source_file_name
112-
character(:), allocatable :: object_file
113-
114-
integer :: i
115-
character(1) :: filesep
116-
117-
select case(get_os_type())
118-
case (OS_WINDOWS)
119-
filesep = '\'
120-
case default
121-
filesep = '/'
122-
end select
123-
124-
! Exclude first directory level from path
125-
object_file = source_file_name(index(source_file_name,filesep)+1:)//'.o'
126-
127-
end function get_object_name
128-
129-
130142
subroutine resolve_module_dependencies(targets,error)
131143
! After enumerating all source files: resolve file dependencies
132144
! by searching on module names

0 commit comments

Comments
 (0)