Skip to content

Commit aef5d11

Browse files
committed
Fix issue with Windows paths stored in cache.toml
1 parent f8190b0 commit aef5d11

File tree

1 file changed

+13
-3
lines changed

1 file changed

+13
-3
lines changed

fpm/src/fpm/dependency.f90

Lines changed: 13 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -56,8 +56,9 @@
5656
!> Currenly ignored. First come, first serve.
5757
module fpm_dependency
5858
use, intrinsic :: iso_fortran_env, only : output_unit
59+
use fpm_environment, only : get_os_type, OS_WINDOWS
5960
use fpm_error, only : error_t, fatal_error
60-
use fpm_filesystem, only : exists, join_path, mkdir
61+
use fpm_filesystem, only : exists, join_path, mkdir, canon_path, windows_path
6162
use fpm_git, only : git_target_revision, git_target_default, git_revision
6263
use fpm_manifest, only : package_config_t, dependency_config_t, &
6364
get_package_data
@@ -634,6 +635,7 @@ subroutine load_from_toml(self, table, error)
634635
type(error_t), allocatable, intent(out) :: error
635636

636637
integer :: ndep, ii
638+
logical :: unix
637639
character(len=:), allocatable :: version, url, obj, rev, proj_dir
638640
type(toml_key), allocatable :: list(:)
639641
type(toml_table), pointer :: ptr
@@ -646,6 +648,8 @@ subroutine load_from_toml(self, table, error)
646648
call resize(self%dep, ndep + ndep/2 + size(list))
647649
end if
648650

651+
unix = get_os_type() /= OS_WINDOWS
652+
649653
do ii = 1, size(list)
650654
call get_value(table, list(ii)%key, ptr)
651655
call get_value(ptr, "version", version)
@@ -657,7 +661,11 @@ subroutine load_from_toml(self, table, error)
657661
self%ndep = self%ndep + 1
658662
associate(dep => self%dep(self%ndep))
659663
dep%name = list(ii)%key
660-
dep%proj_dir = proj_dir
664+
if (unix) then
665+
dep%proj_dir = proj_dir
666+
else
667+
dep%proj_dir = windows_path(proj_dir)
668+
end if
661669
dep%done = .false.
662670
if (allocated(version)) then
663671
if (.not.allocated(dep%version)) allocate(dep%version)
@@ -737,6 +745,7 @@ subroutine dump_to_toml(self, table, error)
737745

738746
integer :: ii
739747
type(toml_table), pointer :: ptr
748+
character(len=:), allocatable :: proj_dir
740749

741750
do ii = 1, self%ndep
742751
associate(dep => self%dep(ii))
@@ -748,7 +757,8 @@ subroutine dump_to_toml(self, table, error)
748757
if (allocated(dep%version)) then
749758
call set_value(ptr, "version", char(dep%version))
750759
end if
751-
call set_value(ptr, "proj-dir", dep%proj_dir)
760+
proj_dir = canon_path(dep%proj_dir)
761+
call set_value(ptr, "proj-dir", proj_dir)
752762
if (allocated(dep%git)) then
753763
call set_value(ptr, "git", dep%git%url)
754764
if (allocated(dep%git%object)) then

0 commit comments

Comments
 (0)