@@ -21,6 +21,8 @@ module fpm_installer
2121 character (len= :), allocatable :: bindir
2222 ! > Library directory relative to the installation prefix
2323 character (len= :), allocatable :: libdir
24+ ! > Test program directory relative to the installation prefix
25+ character (len= :), allocatable :: testdir
2426 ! > Include directory relative to the installation prefix
2527 character (len= :), allocatable :: includedir
2628 ! > Output unit for informative printout
@@ -40,6 +42,8 @@ module fpm_installer
4042 procedure :: install_library
4143 ! > Install a header/module in its correct subdirectory
4244 procedure :: install_header
45+ ! > Install a test program in its correct subdirectory
46+ procedure :: install_test
4347 ! > Install a generic file into a subdirectory in the installation prefix
4448 procedure :: install
4549 ! > Run an installation command, type-bound for unit testing purposes
@@ -53,6 +57,9 @@ module fpm_installer
5357
5458 ! > Default name of the library subdirectory
5559 character (len=* ), parameter :: default_libdir = " lib"
60+
61+ ! > Default name of the test subdirectory
62+ character (len=* ), parameter :: default_testdir = " test"
5663
5764 ! > Default name of the include subdirectory
5865 character (len=* ), parameter :: default_includedir = " include"
@@ -78,7 +85,7 @@ module fpm_installer
7885contains
7986
8087 ! > Create a new instance of an installer
81- subroutine new_installer (self , prefix , bindir , libdir , includedir , verbosity , &
88+ subroutine new_installer (self , prefix , bindir , libdir , includedir , testdir , verbosity , &
8289 copy , move )
8390 ! > Instance of the installer
8491 type (installer_t), intent (out ) :: self
@@ -90,6 +97,8 @@ subroutine new_installer(self, prefix, bindir, libdir, includedir, verbosity, &
9097 character (len=* ), intent (in ), optional :: libdir
9198 ! > Include directory relative to the installation prefix
9299 character (len=* ), intent (in ), optional :: includedir
100+ ! > Test directory relative to the installation prefix
101+ character (len=* ), intent (in ), optional :: testdir
93102 ! > Verbosity of the installer
94103 integer , intent (in ), optional :: verbosity
95104 ! > Copy command
@@ -125,6 +134,12 @@ subroutine new_installer(self, prefix, bindir, libdir, includedir, verbosity, &
125134 else
126135 self% includedir = default_includedir
127136 end if
137+
138+ if (present (testdir)) then
139+ self% testdir = testdir
140+ else
141+ self% testdir = default_testdir
142+ end if
128143
129144 if (present (prefix)) then
130145 self% prefix = prefix
@@ -186,6 +201,28 @@ subroutine install_library(self, library, error)
186201 call self% install(library, self% libdir, error)
187202 end subroutine install_library
188203
204+ ! > Install a test program in its correct subdirectory
205+ subroutine install_test (self , test , error )
206+ ! > Instance of the installer
207+ class(installer_t), intent (inout ) :: self
208+ ! > Path to the test executable
209+ character (len=* ), intent (in ) :: test
210+ ! > Error handling
211+ type (error_t), allocatable , intent (out ) :: error
212+ integer :: ll
213+
214+ if (.not. os_is_unix(self% os)) then
215+ ll = len (test)
216+ if (test(max (1 , ll-3 ):ll) /= " .exe" ) then
217+ call self% install(test// " .exe" , self% testdir, error)
218+ return
219+ end if
220+ end if
221+
222+ call self% install(test, self% testdir, error)
223+
224+ end subroutine install_test
225+
189226 ! > Install a header/module in its correct subdirectory
190227 subroutine install_header (self , header , error )
191228 ! > Instance of the installer
0 commit comments