Skip to content

Commit c66f052

Browse files
authored
Merge pull request #257 from awvwgk/install
Implement fpm-install command
2 parents 55db69e + 2fdd5dd commit c66f052

18 files changed

+1020
-30
lines changed

ci/run_tests.bat

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -26,6 +26,12 @@ echo %fpm_path%
2626
%fpm_path%
2727
if errorlevel 1 exit 1
2828

29+
%fpm_path% build
30+
if errorlevel 1 exit 1
31+
32+
%fpm_path% install --prefix "%CD%\_dist" --no-rebuild
33+
if errorlevel 1 exit 1
34+
2935
cd ..\example_packages\hello_world
3036
if errorlevel 1 exit 1
3137

ci/run_tests.sh

Lines changed: 9 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,12 +15,20 @@ rm -rf fpm_scratch_*/
1515
fpm test $@
1616
rm -rf fpm_scratch_*/
1717

18-
# Build example packages
1918
f_fpm_path="$(fpm run $@ --runner echo)"
19+
20+
# Let fpm build itself
21+
"${f_fpm_path}" build
22+
23+
# Install fpm into local directory
24+
"${f_fpm_path}" install --prefix "$PWD/_dist" --no-rebuild
25+
26+
# Build example packages
2027
cd ../example_packages/
2128
rm -rf ./*/build
2229

2330
cd hello_world
31+
2432
"${f_fpm_path}" build
2533
./build/gfortran_debug/app/hello_world
2634
"${f_fpm_path}" run

fpm/app/main.f90

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,8 @@ program main
88
fpm_install_settings, &
99
fpm_update_settings, &
1010
get_command_line_settings
11-
use fpm, only: cmd_build, cmd_install, cmd_run
11+
use fpm, only: cmd_build, cmd_run
12+
use fpm_cmd_install, only: cmd_install
1213
use fpm_cmd_new, only: cmd_new
1314
use fpm_cmd_update, only : cmd_update
1415

fpm/src/fpm.f90

Lines changed: 2 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,8 @@ module fpm
2525
use fpm_manifest_dependency, only: dependency_config_t
2626
implicit none
2727
private
28-
public :: build_model, cmd_build, cmd_install, cmd_run
28+
public :: cmd_build, cmd_run
29+
public :: build_model
2930

3031
contains
3132

@@ -204,12 +205,6 @@ subroutine cmd_build(settings)
204205

205206
end subroutine
206207

207-
subroutine cmd_install(settings)
208-
type(fpm_install_settings), intent(in) :: settings
209-
print *, "fpm error: 'fpm install' not implemented."
210-
error stop 8
211-
end subroutine cmd_install
212-
213208
subroutine cmd_run(settings,test)
214209
class(fpm_run_settings), intent(in) :: settings
215210
logical, intent(in) :: test

fpm/src/fpm/cmd/install.f90

Lines changed: 170 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,170 @@
1+
module fpm_cmd_install
2+
use, intrinsic :: iso_fortran_env, only : output_unit
3+
use fpm, only : build_model
4+
use fpm_backend, only : build_package
5+
use fpm_command_line, only : fpm_install_settings
6+
use fpm_error, only : error_t, fatal_error
7+
use fpm_filesystem, only : join_path, list_files
8+
use fpm_installer, only : installer_t, new_installer
9+
use fpm_manifest, only : package_config_t, get_package_data
10+
use fpm_model, only : fpm_model_t, build_target_t, FPM_TARGET_EXECUTABLE, &
11+
FPM_SCOPE_APP
12+
use fpm_strings, only : string_t, resize
13+
implicit none
14+
private
15+
16+
public :: cmd_install
17+
18+
contains
19+
20+
!> Entry point for the fpm-install subcommand
21+
subroutine cmd_install(settings)
22+
!> Representation of the command line settings
23+
type(fpm_install_settings), intent(in) :: settings
24+
type(package_config_t) :: package
25+
type(error_t), allocatable :: error
26+
type(fpm_model_t) :: model
27+
type(installer_t) :: installer
28+
character(len=:), allocatable :: lib, exe, dir
29+
logical :: installable
30+
31+
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
32+
call handle_error(error)
33+
34+
call build_model(model, settings%fpm_build_settings, package, error)
35+
call handle_error(error)
36+
37+
installable = (allocated(package%library) .and. package%install%library) &
38+
.or. allocated(package%executable)
39+
if (.not.installable) then
40+
call fatal_error(error, "Project does not contain any installable targets")
41+
call handle_error(error)
42+
end if
43+
44+
if (settings%list) then
45+
call install_info(output_unit, package, model)
46+
return
47+
end if
48+
49+
if (.not.settings%no_rebuild) then
50+
call build_package(model)
51+
end if
52+
53+
call new_installer(installer, prefix=settings%prefix, &
54+
bindir=settings%bindir, libdir=settings%libdir, &
55+
includedir=settings%includedir, &
56+
verbosity=merge(2, 1, settings%verbose))
57+
58+
if (allocated(package%library) .and. package%install%library) then
59+
dir = join_path(model%output_directory, model%package_name)
60+
lib = "lib"//model%package_name//".a"
61+
call installer%install_library(join_path(dir, lib), error)
62+
call handle_error(error)
63+
64+
call install_module_files(installer, dir, error)
65+
call handle_error(error)
66+
end if
67+
68+
if (allocated(package%executable)) then
69+
call install_executables(installer, model, error)
70+
call handle_error(error)
71+
end if
72+
73+
end subroutine cmd_install
74+
75+
subroutine install_info(unit, package, model)
76+
integer, intent(in) :: unit
77+
type(package_config_t), intent(in) :: package
78+
type(fpm_model_t), intent(in) :: model
79+
80+
integer :: ii, ntargets
81+
character(len=:), allocatable :: lib
82+
type(string_t), allocatable :: install_target(:)
83+
84+
call resize(install_target)
85+
86+
ntargets = 0
87+
if (allocated(package%library) .and. package%install%library) then
88+
ntargets = ntargets + 1
89+
lib = join_path(model%output_directory, model%package_name, &
90+
"lib"//model%package_name//".a")
91+
install_target(ntargets)%s = lib
92+
end if
93+
do ii = 1, size(model%targets)
94+
if (is_executable_target(model%targets(ii)%ptr)) then
95+
if (ntargets >= size(install_target)) call resize(install_target)
96+
ntargets = ntargets + 1
97+
install_target(ntargets)%s = model%targets(ii)%ptr%output_file
98+
end if
99+
end do
100+
101+
write(unit, '("#", *(1x, g0))') &
102+
"total number of installable targets:", ntargets
103+
do ii = 1, ntargets
104+
write(unit, '("-", *(1x, g0))') install_target(ii)%s
105+
end do
106+
107+
end subroutine install_info
108+
109+
subroutine install_module_files(installer, dir, error)
110+
type(installer_t), intent(inout) :: installer
111+
character(len=*), intent(in) :: dir
112+
type(error_t), allocatable, intent(out) :: error
113+
type(string_t), allocatable :: modules(:)
114+
integer :: ii
115+
116+
call list_files(dir, modules, recurse=.false.)
117+
118+
do ii = 1, size(modules)
119+
if (is_module_file(modules(ii)%s)) then
120+
call installer%install_header(modules(ii)%s, error)
121+
if (allocated(error)) exit
122+
end if
123+
end do
124+
if (allocated(error)) return
125+
126+
end subroutine install_module_files
127+
128+
subroutine install_executables(installer, model, error)
129+
type(installer_t), intent(inout) :: installer
130+
type(fpm_model_t), intent(in) :: model
131+
type(error_t), allocatable, intent(out) :: error
132+
integer :: ii
133+
134+
do ii = 1, size(model%targets)
135+
if (is_executable_target(model%targets(ii)%ptr)) then
136+
call installer%install_executable(model%targets(ii)%ptr%output_file, error)
137+
if (allocated(error)) exit
138+
end if
139+
end do
140+
if (allocated(error)) return
141+
142+
end subroutine install_executables
143+
144+
elemental function is_executable_target(target_ptr) result(is_exe)
145+
type(build_target_t), intent(in) :: target_ptr
146+
logical :: is_exe
147+
is_exe = target_ptr%target_type == FPM_TARGET_EXECUTABLE .and. &
148+
allocated(target_ptr%dependencies)
149+
if (is_exe) then
150+
is_exe = target_ptr%dependencies(1)%ptr%source%unit_scope == FPM_SCOPE_APP
151+
end if
152+
end function is_executable_target
153+
154+
elemental function is_module_file(name) result(is_mod)
155+
character(len=*), intent(in) :: name
156+
logical :: is_mod
157+
integer :: ll
158+
ll = len(name)
159+
is_mod = name(max(1, ll-3):ll) == ".mod"
160+
end function is_module_file
161+
162+
subroutine handle_error(error)
163+
type(error_t), intent(in), optional :: error
164+
if (present(error)) then
165+
print '("[Error]", 1x, a)', error%message
166+
error stop 1
167+
end if
168+
end subroutine handle_error
169+
170+
end module fpm_cmd_install

0 commit comments

Comments
 (0)