aboutsummaryrefslogtreecommitdiff
path: root/test/fpm_test/test_filesystem.f90
diff options
context:
space:
mode:
authorSebastian Ehlert <28669218+awvwgk@users.noreply.github.com>2021-03-31 16:13:58 +0200
committerGitHub <noreply@github.com>2021-03-31 16:13:58 +0200
commitd9dc9f2ae5f196c15a7d35cddabc805c40ff86ce (patch)
tree6f61952c630b023edec391daae2747063703d489 /test/fpm_test/test_filesystem.f90
parent5422ec57f4081bf2225f5dde5cc07999bf8010f9 (diff)
downloadfpm-d9dc9f2ae5f196c15a7d35cddabc805c40ff86ce.tar.gz
fpm-d9dc9f2ae5f196c15a7d35cddabc805c40ff86ce.zip
Phase out Haskell fpm (#420)
- remove bootstrap directory from repository - remove stack-build from CI workflow - move Fortran fpm to project root - adjust install script and bootstrap instructions
Diffstat (limited to 'test/fpm_test/test_filesystem.f90')
-rw-r--r--test/fpm_test/test_filesystem.f90106
1 files changed, 106 insertions, 0 deletions
diff --git a/test/fpm_test/test_filesystem.f90 b/test/fpm_test/test_filesystem.f90
new file mode 100644
index 0000000..5a7e18a
--- /dev/null
+++ b/test/fpm_test/test_filesystem.f90
@@ -0,0 +1,106 @@
+module test_filesystem
+ use testsuite, only : new_unittest, unittest_t, error_t, test_failed
+ use fpm_filesystem, only: canon_path
+ implicit none
+ private
+
+ public :: collect_filesystem
+
+contains
+
+
+ !> Collect all exported unit tests
+ subroutine collect_filesystem(testsuite)
+
+ !> Collection of tests
+ type(unittest_t), allocatable, intent(out) :: testsuite(:)
+
+ testsuite = [ &
+ & new_unittest("canon-path", test_canon_path) &
+ ]
+
+ end subroutine collect_filesystem
+
+
+ subroutine test_canon_path(error)
+
+ !> Error handling
+ type(error_t), allocatable, intent(out) :: error
+
+ call check_string(error, &
+ & canon_path("git/project/src/origin"), "git/project/src/origin")
+ if (allocated(error)) return
+
+ call check_string(error, &
+ & canon_path("./project/src/origin"), "project/src/origin")
+ if (allocated(error)) return
+
+ call check_string(error, &
+ & canon_path("./project/src///origin/"), "project/src/origin")
+ if (allocated(error)) return
+
+ call check_string(error, &
+ & canon_path("../project/./src/origin/"), "../project/src/origin")
+ if (allocated(error)) return
+
+ call check_string(error, &
+ & canon_path("/project//src/origin/"), "/project/src/origin")
+ if (allocated(error)) return
+
+ call check_string(error, &
+ & canon_path("/project/src/../origin/"), "/project/origin")
+ if (allocated(error)) return
+
+ call check_string(error, &
+ & canon_path("/project/src/../origin/.."), "/project")
+ if (allocated(error)) return
+
+ call check_string(error, &
+ & canon_path("/project/src//../origin/."), "/project/origin")
+ if (allocated(error)) return
+
+ call check_string(error, &
+ & canon_path("../project/src/./../origin/."), "../project/origin")
+ if (allocated(error)) return
+
+ call check_string(error, &
+ & canon_path("../project/src/../../../origin/."), "../../origin")
+ if (allocated(error)) return
+
+ call check_string(error, &
+ & canon_path("/../.."), "/")
+ if (allocated(error)) return
+
+ call check_string(error, &
+ & canon_path("././././././/////a/b/.///././////.///c/../../../"), ".")
+ if (allocated(error)) return
+
+ call check_string(error, &
+ & canon_path("/./././././/////a/b/.///././////.///c/../../../"), "/")
+ if (allocated(error)) return
+
+ end subroutine test_canon_path
+
+
+ !> Check a character variable against a reference value
+ subroutine check_string(error, actual, expected)
+
+ !> Error handling
+ type(error_t), allocatable, intent(out) :: error
+
+ !> Actual string value
+ character(len=*), intent(in) :: actual
+
+ !> Expected string value
+ character(len=*), intent(in) :: expected
+
+ if (actual /= expected) then
+ call test_failed(error, &
+ "Character value missmatch "//&
+ "expected '"//expected//"' but got '"//actual//"'")
+ end if
+
+ end subroutine check_string
+
+
+end module test_filesystem