@@ -21,6 +21,8 @@ module fpm_installer
21
21
character (len= :), allocatable :: bindir
22
22
! > Library directory relative to the installation prefix
23
23
character (len= :), allocatable :: libdir
24
+ ! > Test program directory relative to the installation prefix
25
+ character (len= :), allocatable :: testdir
24
26
! > Include directory relative to the installation prefix
25
27
character (len= :), allocatable :: includedir
26
28
! > Output unit for informative printout
@@ -40,6 +42,8 @@ module fpm_installer
40
42
procedure :: install_library
41
43
! > Install a header/module in its correct subdirectory
42
44
procedure :: install_header
45
+ ! > Install a test program in its correct subdirectory
46
+ procedure :: install_test
43
47
! > Install a generic file into a subdirectory in the installation prefix
44
48
procedure :: install
45
49
! > Run an installation command, type-bound for unit testing purposes
@@ -53,6 +57,9 @@ module fpm_installer
53
57
54
58
! > Default name of the library subdirectory
55
59
character (len=* ), parameter :: default_libdir = " lib"
60
+
61
+ ! > Default name of the test subdirectory
62
+ character (len=* ), parameter :: default_testdir = " test"
56
63
57
64
! > Default name of the include subdirectory
58
65
character (len=* ), parameter :: default_includedir = " include"
@@ -78,7 +85,7 @@ module fpm_installer
78
85
contains
79
86
80
87
! > 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 , &
82
89
copy , move )
83
90
! > Instance of the installer
84
91
type (installer_t), intent (out ) :: self
@@ -90,6 +97,8 @@ subroutine new_installer(self, prefix, bindir, libdir, includedir, verbosity, &
90
97
character (len=* ), intent (in ), optional :: libdir
91
98
! > Include directory relative to the installation prefix
92
99
character (len=* ), intent (in ), optional :: includedir
100
+ ! > Test directory relative to the installation prefix
101
+ character (len=* ), intent (in ), optional :: testdir
93
102
! > Verbosity of the installer
94
103
integer , intent (in ), optional :: verbosity
95
104
! > Copy command
@@ -125,6 +134,12 @@ subroutine new_installer(self, prefix, bindir, libdir, includedir, verbosity, &
125
134
else
126
135
self% includedir = default_includedir
127
136
end if
137
+
138
+ if (present (testdir)) then
139
+ self% testdir = testdir
140
+ else
141
+ self% testdir = default_testdir
142
+ end if
128
143
129
144
if (present (prefix)) then
130
145
self% prefix = prefix
@@ -186,6 +201,28 @@ subroutine install_library(self, library, error)
186
201
call self% install(library, self% libdir, error)
187
202
end subroutine install_library
188
203
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
+
189
226
! > Install a header/module in its correct subdirectory
190
227
subroutine install_header (self , header , error )
191
228
! > Instance of the installer
0 commit comments