Skip to content

Commit 388108d

Browse files
committed
installer: use moduledir for modules
1 parent 6455ce4 commit 388108d

File tree

3 files changed

+47
-3
lines changed

3 files changed

+47
-3
lines changed

src/fpm/cmd/install.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -63,7 +63,7 @@ subroutine cmd_install(settings)
6363

6464
call new_installer(installer, prefix=settings%prefix, &
6565
bindir=settings%bindir, libdir=settings%libdir, testdir=settings%testdir, &
66-
includedir=settings%includedir, &
66+
includedir=settings%includedir, moduledir=package%install%module_dir, &
6767
verbosity=merge(2, 1, settings%verbose))
6868

6969
if (allocated(package%library) .and. package%install%library) then
@@ -141,7 +141,7 @@ subroutine install_module_files(installer, targets, error)
141141
call filter_modules(targets, modules)
142142

143143
do ii = 1, size(modules)
144-
call installer%install_header(modules(ii)%s//".mod", error)
144+
call installer%install_module(modules(ii)%s//".mod", error)
145145
if (allocated(error)) exit
146146
end do
147147
if (allocated(error)) return

src/fpm/installer.f90

Lines changed: 28 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,8 @@ module fpm_installer
2727
character(len=:), allocatable :: testdir
2828
!> Include directory relative to the installation prefix
2929
character(len=:), allocatable :: includedir
30+
!> Module directory relative to the installation prefix
31+
character(len=:), allocatable :: moduledir
3032
!> Output unit for informative printout
3133
integer :: unit = output_unit
3234
!> Verbosity of the installer
@@ -46,6 +48,8 @@ module fpm_installer
4648
procedure :: install_library
4749
!> Install a header/module in its correct subdirectory
4850
procedure :: install_header
51+
!> Install a module in its correct subdirectory
52+
procedure :: install_module
4953
!> Install a test program in its correct subdirectory
5054
procedure :: install_test
5155
!> Install a generic file into a subdirectory in the installation prefix
@@ -69,6 +73,9 @@ module fpm_installer
6973
!> Default name of the include subdirectory
7074
character(len=*), parameter :: default_includedir = "include"
7175

76+
!> Default name of the module subdirectory
77+
character(len=*), parameter :: default_moduledir = "include"
78+
7279
!> Copy command on Unix platforms
7380
character(len=*), parameter :: default_copy_unix = "cp"
7481

@@ -90,7 +97,7 @@ module fpm_installer
9097
contains
9198

9299
!> Create a new instance of an installer
93-
subroutine new_installer(self, prefix, bindir, libdir, includedir, testdir, verbosity, &
100+
subroutine new_installer(self, prefix, bindir, libdir, includedir, moduledir, testdir, verbosity, &
94101
copy, move)
95102
!> Instance of the installer
96103
type(installer_t), intent(out) :: self
@@ -102,6 +109,8 @@ subroutine new_installer(self, prefix, bindir, libdir, includedir, testdir, verb
102109
character(len=*), intent(in), optional :: libdir
103110
!> Include directory relative to the installation prefix
104111
character(len=*), intent(in), optional :: includedir
112+
!> Module directory relative to the installation prefix
113+
character(len=*), intent(in), optional :: moduledir
105114
!> Test directory relative to the installation prefix
106115
character(len=*), intent(in), optional :: testdir
107116
!> Verbosity of the installer
@@ -139,6 +148,12 @@ subroutine new_installer(self, prefix, bindir, libdir, includedir, testdir, verb
139148
else
140149
self%includedir = default_includedir
141150
end if
151+
152+
if (present(moduledir)) then
153+
self%moduledir = moduledir
154+
else
155+
self%moduledir = default_moduledir
156+
end if
142157

143158
if (present(testdir)) then
144159
self%testdir = testdir
@@ -288,6 +303,18 @@ subroutine install_header(self, header, error)
288303
call self%install(header, self%includedir, error)
289304
end subroutine install_header
290305

306+
!> Install a module in its correct subdirectory
307+
subroutine install_module(self, module, error)
308+
!> Instance of the installer
309+
class(installer_t), intent(inout) :: self
310+
!> Path to the module
311+
character(len=*), intent(in) :: module
312+
!> Error handling
313+
type(error_t), allocatable, intent(out) :: error
314+
315+
call self%install(module, self%moduledir, error)
316+
end subroutine install_module
317+
291318
!> Install a generic file into a subdirectory in the installation prefix
292319
subroutine install(self, source, destination, error)
293320
!> Instance of the installer

test/fpm_test/test_installer.f90

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -36,6 +36,7 @@ subroutine collect_installer(testsuite)
3636
& new_unittest("install-pkgconfig", test_install_pkgconfig), &
3737
& new_unittest("install-sitepackages", test_install_sitepackages), &
3838
& new_unittest("install-mod", test_install_mod), &
39+
& new_unittest("install-module-custom", test_install_module_custom), &
3940
& new_unittest("install-exe-unix", test_install_exe_unix), &
4041
& new_unittest("install-exe-win", test_install_exe_win), &
4142
& new_unittest("install-test-unix", test_install_tests_unix), &
@@ -184,6 +185,22 @@ subroutine test_install_mod(error)
184185

185186
end subroutine test_install_mod
186187

188+
subroutine test_install_module_custom(error)
189+
!> Error handling
190+
type(error_t), allocatable, intent(out) :: error
191+
192+
type(mock_installer_t) :: mock
193+
type(installer_t) :: installer
194+
195+
call new_installer(installer, prefix="PREFIX", moduledir="custom/modules", verbosity=0, copy="mock")
196+
mock%installer_t = installer
197+
mock%expected_dir = join_path("PREFIX", "custom/modules")
198+
mock%expected_run = 'mock "test_module.mod" "'//join_path("PREFIX", "custom/modules")//'"'
199+
200+
call mock%install_module("test_module.mod", error)
201+
202+
end subroutine test_install_module_custom
203+
187204
subroutine test_install_shared_library_unix(error)
188205
!> Error handling
189206
type(error_t), allocatable, intent(out) :: error

0 commit comments

Comments
 (0)