Skip to content

Commit 6908108

Browse files
authored
[macOS] Standardize dynamic library paths using @rpath (#1146)
2 parents 413fdbd + ea6b7e6 commit 6908108

File tree

4 files changed

+123
-24
lines changed

4 files changed

+123
-24
lines changed

src/fpm.f90

Lines changed: 20 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -604,6 +604,12 @@ subroutine cmd_run(settings,test)
604604
if (settings%runner/=' ') run_cmd = settings%runner_command()//' '//run_cmd
605605
if (allocated(settings%args)) run_cmd = run_cmd//" "//settings%args
606606

607+
! System Integrity Protection will not propagate the .dylib environment variables
608+
! to the child process: add paths manually
609+
if (get_os_type()==OS_MACOS) run_cmd = "env DYLD_LIBRARY_PATH=" // &
610+
get_env("DYLD_LIBRARY_PATH","") // &
611+
" " // run_cmd
612+
607613
call run(run_cmd,echo=settings%verbose,exitstat=stat(i))
608614

609615
else
@@ -809,8 +815,7 @@ function save_library_path() result(path)
809815
case (OS_WINDOWS)
810816
path = get_env("PATH", default="")
811817
case (OS_MACOS)
812-
! macOS does not use LD_LIBRARY_PATH by default for `.dylib`
813-
allocate(character(0) :: path)
818+
path = get_env("DYLD_LIBRARY_PATH", default="")
814819
case default ! UNIX/Linux
815820
path = get_env("LD_LIBRARY_PATH", default="")
816821
end select
@@ -823,7 +828,7 @@ subroutine set_library_path(model, targets, error)
823828
type(error_t), allocatable, intent(out) :: error
824829

825830
type(string_t), allocatable :: shared_lib_dirs(:)
826-
character(len=:), allocatable :: new_path, sep
831+
character(len=:), allocatable :: new_path, sep, current
827832
logical :: success
828833
integer :: i
829834

@@ -839,30 +844,32 @@ subroutine set_library_path(model, targets, error)
839844
end select
840845

841846
! Join the directories into a path string
842-
! Manually join paths
843847
new_path = ""
844848
do i = 1, size(shared_lib_dirs)
845849
if (i > 1) new_path = new_path // sep
846850
new_path = new_path // shared_lib_dirs(i)%s
847851
end do
852+
853+
! Get current library path
854+
current = save_library_path()
848855

849856
! Set the appropriate environment variable
850857
select case (get_os_type())
851858
case (OS_WINDOWS)
852-
success = set_env("PATH", new_path // sep // get_env("PATH", default=""))
859+
success = set_env("PATH", new_path // sep // current)
853860
case (OS_MACOS)
854-
! Typically not required for local .dylib use, noop or DYLD_LIBRARY_PATH if needed
855-
success = .true.
861+
success = set_env("DYLD_LIBRARY_PATH", new_path // sep // current)
856862
case default ! UNIX/Linux
857-
success = set_env("LD_LIBRARY_PATH", new_path // sep // get_env("LD_LIBRARY_PATH", default=""))
863+
success = set_env("LD_LIBRARY_PATH", new_path // sep // current)
858864
end select
859865

860-
if (.not.success) call fatal_error(error," Cannot set library path: "//new_path)
866+
if (.not.success) call fatal_error(error,"Cannot set library path: "//new_path)
861867

862868
end subroutine set_library_path
863869

870+
864871
!> Restore a previously saved runtime library path
865-
subroutine restore_library_path(saved_path,error)
872+
subroutine restore_library_path(saved_path, error)
866873
character(*), intent(in) :: saved_path
867874
type(error_t), allocatable, intent(out) :: error
868875
logical :: success
@@ -871,16 +878,16 @@ subroutine restore_library_path(saved_path,error)
871878
case (OS_WINDOWS)
872879
success = set_env("PATH", saved_path)
873880
case (OS_MACOS)
874-
! noop
875-
success = .true.
881+
success = set_env("DYLD_LIBRARY_PATH", saved_path)
876882
case default ! UNIX/Linux
877883
success = set_env("LD_LIBRARY_PATH", saved_path)
878884
end select
879885

880-
if (.not.success) call fatal_error(error, "Cannot restore library path "//saved_path)
886+
if (.not.success) call fatal_error(error, "Cannot restore library path: "//saved_path)
881887

882888
end subroutine restore_library_path
883889

884890

885891

892+
886893
end module fpm

src/fpm/installer.f90

Lines changed: 45 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -5,10 +5,11 @@
55
!> to any directory within the prefix.
66
module fpm_installer
77
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
99
use fpm_error, only : error_t, fatal_error
1010
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
1213

1314
implicit none
1415
private
@@ -37,6 +38,8 @@ module fpm_installer
3738
!> Cached operating system
3839
integer :: os
3940
contains
41+
!> Evaluate the installation path
42+
procedure :: install_destination
4043
!> Install an executable in its correct subdirectory
4144
procedure :: install_executable
4245
!> Install a library in its correct subdirectory
@@ -51,6 +54,7 @@ module fpm_installer
5154
procedure :: run
5255
!> Create a new directory in the prefix, type-bound for unit testing purposes
5356
procedure :: make_dir
57+
5458
end type installer_t
5559

5660
!> Default name of the binary subdirectory
@@ -177,6 +181,8 @@ subroutine install_executable(self, executable, error)
177181
!> Error handling
178182
type(error_t), allocatable, intent(out) :: error
179183
integer :: ll
184+
185+
character(len=:), allocatable :: exe_path, cmd
180186

181187
if (.not.os_is_unix(self%os)) then
182188
ll = len(executable)
@@ -185,9 +191,26 @@ subroutine install_executable(self, executable, error)
185191
return
186192
end if
187193
end if
188-
194+
189195
call self%install(executable, self%bindir, error)
190196

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+
191214
end subroutine install_executable
192215

193216
!> Install a library in its correct subdirectory
@@ -278,12 +301,7 @@ subroutine install(self, source, destination, error)
278301

279302
character(len=:), allocatable :: install_dest
280303

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)
287305
call self%make_dir(install_dest, error)
288306
if (allocated(error)) return
289307

@@ -303,6 +321,24 @@ subroutine install(self, source, destination, error)
303321
if (allocated(error)) return
304322

305323
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
306342

307343
!> Create a new directory in the prefix
308344
subroutine make_dir(self, dir, error)

src/fpm_compiler.F90

Lines changed: 46 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -105,6 +105,10 @@ module fpm_compiler
105105
procedure :: get_main_flags
106106
!> Get library export flags
107107
procedure :: get_export_flags
108+
!> Get library install name flags
109+
procedure :: get_install_name_flags
110+
!> Generate header padding flags for macOS executables
111+
procedure :: get_headerpad_flags
108112
!> Compile a Fortran object
109113
procedure :: compile_fortran
110114
!> Compile a C object
@@ -1117,6 +1121,48 @@ function get_export_flags(self, target_dir, target_name) result(export_flags)
11171121

11181122
end function get_export_flags
11191123

1124+
!>
1125+
!> Generate `install_name` flag for a shared library build on macOS
1126+
!>
1127+
function get_install_name_flags(self, target_dir, target_name) result(flags)
1128+
class(compiler_t), intent(in) :: self
1129+
character(len=*), intent(in) :: target_dir, target_name
1130+
character(len=:), allocatable :: flags
1131+
character(len=:), allocatable :: library_file
1132+
1133+
if (get_os_type() /= OS_MACOS) then
1134+
flags = ""
1135+
return
1136+
end if
1137+
1138+
! Shared library basename (e.g., libfoo.dylib)
1139+
if (str_ends_with(target_name, ".dylib")) then
1140+
library_file = target_name
1141+
else
1142+
library_file = library_filename(target_name,.true.,.false.,OS_MACOS)
1143+
end if
1144+
1145+
flags = " -Wl,-install_name,@rpath/" // library_file
1146+
1147+
end function get_install_name_flags
1148+
1149+
!>
1150+
!> Generate header padding flags for install_name_tool compatibility on macOS
1151+
!>
1152+
function get_headerpad_flags(self) result(flags)
1153+
class(compiler_t), intent(in) :: self
1154+
character(len=:), allocatable :: flags
1155+
1156+
if (get_os_type() /= OS_MACOS) then
1157+
flags = ""
1158+
return
1159+
end if
1160+
1161+
! Reserve enough space in the Mach-O header to safely add two install_name or rpath later
1162+
flags = " -Wl,-headerpad,0x200"
1163+
1164+
end function get_headerpad_flags
1165+
11201166
!> Create new compiler instance
11211167
subroutine new_compiler(self, fc, cc, cxx, echo, verbose)
11221168
!> New instance of the compiler

src/fpm_targets.f90

Lines changed: 12 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1142,8 +1142,13 @@ subroutine resolve_target_linking(targets, model, library, error)
11421142
target%link_flags = target%link_flags // " " // &
11431143
model%compiler%get_export_flags(target%output_dir,target%package_name)
11441144

1145+
! Add install_name flag (macOS only)
1146+
target%link_flags = target%link_flags // " " // &
1147+
model%compiler%get_install_name_flags(target%output_dir, target%package_name)
1148+
11451149
! Add global link flags (e.g., system-wide libraries)
1146-
target%link_flags = target%link_flags // " " // global_link_flags
1150+
target%link_flags = target%link_flags // " " // global_link_flags
1151+
11471152

11481153
case (FPM_TARGET_EXECUTABLE)
11491154

@@ -1176,7 +1181,12 @@ subroutine resolve_target_linking(targets, model, library, error)
11761181
target%link_flags = model%get_package_libraries_link(target%package_name, &
11771182
target%link_flags, &
11781183
error=error, &
1179-
exclude_self=.not.has_self_lib)
1184+
exclude_self=.not.has_self_lib)
1185+
1186+
1187+
! On macOS, add room for 2 install_name_tool paths
1188+
target%link_flags = target%link_flags // model%compiler%get_headerpad_flags()
1189+
11801190
end if
11811191

11821192
if (allocated(target%link_libraries)) then

0 commit comments

Comments
 (0)