Skip to content

Commit 265cbee

Browse files
authored
feat: custom module install directory (#1170)
2 parents 9162137 + a4b2679 commit 265cbee

File tree

10 files changed

+177
-5
lines changed

10 files changed

+177
-5
lines changed

ci/run_tests.sh

Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -344,6 +344,20 @@ pushd static_app_only
344344
test $EXIT_CODE -eq 0
345345
popd
346346

347+
# Test custom module directory
348+
pushd custom_module_dir
349+
"$fpm" build
350+
rm -rf ./test_custom_install
351+
"$fpm" install --prefix ./test_custom_install
352+
# Verify modules are installed in custom directory
353+
test -f ./test_custom_install/custom_modules/greeting.mod
354+
test -f ./test_custom_install/custom_modules/math_utils.mod
355+
# Verify library is still installed normally
356+
test -f ./test_custom_install/lib/libcustom-module-dir.a
357+
# Clean up
358+
rm -rf ./test_custom_install
359+
popd
360+
347361
# Test both shared and static library types
348362
pushd both_lib_types
349363
"$fpm" build
Lines changed: 32 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,32 @@
1+
# Custom Module Directory Example
2+
3+
This example demonstrates the use of a custom module directory in the `[install]` section of `fpm.toml`.
4+
5+
## Features
6+
7+
- Two simple Fortran modules: `greeting` and `math_utils`
8+
- Custom module installation directory specified as `custom_modules`
9+
- Shows how modules can be installed to a different location than headers
10+
11+
## Configuration
12+
13+
In `fpm.toml`:
14+
15+
```toml
16+
[install]
17+
library = true
18+
module-dir = "custom_modules"
19+
```
20+
21+
This configuration will install compiled `.mod` files to the `custom_modules` directory instead of the default `include` directory.
22+
23+
## Testing
24+
25+
To test this example:
26+
27+
```bash
28+
cd example_packages/custom_module_dir
29+
fpm build
30+
fpm install --prefix /tmp/test_install
31+
# Check that .mod files are in /tmp/test_install/custom_modules/
32+
```
Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
name = "custom-module-dir"
2+
install.library = true
3+
install.module-dir = "custom_modules"
Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,13 @@
1+
module greeting
2+
implicit none
3+
private
4+
public :: say_hello
5+
6+
contains
7+
8+
subroutine say_hello(name)
9+
character(len=*), intent(in) :: name
10+
print *, 'Hello, ' // name // '!'
11+
end subroutine say_hello
12+
13+
end module greeting
Lines changed: 20 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,20 @@
1+
module math_utils
2+
implicit none
3+
private
4+
public :: add_numbers, multiply_numbers
5+
6+
contains
7+
8+
function add_numbers(a, b) result(sum)
9+
integer, intent(in) :: a, b
10+
integer :: sum
11+
sum = a + b
12+
end function add_numbers
13+
14+
function multiply_numbers(a, b) result(product)
15+
integer, intent(in) :: a, b
16+
integer :: product
17+
product = a * b
18+
end function multiply_numbers
19+
20+
end module math_utils

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

src/fpm/manifest/install.f90

Lines changed: 19 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,11 +4,12 @@
44
!>
55
!>```toml
66
!>library = bool
7+
!>module-dir = "path"
78
!>```
89
module fpm_manifest_install
910
use fpm_error, only : error_t, fatal_error, syntax_error
1011
use tomlf, only : toml_table, toml_key, toml_stat
11-
use fpm_toml, only : get_value, set_value, serializable_t
12+
use fpm_toml, only : get_value, set_value, serializable_t, set_string
1213
implicit none
1314
private
1415

@@ -23,6 +24,9 @@ module fpm_manifest_install
2324
!> Install tests with this project
2425
logical :: test = .false.
2526

27+
!> Directory where compiled module files should be installed
28+
character(len=:), allocatable :: module_dir
29+
2630
contains
2731

2832
!> Print information on this instance
@@ -56,6 +60,7 @@ subroutine new_install_config(self, table, error)
5660

5761
call get_value(table, "library", self%library, .false.)
5862
call get_value(table, "test", self%test, .false.)
63+
call get_value(table, "module-dir", self%module_dir)
5964

6065
end subroutine new_install_config
6166

@@ -80,7 +85,7 @@ subroutine check(table, error)
8085
case default
8186
call syntax_error(error, "Key "//list(ikey)%key//" is not allowed in install table")
8287
exit
83-
case("library","test")
88+
case("library","test","module-dir")
8489
continue
8590
end select
8691
end do
@@ -114,6 +119,9 @@ subroutine info(self, unit, verbosity)
114119
write(unit, fmt) "Install configuration"
115120
write(unit, fmt) " - library install", trim(merge("enabled ", "disabled", self%library))
116121
write(unit, fmt) " - test install", trim(merge("enabled ", "disabled", self%test))
122+
if (allocated(self%module_dir)) then
123+
write(unit, fmt) " - module directory", self%module_dir
124+
end if
117125

118126
end subroutine info
119127

@@ -127,6 +135,10 @@ logical function install_conf_same(this,that)
127135
type is (install_config_t)
128136
if (this%library.neqv.other%library) return
129137
if (this%test.neqv.other%test) return
138+
if (allocated(this%module_dir).neqv.allocated(other%module_dir)) return
139+
if (allocated(this%module_dir)) then
140+
if (.not.(this%module_dir==other%module_dir)) return
141+
end if
130142
class default
131143
! Not the same type
132144
return
@@ -155,6 +167,9 @@ subroutine dump_to_toml(self, table, error)
155167
call set_value(table, "test", self%test, error, class_name)
156168
if (allocated(error)) return
157169

170+
call set_string(table, "module-dir", self%module_dir, error, class_name)
171+
if (allocated(error)) return
172+
158173
end subroutine dump_to_toml
159174

160175
!> Read install config from toml table (no checks made at this stage)
@@ -175,6 +190,8 @@ subroutine load_from_toml(self, table, error)
175190
if (allocated(error)) return
176191
call get_value(table, "test", self%test, error, class_name)
177192
if (allocated(error)) return
193+
call get_value(table, "module-dir", self%module_dir)
194+
if (allocated(error)) return
178195

179196
end subroutine load_from_toml
180197

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

test/fpm_test/test_manifest.f90

Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -69,6 +69,7 @@ subroutine collect_manifest(tests)
6969
& new_unittest("example-empty", test_example_empty, should_fail=.true.), &
7070
& new_unittest("install-library", test_install_library), &
7171
& new_unittest("install-empty", test_install_empty), &
72+
& new_unittest("install-module-dir", test_install_module_dir), &
7273
& new_unittest("install-wrongkey", test_install_wrongkey, should_fail=.true.), &
7374
& new_unittest("preprocess-empty", test_preprocess_empty), &
7475
& new_unittest("preprocess-wrongkey", test_preprocess_wrongkey, should_fail=.true.), &
@@ -1409,6 +1410,34 @@ subroutine test_install_wrongkey(error)
14091410

14101411
end subroutine test_install_wrongkey
14111412

1413+
1414+
subroutine test_install_module_dir(error)
1415+
use fpm_manifest_install
1416+
1417+
!> Error handling
1418+
type(error_t), allocatable, intent(out) :: error
1419+
1420+
type(toml_table) :: table
1421+
type(install_config_t) :: install
1422+
1423+
table = toml_table()
1424+
call set_value(table, "module-dir", "custom_modules")
1425+
1426+
call new_install_config(install, table, error)
1427+
if (allocated(error)) return
1428+
1429+
if (.not.allocated(install%module_dir)) then
1430+
call test_failed(error, "Module directory should be allocated")
1431+
return
1432+
end if
1433+
1434+
if (install%module_dir /= "custom_modules") then
1435+
call test_failed(error, "Module directory should match input")
1436+
return
1437+
end if
1438+
1439+
end subroutine test_install_module_dir
1440+
14121441
subroutine test_preprocess_empty(error)
14131442
use fpm_manifest_preprocess
14141443

0 commit comments

Comments
 (0)