Skip to content

Commit e02171d

Browse files
Merge pull request #155 from LKedward/dependencies
[Fortran fpm] Internal dependencies & build backend
2 parents 9dca64d + eed082b commit e02171d

File tree

11 files changed

+1226
-126
lines changed

11 files changed

+1226
-126
lines changed

ci/run_tests.bat

Lines changed: 20 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -21,5 +21,24 @@ if errorlevel 1 exit 1
2121
..\..\..\fpm\build\gfortran_debug\app\fpm build
2222
if errorlevel 1 exit 1
2323

24-
.\hello_world
24+
.\build\gfortran_debug\app\hello_world
2525
if errorlevel 1 exit 1
26+
27+
28+
cd ..\hello_complex
29+
if errorlevel 1 exit 1
30+
31+
..\..\..\fpm\build\gfortran_debug\app\fpm build
32+
if errorlevel 1 exit 1
33+
34+
.\build\gfortran_debug\app\say_Hello
35+
if errorlevel 1 exit 1
36+
37+
.\build\gfortran_debug\app\say_goodbye
38+
if errorlevel 1 exit 1
39+
40+
.\build\gfortran_debug\test\greet_test
41+
if errorlevel 1 exit 1
42+
43+
.\build\gfortran_debug\test\farewell_test
44+
if errorlevel 1 exit 1

ci/run_tests.sh

Lines changed: 9 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,14 @@ fpm build
77
fpm run
88
fpm test
99
build/gfortran_debug/app/fpm
10+
1011
cd ../test/example_packages/hello_world
1112
../../../fpm/build/gfortran_debug/app/fpm build
12-
./hello_world
13+
./build/gfortran_debug/app/hello_world
14+
15+
cd ../hello_complex
16+
../../../fpm/build/gfortran_debug/app/fpm build
17+
./build/gfortran_debug/app/say_Hello
18+
./build/gfortran_debug/app/say_goodbye
19+
./build/gfortran_debug/test/greet_test
20+
./build/gfortran_debug/test/farewell_test

fpm/app/main.f90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
program main
2-
use command_line, only: &
2+
use fpm_command_line, only: &
33
fpm_cmd_settings, &
44
fpm_new_settings, &
55
fpm_build_settings, &
@@ -15,11 +15,11 @@ program main
1515

1616
call get_command_line_settings(cmd_settings)
1717

18-
select type(cmd_settings)
18+
select type(settings=>cmd_settings)
1919
type is (fpm_new_settings)
2020
call cmd_new()
2121
type is (fpm_build_settings)
22-
call cmd_build()
22+
call cmd_build(settings)
2323
type is (fpm_run_settings)
2424
call cmd_run()
2525
type is (fpm_test_settings)

fpm/src/fpm.f90

Lines changed: 51 additions & 105 deletions
Original file line numberDiff line numberDiff line change
@@ -1,99 +1,61 @@
11
module fpm
2-
use environment, only: get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
3-
use fpm_manifest, only : get_package_data, default_executable, default_library, &
4-
& package_t
2+
3+
use fpm_strings, only: string_t, str_ends_with
4+
use fpm_backend, only: build_package
5+
use fpm_command_line, only: fpm_build_settings
6+
use fpm_environment, only: run, get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
7+
use fpm_filesystem, only: join_path, number_of_rows, list_files, exists
8+
use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t
9+
use fpm_sources, only: add_executable_sources, add_sources_from_dir, &
10+
resolve_module_dependencies
11+
use fpm_manifest, only : get_package_data, default_executable, &
12+
default_library, package_t
513
use fpm_error, only : error_t
614
implicit none
715
private
816
public :: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test
917

10-
type string_t
11-
character(len=:), allocatable :: s
12-
end type
1318

1419
contains
1520

16-
integer function number_of_rows(s) result(nrows)
17-
! determine number or rows
18-
integer,intent(in)::s
19-
integer :: ios
20-
character(len=100) :: r
21-
rewind(s)
22-
nrows = 0
23-
do
24-
read(s, *, iostat=ios) r
25-
if (ios /= 0) exit
26-
nrows = nrows + 1
27-
end do
28-
rewind(s)
29-
end function
30-
31-
32-
subroutine list_files(dir, files)
33-
character(len=*), intent(in) :: dir
34-
type(string_t), allocatable, intent(out) :: files(:)
35-
character(len=100) :: filename
36-
integer :: stat, u, i
37-
! Using `inquire` / exists on directories works with gfortran, but not ifort
38-
if (.not. exists(dir)) then
39-
allocate(files(0))
40-
return
41-
end if
42-
select case (get_os_type())
43-
case (OS_LINUX)
44-
call execute_command_line("ls " // dir // " > fpm_ls.out", exitstat=stat)
45-
case (OS_MACOS)
46-
call execute_command_line("ls " // dir // " > fpm_ls.out", exitstat=stat)
47-
case (OS_WINDOWS)
48-
call execute_command_line("dir /b " // dir // " > fpm_ls.out", exitstat=stat)
49-
end select
50-
if (stat /= 0) then
51-
print *, "execute_command_line() failed"
52-
error stop
53-
end if
54-
open(newunit=u, file="fpm_ls.out", status="old")
55-
allocate(files(number_of_rows(u)))
56-
do i = 1, size(files)
57-
read(u, *) filename
58-
files(i)%s = trim(filename)
59-
end do
60-
close(u)
61-
end subroutine
62-
63-
subroutine run(cmd)
64-
character(len=*), intent(in) :: cmd
65-
integer :: stat
66-
print *, "+ ", cmd
67-
call execute_command_line(cmd, exitstat=stat)
68-
if (stat /= 0) then
69-
print *, "Command failed"
70-
error stop
71-
end if
72-
end subroutine
73-
74-
logical function exists(filename) result(r)
75-
character(len=*), intent(in) :: filename
76-
inquire(file=filename, exist=r)
77-
end function
78-
79-
logical function str_ends_with(s, e) result(r)
80-
character(*), intent(in) :: s, e
81-
integer :: n1, n2
82-
n1 = len(s)-len(e)+1
83-
n2 = len(s)
84-
if (n1 < 1) then
85-
r = .false.
86-
else
87-
r = (s(n1:n2) == e)
88-
end if
89-
end function
90-
91-
subroutine cmd_build()
21+
subroutine build_model(model, settings, package)
22+
! Constructs a valid fpm model from command line settings and toml manifest
23+
!
24+
type(fpm_model_t), intent(out) :: model
25+
type(fpm_build_settings), intent(in) :: settings
26+
type(package_t), intent(in) :: package
27+
28+
model%package_name = package%name
29+
30+
! #TODO: Choose flags and output directory based on cli settings & manifest inputs
31+
model%fortran_compiler = 'gfortran'
32+
model%output_directory = 'build/gfortran_debug'
33+
model%fortran_compile_flags = ' -Wall -Wextra -Wimplicit-interface -fPIC -fmax-errors=1 -g '// &
34+
'-fbounds-check -fcheck-array-temporaries -fbacktrace '// &
35+
'-J'//join_path(model%output_directory,model%package_name)
36+
model%link_flags = ''
37+
38+
! Add sources from executable directories
39+
if (allocated(package%executable)) then
40+
call add_executable_sources(model%sources, package%executable,is_test=.false.)
41+
end if
42+
if (allocated(package%test)) then
43+
call add_executable_sources(model%sources, package%test,is_test=.true.)
44+
end if
45+
46+
if (allocated(package%library)) then
47+
call add_sources_from_dir(model%sources,package%library%source_dir)
48+
end if
49+
50+
call resolve_module_dependencies(model%sources)
51+
52+
end subroutine build_model
53+
54+
subroutine cmd_build(settings)
55+
type(fpm_build_settings), intent(in) :: settings
9256
type(package_t) :: package
57+
type(fpm_model_t) :: model
9358
type(error_t), allocatable :: error
94-
type(string_t), allocatable :: files(:)
95-
character(:), allocatable :: basename, linking
96-
integer :: i, n
9759
call get_package_data(package, "fpm.toml", error)
9860
if (allocated(error)) then
9961
print '(a)', error%message
@@ -102,6 +64,7 @@ subroutine cmd_build()
10264

10365
! Populate library in case we find the default src directory
10466
if (.not.allocated(package%library) .and. exists("src")) then
67+
allocate(package%library)
10568
call default_library(package%library)
10669
end if
10770

@@ -116,27 +79,10 @@ subroutine cmd_build()
11679
error stop 1
11780
end if
11881

119-
linking = ""
120-
if (allocated(package%library)) then
121-
call list_files(package%library%source_dir, files)
122-
do i = 1, size(files)
123-
if (str_ends_with(files(i)%s, ".f90")) then
124-
n = len(files(i)%s)
125-
basename = files(i)%s
126-
call run("gfortran -c " // package%library%source_dir // "/" // &
127-
& basename // " -o " // basename // ".o")
128-
linking = linking // " " // basename // ".o"
129-
end if
130-
end do
131-
end if
82+
call build_model(model, settings, package)
83+
84+
call build_package(model)
13285

133-
do i = 1, size(package%executable)
134-
basename = package%executable(i)%main
135-
call run("gfortran -c " // package%executable(i)%source_dir // "/" // &
136-
& basename // " -o " // basename // ".o")
137-
call run("gfortran " // basename // ".o " // linking // " -o " // &
138-
& package%executable(i)%name)
139-
end do
14086
end subroutine
14187

14288
subroutine cmd_install()

fpm/src/fpm_backend.f90

Lines changed: 123 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,123 @@
1+
module fpm_backend
2+
3+
! Implements the native fpm build backend
4+
5+
use fpm_environment, only: run
6+
use fpm_filesystem, only: basename, join_path, exists, mkdir
7+
use fpm_model, only: fpm_model_t, srcfile_t, FPM_UNIT_MODULE, &
8+
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, &
9+
FPM_UNIT_CSOURCE, FPM_UNIT_PROGRAM
10+
use fpm_strings, only: split
11+
12+
implicit none
13+
14+
private
15+
public :: build_package
16+
17+
contains
18+
19+
20+
subroutine build_package(model)
21+
type(fpm_model_t), intent(inout) :: model
22+
23+
integer :: i
24+
character(:), allocatable :: base, linking, subdir
25+
26+
if (.not.exists(model%output_directory)) then
27+
call mkdir(model%output_directory)
28+
end if
29+
if (.not.exists(join_path(model%output_directory,model%package_name))) then
30+
call mkdir(join_path(model%output_directory,model%package_name))
31+
end if
32+
33+
linking = ""
34+
do i=1,size(model%sources)
35+
36+
if (model%sources(i)%unit_type == FPM_UNIT_MODULE .or. &
37+
model%sources(i)%unit_type == FPM_UNIT_SUBMODULE .or. &
38+
model%sources(i)%unit_type == FPM_UNIT_SUBPROGRAM .or. &
39+
model%sources(i)%unit_type == FPM_UNIT_CSOURCE) then
40+
41+
call build_source(model,model%sources(i),linking)
42+
43+
end if
44+
45+
end do
46+
47+
if (any([(model%sources(i)%unit_type == FPM_UNIT_PROGRAM,i=1,size(model%sources))])) then
48+
if (.not.exists(join_path(model%output_directory,'test'))) then
49+
call mkdir(join_path(model%output_directory,'test'))
50+
end if
51+
if (.not.exists(join_path(model%output_directory,'app'))) then
52+
call mkdir(join_path(model%output_directory,'app'))
53+
end if
54+
end if
55+
56+
do i=1,size(model%sources)
57+
58+
if (model%sources(i)%unit_type == FPM_UNIT_PROGRAM) then
59+
60+
base = basename(model%sources(i)%file_name,suffix=.false.)
61+
62+
if (model%sources(i)%is_test) then
63+
subdir = 'test'
64+
else
65+
subdir = 'app'
66+
end if
67+
68+
call run("gfortran -c " // model%sources(i)%file_name // ' '//model%fortran_compile_flags &
69+
// " -o " // join_path(model%output_directory,subdir,base) // ".o")
70+
71+
call run("gfortran " // join_path(model%output_directory, subdir, base) // ".o "// &
72+
linking //" " //model%link_flags // " -o " // &
73+
join_path(model%output_directory,subdir,model%sources(i)%exe_name) )
74+
75+
end if
76+
77+
end do
78+
79+
end subroutine build_package
80+
81+
82+
83+
recursive subroutine build_source(model,source_file,linking)
84+
! Compile Fortran source, called recursively on it dependents
85+
!
86+
type(fpm_model_t), intent(in) :: model
87+
type(srcfile_t), intent(inout) :: source_file
88+
character(:), allocatable, intent(inout) :: linking
89+
90+
integer :: i
91+
character(:), allocatable :: object_file
92+
93+
if (source_file%built) then
94+
return
95+
end if
96+
97+
if (source_file%touched) then
98+
write(*,*) '(!) Circular dependency found with: ',source_file%file_name
99+
stop
100+
else
101+
source_file%touched = .true.
102+
end if
103+
104+
do i=1,size(source_file%file_dependencies)
105+
106+
if (associated(source_file%file_dependencies(i)%ptr)) then
107+
call build_source(model,source_file%file_dependencies(i)%ptr,linking)
108+
end if
109+
110+
end do
111+
112+
object_file = join_path(model%output_directory, model%package_name, &
113+
basename(source_file%file_name,suffix=.false.)//'.o')
114+
115+
call run("gfortran -c " // source_file%file_name // model%fortran_compile_flags &
116+
// " -o " // object_file)
117+
linking = linking // " " // object_file
118+
119+
source_file%built = .true.
120+
121+
end subroutine build_source
122+
123+
end module fpm_backend

0 commit comments

Comments
 (0)