Skip to content

Commit f57a8b8

Browse files
committed
[macOS] dynamically add current library path
1 parent 1b4da71 commit f57a8b8

File tree

1 file changed

+14
-13
lines changed

1 file changed

+14
-13
lines changed

src/fpm.f90

Lines changed: 14 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -809,8 +809,7 @@ function save_library_path() result(path)
809809
case (OS_WINDOWS)
810810
path = get_env("PATH", default="")
811811
case (OS_MACOS)
812-
! macOS does not use LD_LIBRARY_PATH by default for `.dylib`
813-
allocate(character(0) :: path)
812+
path = get_env("DYLD_LIBRARY_PATH", default="")
814813
case default ! UNIX/Linux
815814
path = get_env("LD_LIBRARY_PATH", default="")
816815
end select
@@ -823,7 +822,7 @@ subroutine set_library_path(model, targets, error)
823822
type(error_t), allocatable, intent(out) :: error
824823

825824
type(string_t), allocatable :: shared_lib_dirs(:)
826-
character(len=:), allocatable :: new_path, sep
825+
character(len=:), allocatable :: new_path, sep, current
827826
logical :: success
828827
integer :: i
829828

@@ -839,30 +838,32 @@ subroutine set_library_path(model, targets, error)
839838
end select
840839

841840
! Join the directories into a path string
842-
! Manually join paths
843841
new_path = ""
844842
do i = 1, size(shared_lib_dirs)
845843
if (i > 1) new_path = new_path // sep
846844
new_path = new_path // shared_lib_dirs(i)%s
847845
end do
846+
847+
! Get current library path
848+
current = save_library_path()
848849

849850
! Set the appropriate environment variable
850851
select case (get_os_type())
851852
case (OS_WINDOWS)
852-
success = set_env("PATH", new_path // sep // get_env("PATH", default=""))
853+
success = set_env("PATH", new_path // sep // current)
853854
case (OS_MACOS)
854-
! Typically not required for local .dylib use, noop or DYLD_LIBRARY_PATH if needed
855-
success = .true.
855+
success = set_env("DYLD_LIBRARY_PATH", new_path // sep // current)
856856
case default ! UNIX/Linux
857-
success = set_env("LD_LIBRARY_PATH", new_path // sep // get_env("LD_LIBRARY_PATH", default=""))
857+
success = set_env("LD_LIBRARY_PATH", new_path // sep // current)
858858
end select
859859

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

862862
end subroutine set_library_path
863863

864+
864865
!> Restore a previously saved runtime library path
865-
subroutine restore_library_path(saved_path,error)
866+
subroutine restore_library_path(saved_path, error)
866867
character(*), intent(in) :: saved_path
867868
type(error_t), allocatable, intent(out) :: error
868869
logical :: success
@@ -871,16 +872,16 @@ subroutine restore_library_path(saved_path,error)
871872
case (OS_WINDOWS)
872873
success = set_env("PATH", saved_path)
873874
case (OS_MACOS)
874-
! noop
875-
success = .true.
875+
success = set_env("DYLD_LIBRARY_PATH", saved_path)
876876
case default ! UNIX/Linux
877877
success = set_env("LD_LIBRARY_PATH", saved_path)
878878
end select
879879

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

882882
end subroutine restore_library_path
883883

884884

885885

886+
886887
end module fpm

0 commit comments

Comments
 (0)