Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
14 changes: 14 additions & 0 deletions ci/run_tests.sh
Original file line number Diff line number Diff line change
Expand Up @@ -344,6 +344,20 @@ pushd static_app_only
test $EXIT_CODE -eq 0
popd

# Test custom module directory
pushd custom_module_dir
"$fpm" build
rm -rf ./test_custom_install
"$fpm" install --prefix ./test_custom_install
# Verify modules are installed in custom directory
test -f ./test_custom_install/custom_modules/greeting.mod
test -f ./test_custom_install/custom_modules/math_utils.mod
# Verify library is still installed normally
test -f ./test_custom_install/lib/libcustom-module-dir.a
# Clean up
rm -rf ./test_custom_install
popd

# Test both shared and static library types
pushd both_lib_types
"$fpm" build
Expand Down
32 changes: 32 additions & 0 deletions example_packages/custom_module_dir/README.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,32 @@
# Custom Module Directory Example

This example demonstrates the use of a custom module directory in the `[install]` section of `fpm.toml`.

## Features

- Two simple Fortran modules: `greeting` and `math_utils`
- Custom module installation directory specified as `custom_modules`
- Shows how modules can be installed to a different location than headers

## Configuration

In `fpm.toml`:

```toml
[install]
library = true
module-dir = "custom_modules"
```

This configuration will install compiled `.mod` files to the `custom_modules` directory instead of the default `include` directory.

## Testing

To test this example:

```bash
cd example_packages/custom_module_dir
fpm build
fpm install --prefix /tmp/test_install
# Check that .mod files are in /tmp/test_install/custom_modules/
```
3 changes: 3 additions & 0 deletions example_packages/custom_module_dir/fpm.toml
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
name = "custom-module-dir"
install.library = true
install.module-dir = "custom_modules"
13 changes: 13 additions & 0 deletions example_packages/custom_module_dir/src/greeting.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
module greeting
implicit none
private
public :: say_hello

contains

subroutine say_hello(name)
character(len=*), intent(in) :: name
print *, 'Hello, ' // name // '!'
end subroutine say_hello

end module greeting
20 changes: 20 additions & 0 deletions example_packages/custom_module_dir/src/math_utils.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,20 @@
module math_utils
implicit none
private
public :: add_numbers, multiply_numbers

contains

function add_numbers(a, b) result(sum)
integer, intent(in) :: a, b
integer :: sum
sum = a + b
end function add_numbers

function multiply_numbers(a, b) result(product)
integer, intent(in) :: a, b
integer :: product
product = a * b
end function multiply_numbers

end module math_utils
4 changes: 2 additions & 2 deletions src/fpm/cmd/install.f90
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,7 @@ subroutine cmd_install(settings)

call new_installer(installer, prefix=settings%prefix, &
bindir=settings%bindir, libdir=settings%libdir, testdir=settings%testdir, &
includedir=settings%includedir, &
includedir=settings%includedir, moduledir=package%install%module_dir, &
verbosity=merge(2, 1, settings%verbose))

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

do ii = 1, size(modules)
call installer%install_header(modules(ii)%s//".mod", error)
call installer%install_module(modules(ii)%s//".mod", error)
if (allocated(error)) exit
end do
if (allocated(error)) return
Expand Down
29 changes: 28 additions & 1 deletion src/fpm/installer.f90
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,8 @@ module fpm_installer
character(len=:), allocatable :: testdir
!> Include directory relative to the installation prefix
character(len=:), allocatable :: includedir
!> Module directory relative to the installation prefix
character(len=:), allocatable :: moduledir
!> Output unit for informative printout
integer :: unit = output_unit
!> Verbosity of the installer
Expand All @@ -46,6 +48,8 @@ module fpm_installer
procedure :: install_library
!> Install a header/module in its correct subdirectory
procedure :: install_header
!> Install a module in its correct subdirectory
procedure :: install_module
!> Install a test program in its correct subdirectory
procedure :: install_test
!> Install a generic file into a subdirectory in the installation prefix
Expand All @@ -69,6 +73,9 @@ module fpm_installer
!> Default name of the include subdirectory
character(len=*), parameter :: default_includedir = "include"

!> Default name of the module subdirectory
character(len=*), parameter :: default_moduledir = "include"

!> Copy command on Unix platforms
character(len=*), parameter :: default_copy_unix = "cp"

Expand All @@ -90,7 +97,7 @@ module fpm_installer
contains

!> Create a new instance of an installer
subroutine new_installer(self, prefix, bindir, libdir, includedir, testdir, verbosity, &
subroutine new_installer(self, prefix, bindir, libdir, includedir, moduledir, testdir, verbosity, &
copy, move)
!> Instance of the installer
type(installer_t), intent(out) :: self
Expand All @@ -102,6 +109,8 @@ subroutine new_installer(self, prefix, bindir, libdir, includedir, testdir, verb
character(len=*), intent(in), optional :: libdir
!> Include directory relative to the installation prefix
character(len=*), intent(in), optional :: includedir
!> Module directory relative to the installation prefix
character(len=*), intent(in), optional :: moduledir
!> Test directory relative to the installation prefix
character(len=*), intent(in), optional :: testdir
!> Verbosity of the installer
Expand Down Expand Up @@ -139,6 +148,12 @@ subroutine new_installer(self, prefix, bindir, libdir, includedir, testdir, verb
else
self%includedir = default_includedir
end if

if (present(moduledir)) then
self%moduledir = moduledir
else
self%moduledir = default_moduledir
end if

if (present(testdir)) then
self%testdir = testdir
Expand Down Expand Up @@ -288,6 +303,18 @@ subroutine install_header(self, header, error)
call self%install(header, self%includedir, error)
end subroutine install_header

!> Install a module in its correct subdirectory
subroutine install_module(self, module, error)
!> Instance of the installer
class(installer_t), intent(inout) :: self
!> Path to the module
character(len=*), intent(in) :: module
!> Error handling
type(error_t), allocatable, intent(out) :: error

call self%install(module, self%moduledir, error)
end subroutine install_module

!> Install a generic file into a subdirectory in the installation prefix
subroutine install(self, source, destination, error)
!> Instance of the installer
Expand Down
21 changes: 19 additions & 2 deletions src/fpm/manifest/install.f90
Original file line number Diff line number Diff line change
Expand Up @@ -4,11 +4,12 @@
!>
!>```toml
!>library = bool
!>module-dir = "path"
!>```
module fpm_manifest_install
use fpm_error, only : error_t, fatal_error, syntax_error
use tomlf, only : toml_table, toml_key, toml_stat
use fpm_toml, only : get_value, set_value, serializable_t
use fpm_toml, only : get_value, set_value, serializable_t, set_string
implicit none
private

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

!> Directory where compiled module files should be installed
character(len=:), allocatable :: module_dir

contains

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

call get_value(table, "library", self%library, .false.)
call get_value(table, "test", self%test, .false.)
call get_value(table, "module-dir", self%module_dir)

end subroutine new_install_config

Expand All @@ -80,7 +85,7 @@ subroutine check(table, error)
case default
call syntax_error(error, "Key "//list(ikey)%key//" is not allowed in install table")
exit
case("library","test")
case("library","test","module-dir")
continue
end select
end do
Expand Down Expand Up @@ -114,6 +119,9 @@ subroutine info(self, unit, verbosity)
write(unit, fmt) "Install configuration"
write(unit, fmt) " - library install", trim(merge("enabled ", "disabled", self%library))
write(unit, fmt) " - test install", trim(merge("enabled ", "disabled", self%test))
if (allocated(self%module_dir)) then
write(unit, fmt) " - module directory", self%module_dir
end if

end subroutine info

Expand All @@ -127,6 +135,10 @@ logical function install_conf_same(this,that)
type is (install_config_t)
if (this%library.neqv.other%library) return
if (this%test.neqv.other%test) return
if (allocated(this%module_dir).neqv.allocated(other%module_dir)) return
if (allocated(this%module_dir)) then
if (.not.(this%module_dir==other%module_dir)) return
end if
class default
! Not the same type
return
Expand Down Expand Up @@ -155,6 +167,9 @@ subroutine dump_to_toml(self, table, error)
call set_value(table, "test", self%test, error, class_name)
if (allocated(error)) return

call set_string(table, "module-dir", self%module_dir, error, class_name)
if (allocated(error)) return

end subroutine dump_to_toml

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

end subroutine load_from_toml

Expand Down
17 changes: 17 additions & 0 deletions test/fpm_test/test_installer.f90
Original file line number Diff line number Diff line change
Expand Up @@ -36,6 +36,7 @@ subroutine collect_installer(testsuite)
& new_unittest("install-pkgconfig", test_install_pkgconfig), &
& new_unittest("install-sitepackages", test_install_sitepackages), &
& new_unittest("install-mod", test_install_mod), &
& new_unittest("install-module-custom", test_install_module_custom), &
& new_unittest("install-exe-unix", test_install_exe_unix), &
& new_unittest("install-exe-win", test_install_exe_win), &
& new_unittest("install-test-unix", test_install_tests_unix), &
Expand Down Expand Up @@ -184,6 +185,22 @@ subroutine test_install_mod(error)

end subroutine test_install_mod

subroutine test_install_module_custom(error)
!> Error handling
type(error_t), allocatable, intent(out) :: error

type(mock_installer_t) :: mock
type(installer_t) :: installer

call new_installer(installer, prefix="PREFIX", moduledir="custom_modules", verbosity=0, copy="mock")
mock%installer_t = installer
mock%expected_dir = join_path("PREFIX", "custom_modules")
mock%expected_run = 'mock "test_module.mod" "'//join_path("PREFIX", "custom_modules")//'"'

call mock%install_module("test_module.mod", error)

end subroutine test_install_module_custom

subroutine test_install_shared_library_unix(error)
!> Error handling
type(error_t), allocatable, intent(out) :: error
Expand Down
29 changes: 29 additions & 0 deletions test/fpm_test/test_manifest.f90
Original file line number Diff line number Diff line change
Expand Up @@ -69,6 +69,7 @@ subroutine collect_manifest(tests)
& new_unittest("example-empty", test_example_empty, should_fail=.true.), &
& new_unittest("install-library", test_install_library), &
& new_unittest("install-empty", test_install_empty), &
& new_unittest("install-module-dir", test_install_module_dir), &
& new_unittest("install-wrongkey", test_install_wrongkey, should_fail=.true.), &
& new_unittest("preprocess-empty", test_preprocess_empty), &
& new_unittest("preprocess-wrongkey", test_preprocess_wrongkey, should_fail=.true.), &
Expand Down Expand Up @@ -1409,6 +1410,34 @@ subroutine test_install_wrongkey(error)

end subroutine test_install_wrongkey


subroutine test_install_module_dir(error)
use fpm_manifest_install

!> Error handling
type(error_t), allocatable, intent(out) :: error

type(toml_table) :: table
type(install_config_t) :: install

table = toml_table()
call set_value(table, "module-dir", "custom_modules")

call new_install_config(install, table, error)
if (allocated(error)) return

if (.not.allocated(install%module_dir)) then
call test_failed(error, "Module directory should be allocated")
return
end if

if (install%module_dir /= "custom_modules") then
call test_failed(error, "Module directory should match input")
return
end if

end subroutine test_install_module_dir

subroutine test_preprocess_empty(error)
use fpm_manifest_preprocess

Expand Down
Loading