56
56
! > Currenly ignored. First come, first serve.
57
57
module fpm_dependency
58
58
use , intrinsic :: iso_fortran_env, only : output_unit
59
+ use fpm_environment, only : get_os_type, OS_WINDOWS
59
60
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
61
62
use fpm_git, only : git_target_revision, git_target_default, git_revision
62
63
use fpm_manifest, only : package_config_t, dependency_config_t, &
63
64
get_package_data
@@ -634,6 +635,7 @@ subroutine load_from_toml(self, table, error)
634
635
type (error_t), allocatable , intent (out ) :: error
635
636
636
637
integer :: ndep, ii
638
+ logical :: unix
637
639
character (len= :), allocatable :: version, url, obj, rev, proj_dir
638
640
type (toml_key), allocatable :: list(:)
639
641
type (toml_table), pointer :: ptr
@@ -646,6 +648,8 @@ subroutine load_from_toml(self, table, error)
646
648
call resize(self% dep, ndep + ndep/ 2 + size (list))
647
649
end if
648
650
651
+ unix = get_os_type() /= OS_WINDOWS
652
+
649
653
do ii = 1 , size (list)
650
654
call get_value(table, list(ii)% key, ptr)
651
655
call get_value(ptr, " version" , version)
@@ -657,7 +661,11 @@ subroutine load_from_toml(self, table, error)
657
661
self% ndep = self% ndep + 1
658
662
associate(dep = > self% dep(self% ndep))
659
663
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
661
669
dep% done = .false.
662
670
if (allocated (version)) then
663
671
if (.not. allocated (dep% version)) allocate (dep% version)
@@ -737,6 +745,7 @@ subroutine dump_to_toml(self, table, error)
737
745
738
746
integer :: ii
739
747
type (toml_table), pointer :: ptr
748
+ character (len= :), allocatable :: proj_dir
740
749
741
750
do ii = 1 , self% ndep
742
751
associate(dep = > self% dep(ii))
@@ -748,7 +757,8 @@ subroutine dump_to_toml(self, table, error)
748
757
if (allocated (dep% version)) then
749
758
call set_value(ptr, " version" , char (dep% version))
750
759
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)
752
762
if (allocated (dep% git)) then
753
763
call set_value(ptr, " git" , dep% git% url)
754
764
if (allocated (dep% git% object)) then
0 commit comments