5
5
! > to any directory within the prefix.
6
6
module fpm_installer
7
7
use , intrinsic :: iso_fortran_env, only : output_unit
8
- use fpm_environment, only : get_os_type, os_is_unix, OS_WINDOWS
8
+ use fpm_environment, only : get_os_type, os_is_unix, OS_WINDOWS, OS_MACOS
9
9
use fpm_error, only : error_t, fatal_error
10
10
use fpm_targets, only: build_target_t, FPM_TARGET_ARCHIVE, FPM_TARGET_SHARED, FPM_TARGET_NAME
11
- use fpm_filesystem, only : join_path, mkdir, exists, unix_path, windows_path, get_local_prefix
11
+ use fpm_filesystem, only : join_path, mkdir, exists, unix_path, windows_path, get_local_prefix, &
12
+ basename
12
13
13
14
implicit none
14
15
private
@@ -37,6 +38,8 @@ module fpm_installer
37
38
! > Cached operating system
38
39
integer :: os
39
40
contains
41
+ ! > Evaluate the installation path
42
+ procedure :: install_destination
40
43
! > Install an executable in its correct subdirectory
41
44
procedure :: install_executable
42
45
! > Install a library in its correct subdirectory
@@ -51,6 +54,7 @@ module fpm_installer
51
54
procedure :: run
52
55
! > Create a new directory in the prefix, type-bound for unit testing purposes
53
56
procedure :: make_dir
57
+
54
58
end type installer_t
55
59
56
60
! > Default name of the binary subdirectory
@@ -177,6 +181,8 @@ subroutine install_executable(self, executable, error)
177
181
! > Error handling
178
182
type (error_t), allocatable , intent (out ) :: error
179
183
integer :: ll
184
+
185
+ character (len= :), allocatable :: exe_path, cmd
180
186
181
187
if (.not. os_is_unix(self% os)) then
182
188
ll = len (executable)
@@ -185,9 +191,26 @@ subroutine install_executable(self, executable, error)
185
191
return
186
192
end if
187
193
end if
188
-
194
+
189
195
call self% install(executable, self% bindir, error)
190
196
197
+ ! on MacOS, add two relative paths for search of dynamic library dependencies:
198
+ add_rpath: if (self% os== OS_MACOS) then
199
+
200
+ exe_path = join_path(self% install_destination(self% bindir) , basename(executable))
201
+
202
+ ! First path: for bin/lib/include structure
203
+ cmd = " install_name_tool -add_rpath @executable_path/../lib " // exe_path
204
+ call self% run(cmd, error)
205
+ if (allocated (error)) return
206
+
207
+ ! Second path: same as executable folder
208
+ cmd = " install_name_tool -add_rpath @executable_path " // exe_path
209
+ call self% run(cmd, error)
210
+ if (allocated (error)) return
211
+
212
+ end if add_rpath
213
+
191
214
end subroutine install_executable
192
215
193
216
! > Install a library in its correct subdirectory
@@ -278,12 +301,7 @@ subroutine install(self, source, destination, error)
278
301
279
302
character (len= :), allocatable :: install_dest
280
303
281
- install_dest = join_path(self% prefix, destination)
282
- if (os_is_unix(self% os)) then
283
- install_dest = unix_path(install_dest)
284
- else
285
- install_dest = windows_path(install_dest)
286
- end if
304
+ install_dest = self% install_destination(destination)
287
305
call self% make_dir(install_dest, error)
288
306
if (allocated (error)) return
289
307
@@ -303,6 +321,24 @@ subroutine install(self, source, destination, error)
303
321
if (allocated (error)) return
304
322
305
323
end subroutine install
324
+
325
+ ! > Evaluate the installation path
326
+ function install_destination (self , destination ) result(install_dest)
327
+ ! > Instance of the installer
328
+ class(installer_t), intent (inout ) :: self
329
+ ! > Path to the destination inside the prefix
330
+ character (len=* ), intent (in ) :: destination
331
+
332
+ character (len= :), allocatable :: install_dest
333
+
334
+ install_dest = join_path(self% prefix, destination)
335
+ if (os_is_unix(self% os)) then
336
+ install_dest = unix_path(install_dest)
337
+ else
338
+ install_dest = windows_path(install_dest)
339
+ end if
340
+
341
+ end function install_destination
306
342
307
343
! > Create a new directory in the prefix
308
344
subroutine make_dir (self , dir , error )
0 commit comments