aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorLKedward <laurence.kedward@bristol.ac.uk>2020-09-29 09:36:51 +0100
committerLKedward <laurence.kedward@bristol.ac.uk>2020-09-29 09:36:51 +0100
commita82a07155261116fc15947d1fbf7d3eaa85af103 (patch)
treed610b8a49d9736f384a34acc7c36bc87211cdf44
parent0fde6016d381466e33e4f4ba9281ed11e72d0cb8 (diff)
downloadfpm-a82a07155261116fc15947d1fbf7d3eaa85af103.tar.gz
fpm-a82a07155261116fc15947d1fbf7d3eaa85af103.zip
Add: path canonicalizer for path comparison
Returns canonical path form with redundant artifacts.
-rw-r--r--fpm/src/fpm_filesystem.f9091
1 files changed, 90 insertions, 1 deletions
diff --git a/fpm/src/fpm_filesystem.f90 b/fpm/src/fpm_filesystem.f90
index 91baba1..0ef844f 100644
--- a/fpm/src/fpm_filesystem.f90
+++ b/fpm/src/fpm_filesystem.f90
@@ -5,7 +5,7 @@ module fpm_filesystem
use fpm_strings, only: f_string, string_t, split
implicit none
private
- public :: basename, dirname, is_dir, join_path, number_of_rows, read_lines, list_files,&
+ public :: basename, canon_path, dirname, is_dir, join_path, number_of_rows, read_lines, list_files,&
mkdir, exists, get_temp_filename, windows_path
integer, parameter :: LINE_BUFFER_LEN = 1000
@@ -40,6 +40,76 @@ function basename(path,suffix) result (base)
end function basename
+function canon_path(path) result(canon)
+ ! Canonicalize path for comparison
+ ! Handles path string redundancies
+ ! Does not test existence of path
+ !
+ ! To be replaced by realpath/_fullname in stdlib_os
+ !
+ character(*), intent(in) :: path
+ character(:), allocatable :: canon
+
+ integer :: i, j
+ integer :: iback
+ character(len(path)) :: nixpath
+ character(len(path)) :: temp
+
+ nixpath = unix_path(path)
+
+ j = 1
+ do i=1,len(nixpath)
+
+ ! Skip back to last directory for '/../'
+ if (i > 4) then
+
+ if (nixpath(i-3:i) == '/../') then
+
+ iback = scan(nixpath(1:i-4),'/',back=.true.)
+ if (iback > 0) then
+ j = iback + 1
+ cycle
+ end if
+
+ end if
+
+ end if
+
+ if (i > 1 .and. j > 1) then
+
+ ! Ignore current directory reference
+ if (nixpath(i-1:i) == './') then
+
+ j = j - 1
+ cycle
+
+ end if
+
+ ! Ignore repeated separators
+ if (nixpath(i-1:i) == '//') then
+
+ cycle
+
+ end if
+
+ ! Do NOT include trailing slash
+ if (i == len(nixpath) .and. nixpath(i:i) == '/') then
+ cycle
+ end if
+
+ end if
+
+
+ temp(j:j) = nixpath(i:i)
+ j = j + 1
+
+ end do
+
+ canon = temp(1:j-1)
+
+end function canon_path
+
+
function dirname(path) result (dir)
! Extract dirname from path
!
@@ -287,4 +357,23 @@ function windows_path(path) result(winpath)
end function windows_path
+
+function unix_path(path) result(nixpath)
+ ! Replace file system separators for unix
+ !
+ character(*), intent(in) :: path
+ character(:), allocatable :: nixpath
+
+ integer :: idx
+
+ nixpath = path
+
+ idx = index(nixpath,'\')
+ do while(idx > 0)
+ nixpath(idx:idx) = '/'
+ idx = index(nixpath,'\')
+ end do
+
+end function unix_path
+
end module fpm_filesystem