path-0.9.2/src/0000755000000000000000000000000014162173754011445 5ustar0000000000000000path-0.9.2/src/Path/0000755000000000000000000000000014162271567012342 5ustar0000000000000000path-0.9.2/src/Path/Internal/0000755000000000000000000000000014162173754014115 5ustar0000000000000000path-0.9.2/test/0000755000000000000000000000000014162173754011635 5ustar0000000000000000path-0.9.2/test/Common/0000755000000000000000000000000014162173754013065 5ustar0000000000000000path-0.9.2/test/Path/0000755000000000000000000000000014162173754012531 5ustar0000000000000000path-0.9.2/src/Path.hs0000644000000000000000000000064414162173754012701 0ustar0000000000000000-- | This library provides a well-typed representation of paths in a filesystem -- directory tree. -- -- Both "Path.Posix" and "Path.Windows" provide the same interface. This -- module will reexport the appropriate module for your platform. {-# LANGUAGE CPP #-} #if defined(mingw32_HOST_OS) module Path(module Path.Windows) where import Path.Windows #else module Path(module Path.Posix) where import Path.Posix #endif path-0.9.2/src/Path/Posix.hs0000644000000000000000000000014714162173754014001 0ustar0000000000000000{-# LANGUAGE CPP #-} #define PLATFORM_NAME Posix #define IS_WINDOWS False #include "Include.hs" path-0.9.2/src/Path/Windows.hs0000644000000000000000000000015014162173754014323 0ustar0000000000000000{-# LANGUAGE CPP #-} #define PLATFORM_NAME Windows #define IS_WINDOWS True #include "Include.hs" path-0.9.2/src/Path/Internal.hs0000644000000000000000000000035014162173754014447 0ustar0000000000000000{-# LANGUAGE CPP #-} #if defined(mingw32_HOST_OS) module Path.Internal(module Path.Internal.Windows) where import Path.Internal.Windows #else module Path.Internal(module Path.Internal.Posix) where import Path.Internal.Posix #endif path-0.9.2/src/Path/Internal/Posix.hs0000644000000000000000000000014714162173754015555 0ustar0000000000000000{-# LANGUAGE CPP #-} #define PLATFORM_NAME Posix #define IS_WINDOWS False #include "Include.hs" path-0.9.2/src/Path/Internal/Windows.hs0000644000000000000000000000015014162173754016077 0ustar0000000000000000{-# LANGUAGE CPP #-} #define PLATFORM_NAME Windows #define IS_WINDOWS True #include "Include.hs" path-0.9.2/test/ValidityTest.hs0000644000000000000000000002637614162173754014634 0ustar0000000000000000{-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeApplications #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-} -- | Test suite. module Main where import Data.Maybe import Path import Path.Internal import Test.Hspec import Test.Hspec.QuickCheck import Test.QuickCheck import Test.Validity import Path.Gen -- | Test suite entry point, returns exit failure if any test fails. main :: IO () main = hspec spec -- | Test suite. spec :: Spec spec = modifyMaxShrinks (const 100) $ parallel $ do genValidSpec @(Path Abs File) shrinkValidSpec @(Path Abs File) genValidSpec @(Path Rel File) shrinkValidSpec @(Path Rel File) genValidSpec @(Path Abs Dir) shrinkValidSpec @(Path Abs Dir) genValidSpec @(Path Rel Dir) shrinkValidSpec @(Path Rel Dir) genValidSpec @(SomeBase Dir) shrinkValidSpec @(SomeBase Dir) genValidSpec @(SomeBase File) shrinkValidSpec @(SomeBase File) describe "Parsing" $ do describe "Path Abs Dir" (parserSpec parseAbsDir) describe "Path Rel Dir" (parserSpec parseRelDir) describe "Path Abs File" (parserSpec parseAbsFile) describe "Path Rel File" (parserSpec parseRelFile) describe "SomeBase Dir" (parserSpec parseSomeDir) describe "SomeBase file" (parserSpec parseSomeFile) describe "Operations" $ do describe "()" operationAppend describe "stripProperPrefix" operationStripDir describe "isProperPrefixOf" operationIsParentOf describe "parent" operationParent describe "filename" operationFilename describe "dirname" operationDirname describe "Extensions" extensionsSpec -- | The 'filename' operation. operationFilename :: Spec operationFilename = do forAllDirs "filename (parent $(mkRelFile filename)) == filename $(mkRelFile filename)" $ \parent -> forAllValid $ \file -> filename (parent file) `shouldBe` filename file forSomeDirs "filename (some:parent $(mkRelFile filename)) == filename $(mkRelFile filename)" $ \someParent -> forAllValid $ \file -> prjSomeBase filename (mapSomeBase ( file) someParent) `shouldBe` filename file it "produces a valid path on when passed a valid absolute path" $ do producesValid (filename :: Path Abs File -> Path Rel File) it "produces a valid path on when passed a valid relative path" $ do producesValid (filename :: Path Rel File -> Path Rel File) it "produces a valid filename when passed some valid base path" $ producesValid (prjSomeBase filename :: SomeBase File -> Path Rel File) -- | The 'dirname' operation. operationDirname :: Spec operationDirname = do forAllDirs "dirname parent $(mkRelDir dirname)) == dirname $(mkRelDir dirname)" $ \parent -> forAllValid $ \dir -> if dir == Path [] then pure () else dirname (parent dir) `shouldBe` dirname dir forSomeDirs "dirname (some:parent $(mkRelDir dirname)) == dirname $(mkRelDir dirname)" $ \someParent -> forAllValid $ \dir -> if dir == Path [] then pure () else prjSomeBase dirname (mapSomeBase ( dir) someParent) `shouldBe` dirname dir it "produces a valid path on when passed a valid absolute path" $ do producesValid (dirname :: Path Abs Dir -> Path Rel Dir) it "produces a valid path on when passed a valid relative path" $ do producesValid (dirname :: Path Rel Dir -> Path Rel Dir) it "produces a valid path when passed some valid longer path" $ producesValid (prjSomeBase dirname :: SomeBase Dir -> Path Rel Dir) -- | The 'parent' operation. operationParent :: Spec operationParent = do it "produces a valid path on when passed a valid file path" $ do producesValid (parent :: Path Abs File -> Path Abs Dir) it "produces a valid path on when passed a valid directory path" $ do producesValid (parent :: Path Abs Dir -> Path Abs Dir) it "produces a valid path on when passed a valid abs file path" $ do producesValid (parent :: Path Abs File -> Path Abs Dir) it "produces a valid path on when passed a valid rel file path" $ do producesValid (parent :: Path Rel File -> Path Rel Dir) it "produces a valid path on when passed a valid abs directory path" $ do producesValid (parent :: Path Abs Dir -> Path Abs Dir) it "produces a valid path on when passed a valid rel directory path" $ do producesValid (parent :: Path Rel Dir -> Path Rel Dir) -- | The 'isProperPrefixOf' operation. operationIsParentOf :: Spec operationIsParentOf = do forAllParentsAndChildren "isProperPrefixOf parent (parent child)" $ \parent child -> if child == Path [] then True -- TODO do we always need this condition? else isProperPrefixOf parent (parent child) -- | The 'stripProperPrefix' operation. operationStripDir :: Spec operationStripDir = do forAllParentsAndChildren "stripProperPrefix parent (parent child) = child" $ \parent child -> if child == Path [] then pure () -- TODO do we always need this condition? else stripProperPrefix parent (parent child) `shouldBe` Just child it "produces a valid path on when passed a valid absolute file paths" $ do producesValid2 (stripProperPrefix :: Path Abs Dir -> Path Abs File -> Maybe (Path Rel File)) it "produces a valid path on when passed a valid absolute directory paths" $ do producesValid2 (stripProperPrefix :: Path Abs Dir -> Path Abs Dir -> Maybe (Path Rel Dir)) it "produces a valid path on when passed a valid relative file paths" $ do producesValid2 (stripProperPrefix :: Path Rel Dir -> Path Rel File -> Maybe (Path Rel File)) it "produces a valid path on when passed a valid relative directory paths" $ do producesValid2 (stripProperPrefix :: Path Rel Dir -> Path Rel Dir -> Maybe (Path Rel Dir)) -- | The '' operation. operationAppend :: Spec operationAppend = do it "produces a valid path on when creating valid absolute file paths" $ do producesValid2 (() :: Path Abs Dir -> Path Rel File -> Path Abs File) it "produces a valid path on when creating valid absolute directory paths" $ do producesValid2 (() :: Path Abs Dir -> Path Rel Dir -> Path Abs Dir) it "produces a valid path on when creating valid relative file paths" $ do producesValid2 (() :: Path Rel Dir -> Path Rel File -> Path Rel File) it "produces a valid path on when creating valid relative directory paths" $ do producesValid2 (() :: Path Rel Dir -> Path Rel Dir -> Path Rel Dir) extensionsSpec :: Spec extensionsSpec = do let addExtGensValidFile p = case addExtension p $(mkRelFile "x") of Nothing -> True Just _ -> case parseRelFile p of Nothing -> False _ -> True it "if addExtension a b succeeds then parseRelFile b succeeds - 1" $ forAll genFilePath addExtGensValidFile -- skew the generated path towards a valid extension by prefixing a "." it "if addExtension a b succeeds then parseRelFile b succeeds - 2" $ forAll genFilePath $ addExtGensValidFile . ("." ++) forAllFiles "Adding an extension is like adding the extension to the end if it succeeds" $ \file -> forAllValid $ \ext -> case addExtension ext file of Nothing -> pure () -- Fine Just p -> toFilePath p `shouldBe` toFilePath file ++ ext forAllFiles "splitExtension output joins to result in the original file" $ \file -> case splitExtension file of Nothing -> pure () Just (f, ext) -> toFilePath f ++ ext `shouldBe` toFilePath file forAllFiles "splitExtension generates a valid filename and valid extension" $ \file -> case splitExtension file of Nothing -> True Just (f, ext) -> case parseRelFile ext of Nothing -> False Just _ -> case parseRelFile (toFilePath f) of Nothing -> case parseAbsFile (toFilePath f) of Nothing -> False Just _ -> True Just _ -> True forAllFiles "splitExtension >=> uncurry addExtension . swap == return" $ \file -> case splitExtension file of Nothing -> pure () Just (f, ext) -> addExtension ext f `shouldBe` Just file forAllFiles "an extension that was added can be split off again" $ \file -> forAllValid $ \ext -> case addExtension ext file of Nothing -> pure () -- Fine Just p -> splitExtension p `shouldBe` Just (file, ext) forAllFiles "fileExtension == (fmap snd) . splitExtension" $ \file -> case splitExtension file of Nothing -> pure () Just (_, ext) -> fileExtension file `shouldBe` Just ext forAllFiles "an extension that was added is considered to be there" $ \file -> forAllValid $ \ext -> case addExtension ext file of Nothing -> pure () -- Fine Just p -> fileExtension p `shouldBe` Just ext forAllFiles "(fileExtension >=> flip replaceExtension file) file == return file" $ \file -> case fileExtension file of Nothing -> pure () Just ext -> replaceExtension ext file `shouldBe` Just file forAllFiles :: Testable a => String -> (forall b. Path b File -> a) -> Spec forAllFiles n func = do it (unwords [n, "Path Abs File"]) $ forAllValid $ \(file :: Path Abs File) -> func file it (unwords [n, "Path Rel File"]) $ forAllValid $ \(file :: Path Rel File) -> func file forAllDirs :: Testable a => String -> (forall b. Path b Dir -> a) -> Spec forAllDirs n func = do it (unwords [n, "Path Abs Dir"]) $ forAllValid $ \(parent :: Path Abs Dir) -> func parent it (unwords [n, "Path Rel Dir"]) $ forAllValid $ \(parent :: Path Rel Dir) -> func parent forSomeDirs :: Testable a => String -> (SomeBase Dir -> a) -> Spec forSomeDirs n func = do it (unwords [n, "SomeBase Dir"]) $ forAllValid $ \(parent :: SomeBase Dir) -> func parent forAllParentsAndChildren :: Testable a => String -> (forall b t. Path b Dir -> Path Rel t -> a) -> Spec forAllParentsAndChildren n func = do it (unwords [n, "Path Abs Dir", "Path Rel Dir"]) $ forAllValid $ \(parent :: Path Abs Dir) -> forAllValid $ \(child :: Path Rel Dir) -> func parent child it (unwords [n, "Path Rel Dir", "Path Rel Dir"]) $ forAllValid $ \(parent :: Path Rel Dir) -> forAllValid $ \(child :: Path Rel Dir) -> func parent child it (unwords [n, "Path Abs Dir", "Path Rel File"]) $ forAllValid $ \(parent :: Path Abs Dir) -> forAllValid $ \(child :: Path Rel File) -> func parent child it (unwords [n, "Path Rel Dir", "Path Rel File"]) $ forAllValid $ \(parent :: Path Rel Dir) -> forAllValid $ \(child :: Path Rel File) -> func parent child forAllPaths :: Testable a => String -> (forall b t. Path b t -> a) -> Spec forAllPaths n func = do it (unwords [n, "Path Abs Dir"]) $ forAllValid $ \(path :: Path Abs Dir) -> func path it (unwords [n, "Path Rel Dir"]) $ forAllValid $ \(path :: Path Rel Dir) -> func path it (unwords [n, "Path Abs File"]) $ forAllValid $ \(path :: Path Abs File) -> func path it (unwords [n, "Path Rel File"]) $ forAllValid $ \(path :: Path Rel File) -> func path parserSpec :: (Show p, Validity p) => (FilePath -> Maybe p) -> Spec parserSpec parser = it "Produces valid paths when it succeeds" $ forAllShrink genFilePath shrinkValid $ \path -> case parser path of Nothing -> pure () Just p -> case prettyValidate p of Left err -> expectationFailure err Right _ -> pure () path-0.9.2/test/Path/Gen.hs0000644000000000000000000001003514162173754013575 0ustar0000000000000000{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Path.Gen where import Data.Functor import Prelude import Path import Path.Internal import qualified System.FilePath as FilePath import Data.GenValidity import Data.List (isSuffixOf, isInfixOf) import Data.Maybe (isJust, mapMaybe) import Test.QuickCheck instance Validity (Path Abs File) where validate p@(Path fp) = mconcat [ validateCommon p, validateAbs p, validateFile p, declare "The path can be identically parsed as an absolute file path." $ parseAbsFile fp == Just p ] instance Validity (Path Rel File) where validate p@(Path fp) = mconcat [ validateCommon p, validateRel p, validateFile p, declare "The path can be identically parsed as a relative file path." $ parseRelFile fp == Just p ] instance Validity (Path Abs Dir) where validate p@(Path fp) = mconcat [ validateCommon p, validateAbs p, validateDirectory p, declare "The path can be identically parsed as an absolute directory path." $ parseAbsDir fp == Just p ] instance Validity (Path Rel Dir) where validate p@(Path fp) = mconcat [ validateCommon p, validateRel p, validateDirectory p, declare "The path can be identically parsed as a relative directory path if it's not empty." $ parseRelDir fp == Just p || fp == "" ] instance Validity (SomeBase Dir) instance Validity (SomeBase File) validateCommon :: Path b t -> Validation validateCommon (Path fp) = mconcat [ declare "System.FilePath considers the path valid if it's not empty." $ FilePath.isValid fp || fp == "" , declare "The path does not contain a '..' path component." $ not (hasParentDir fp) ] validateDirectory :: Path b Dir -> Validation validateDirectory (Path fp) = mconcat [ declare "The path has a trailing path separator if it's not empty." $ FilePath.hasTrailingPathSeparator fp || fp == "" ] validateFile :: Path b File -> Validation validateFile (Path fp) = mconcat [ declare "The path has no trailing path separator." $ not (FilePath.hasTrailingPathSeparator fp) , declare "The path does not equal \".\"" $ fp /= "." , declare "The path does not end in /." $ not ("/." `isSuffixOf` fp) ] validateAbs :: Path Abs t -> Validation validateAbs (Path fp) = mconcat [ declare "The path is absolute." $ FilePath.isAbsolute fp ] validateRel :: Path Rel t -> Validation validateRel (Path fp) = mconcat [ declare "The path is relative." $ FilePath.isRelative fp ] instance GenValid (Path Abs File) where genValid = (Path . ('/' :) <$> genFilePath) `suchThat` isValid shrinkValid = filter isValid . shrinkValidWith parseAbsFile instance GenValid (Path Abs Dir) where genValid = (Path . ('/' :) . (++ "/") <$> genFilePath) `suchThat` isValid shrinkValid = filter isValid . shrinkValidWith parseAbsDir instance GenValid (Path Rel File) where genValid = (Path <$> genFilePath) `suchThat` isValid shrinkValid = filter isValid . shrinkValidWith parseRelFile instance GenValid (Path Rel Dir) where genValid = (Path . (++ "/") <$> genFilePath) `suchThat` isValid shrinkValid = filter isValid . shrinkValidWith parseRelDir instance GenValid (SomeBase Dir) where genValid = genValidStructurallyWithoutExtraChecking shrinkValid = shrinkValidStructurallyWithoutExtraFiltering instance GenValid (SomeBase File) where genValid = genValidStructurallyWithoutExtraChecking shrinkValid = shrinkValidStructurallyWithoutExtraFiltering -- | Generates 'FilePath's with a high occurence of @'.'@, @'\/'@ and -- @'\\'@ characters. The resulting 'FilePath's are not guaranteed to -- be valid. genFilePath :: Gen FilePath genFilePath = listOf genPathyChar genPathyChar :: Gen Char genPathyChar = frequency [(2, choose (minBound, maxBound)), (1, elements "./\\")] shrinkValidWith :: (FilePath -> Maybe (Path a b)) -> Path a b -> [Path a b] shrinkValidWith fun (Path f) = filter (/= (Path f)) . mapMaybe fun $ shrinkValid f path-0.9.2/test/Main.hs0000644000000000000000000000042114162173754013052 0ustar0000000000000000module Main (main) where import qualified Windows import qualified Posix import Test.Hspec -- | Test suite entry point, returns exit failure if any test fails. main :: IO () main = hspec $ do describe "Path.Windows" Windows.spec describe "Path.Posix" Posix.spec path-0.9.2/test/Posix.hs0000644000000000000000000002700214162173754013274 0ustar0000000000000000{-# LANGUAGE LambdaCase #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE QuasiQuotes #-} -- | Test suite. module Posix (spec) where import Control.Applicative import Control.Monad import Data.Aeson import qualified Data.ByteString.Lazy.Char8 as LBS import Data.Maybe import Path.Posix import Path.Internal.Posix import Test.Hspec import Common.Posix (extensionOperations) -- | Test suite (Posix version). spec :: Spec spec = do describe "Parsing: Path Abs Dir" parseAbsDirSpec describe "Parsing: Path Rel Dir" parseRelDirSpec describe "Parsing: Path Abs File" parseAbsFileSpec describe "Parsing: Path Rel File" parseRelFileSpec describe "Operations: ()" operationAppend describe "Operations: toFilePath" operationToFilePath describe "Operations: stripProperPrefix" operationStripProperPrefix describe "Operations: isProperPrefixOf" operationIsProperPrefixOf describe "Operations: parent" operationParent describe "Operations: filename" operationFilename describe "Operations: dirname" operationDirname describe "Operations: extensions" (extensionOperations "/") describe "Restrictions" restrictions describe "Aeson Instances" aesonInstances describe "QuasiQuotes" quasiquotes -- | Restricting the input of any tricks. restrictions :: Spec restrictions = do -- These ~ related ones below are now lifted: -- https://github.com/chrisdone/path/issues/19 parseSucceeds "~/" (Path "~/") parseSucceeds "~/foo" (Path "~/foo/") parseSucceeds "~/foo/bar" (Path "~/foo/bar/") parseSucceeds "a.." (Path "a../") parseSucceeds "..a" (Path "..a/") -- parseFails "../" parseFails ".." parseFails "/.." parseFails "/foo/../bar/" parseFails "/foo/bar/.." where parseFails x = it (show x ++ " should be rejected") (isNothing (void (parseAbsDir x) <|> void (parseRelDir x) <|> void (parseAbsFile x) <|> void (parseRelFile x))) parseSucceeds x with = parserTest parseRelDir x (Just with) -- | The 'dirname' operation. operationDirname :: Spec operationDirname = do it "dirname ($(mkAbsDir parent) $(mkRelFile dirname)) == dirname $(mkRelFile dirname) (unit test)" (dirname ($(mkAbsDir "/home/chris/") $(mkRelDir "bar")) == dirname $(mkRelDir "bar")) it "dirname ($(mkRelDir parent) $(mkRelFile dirname)) == dirname $(mkRelFile dirname) (unit test)" (dirname ($(mkRelDir "home/chris/") $(mkRelDir "bar")) == dirname $(mkRelDir "bar")) it "dirname / must be a Rel path" ((parseAbsDir $ show $ dirname (fromJust (parseAbsDir "/")) :: Maybe (Path Abs Dir)) == Nothing) -- | The 'filename' operation. operationFilename :: Spec operationFilename = do it "filename ($(mkAbsDir parent) $(mkRelFile filename)) == filename $(mkRelFile filename) (unit test)" (filename ($(mkAbsDir "/home/chris/") $(mkRelFile "bar.txt")) == filename $(mkRelFile "bar.txt")) it "filename ($(mkRelDir parent) $(mkRelFile filename)) == filename $(mkRelFile filename) (unit test)" (filename ($(mkRelDir "home/chris/") $(mkRelFile "bar.txt")) == filename $(mkRelFile "bar.txt")) -- | The 'parent' operation. operationParent :: Spec operationParent = do it "parent (parent child) == parent" (parent ($(mkAbsDir "/foo") $(mkRelDir "bar")) == $(mkAbsDir "/foo")) it "parent \"/\" == \"/\"" (parent $(mkAbsDir "/") == $(mkAbsDir "/")) it "parent \"/x\" == \"/\"" (parent $(mkAbsDir "/x") == $(mkAbsDir "/")) it "parent \"x\" == \".\"" (parent $(mkRelDir "x") == $(mkRelDir ".")) it "parent \".\" == \".\"" (parent $(mkRelDir ".") == $(mkRelDir ".")) -- | The 'isProperPrefixOf' operation. operationIsProperPrefixOf :: Spec operationIsProperPrefixOf = do it "isProperPrefixOf parent (parent child) (absolute)" (isProperPrefixOf $(mkAbsDir "///bar/") ($(mkAbsDir "///bar/") $(mkRelFile "bar/foo.txt"))) it "isProperPrefixOf parent (parent child) (relative)" (isProperPrefixOf $(mkRelDir "bar/") ($(mkRelDir "bar/") $(mkRelFile "bob/foo.txt"))) it "not (x `isProperPrefixOf` x)" (not (isProperPrefixOf $(mkRelDir "x") $(mkRelDir "x"))) it "not (/ `isProperPrefixOf` /)" (not (isProperPrefixOf $(mkAbsDir "/") $(mkAbsDir "/"))) -- | The 'stripProperPrefix' operation. operationStripProperPrefix :: Spec operationStripProperPrefix = do it "stripProperPrefix parent (parent child) = child (unit test)" (stripProperPrefix $(mkAbsDir "///bar/") ($(mkAbsDir "///bar/") $(mkRelFile "bar/foo.txt")) == Just $(mkRelFile "bar/foo.txt")) it "stripProperPrefix parent (parent child) = child (unit test)" (stripProperPrefix $(mkRelDir "bar/") ($(mkRelDir "bar/") $(mkRelFile "bob/foo.txt")) == Just $(mkRelFile "bob/foo.txt")) it "stripProperPrefix parent parent = _|_" (stripProperPrefix $(mkAbsDir "/home/chris/foo") $(mkAbsDir "/home/chris/foo") == Nothing) -- | The '' operation. operationAppend :: Spec operationAppend = do it "AbsDir + RelDir = AbsDir" ($(mkAbsDir "/home/") $(mkRelDir "chris") == $(mkAbsDir "/home/chris/")) it "AbsDir + RelFile = AbsFile" ($(mkAbsDir "/home/") $(mkRelFile "chris/test.txt") == $(mkAbsFile "/home/chris/test.txt")) it "RelDir + RelDir = RelDir" ($(mkRelDir "home/") $(mkRelDir "chris") == $(mkRelDir "home/chris")) it ". + . = ." ($(mkRelDir "./") $(mkRelDir ".") == $(mkRelDir ".")) it ". + x = x" ($(mkRelDir ".") $(mkRelDir "x") == $(mkRelDir "x")) it "x + . = x" ($(mkRelDir "x") $(mkRelDir "./") == $(mkRelDir "x")) it "RelDir + RelFile = RelFile" ($(mkRelDir "home/") $(mkRelFile "chris/test.txt") == $(mkRelFile "home/chris/test.txt")) operationToFilePath :: Spec operationToFilePath = do it "toFilePath $(mkRelDir \".\") == \"./\"" (toFilePath $(mkRelDir ".") == "./") it "show $(mkRelDir \".\") == \"\\\"./\\\"\"" (show $(mkRelDir ".") == "\"./\"") -- | Tests for the tokenizer. parseAbsDirSpec :: Spec parseAbsDirSpec = do failing "" failing "./" failing "foo.txt" succeeding "/" (Path "/") succeeding "//" (Path "/") succeeding "///foo//bar//mu/" (Path "/foo/bar/mu/") succeeding "///foo//bar////mu" (Path "/foo/bar/mu/") succeeding "///foo//bar/.//mu" (Path "/foo/bar/mu/") where failing x = parserTest parseAbsDir x Nothing succeeding x with = parserTest parseAbsDir x (Just with) -- | Tests for the tokenizer. parseRelDirSpec :: Spec parseRelDirSpec = do failing "" failing "/" failing "//" succeeding "~/" (Path "~/") -- https://github.com/chrisdone/path/issues/19 failing "/" succeeding "./" (Path "") succeeding "././" (Path "") failing "//" failing "///foo//bar//mu/" failing "///foo//bar////mu" failing "///foo//bar/.//mu" succeeding "..." (Path ".../") succeeding "foo.bak" (Path "foo.bak/") succeeding "./foo" (Path "foo/") succeeding "././foo" (Path "foo/") succeeding "./foo/./bar" (Path "foo/bar/") succeeding "foo//bar//mu//" (Path "foo/bar/mu/") succeeding "foo//bar////mu" (Path "foo/bar/mu/") succeeding "foo//bar/.//mu" (Path "foo/bar/mu/") where failing x = parserTest parseRelDir x Nothing succeeding x with = parserTest parseRelDir x (Just with) -- | Tests for the tokenizer. parseAbsFileSpec :: Spec parseAbsFileSpec = do failing "" failing "./" failing "/." failing "/foo/bar/." failing "~/" failing "./foo.txt" failing "/" failing "//" failing "///foo//bar//mu/" succeeding "/..." (Path "/...") succeeding "/foo.txt" (Path "/foo.txt") succeeding "///foo//bar////mu.txt" (Path "/foo/bar/mu.txt") succeeding "///foo//bar/.//mu.txt" (Path "/foo/bar/mu.txt") where failing x = parserTest parseAbsFile x Nothing succeeding x with = parserTest parseAbsFile x (Just with) -- | Tests for the tokenizer. parseRelFileSpec :: Spec parseRelFileSpec = do failing "" failing "/" failing "//" failing "~/" failing "/" failing "./" failing "a/." failing "a/../b" failing "a/.." failing "../foo.txt" failing "//" failing "///foo//bar//mu/" failing "///foo//bar////mu" failing "///foo//bar/.//mu" succeeding "a.." (Path "a..") succeeding "..." (Path "...") succeeding "foo.txt" (Path "foo.txt") succeeding "./foo.txt" (Path "foo.txt") succeeding "././foo.txt" (Path "foo.txt") succeeding "./foo/./bar.txt" (Path "foo/bar.txt") succeeding "foo//bar//mu.txt" (Path "foo/bar/mu.txt") succeeding "foo//bar////mu.txt" (Path "foo/bar/mu.txt") succeeding "foo//bar/.//mu.txt" (Path "foo/bar/mu.txt") where failing x = parserTest parseRelFile x Nothing succeeding x with = parserTest parseRelFile x (Just with) -- | Parser test. parserTest :: (Show a1,Show a,Eq a1) => (a -> Maybe a1) -> a -> Maybe a1 -> SpecWith () parserTest parser input expected = it ((case expected of Nothing -> "Failing: " Just{} -> "Succeeding: ") ++ "Parsing " ++ show input ++ " " ++ case expected of Nothing -> "should fail." Just x -> "should succeed with: " ++ show x) (actual `shouldBe` expected) where actual = parser input -- | Tests for the 'ToJSON' and 'FromJSON' instances -- -- Can't use overloaded strings due to some weird issue with bytestring-0.9.2.1 / ghc-7.4.2: -- https://travis-ci.org/sjakobi/path/jobs/138399072#L989 aesonInstances :: Spec aesonInstances = do it "Decoding \"[\"/foo/bar\"]\" as a [Path Abs Dir] should succeed." $ eitherDecode (LBS.pack "[\"/foo/bar\"]") `shouldBe` Right [Path "/foo/bar/" :: Path Abs Dir] it "Decoding \"[\"/foo/bar\"]\" as a [Path Rel Dir] should fail." $ decode (LBS.pack "[\"/foo/bar\"]") `shouldBe` (Nothing :: Maybe [Path Rel Dir]) it "Encoding \"[\"/foo/bar/mu.txt\"]\" should succeed." $ encode [Path "/foo/bar/mu.txt" :: Path Abs File] `shouldBe` (LBS.pack "[\"/foo/bar/mu.txt\"]") -- | Test QuasiQuoters. Make sure they work the same as the $(mk*) constructors. quasiquotes :: Spec quasiquotes = do it "[absdir|/|] == $(mkAbsDir \"/\")" ([absdir|/|] `shouldBe` $(mkAbsDir "/")) it "[absdir|/home|] == $(mkAbsDir \"/home\")" ([absdir|/home|] `shouldBe` $(mkAbsDir "/home")) it "[reldir|foo|] == $(mkRelDir \"foo\")" ([reldir|foo|] `shouldBe` $(mkRelDir "foo")) it "[reldir|foo/bar|] == $(mkRelDir \"foo/bar\")" ([reldir|foo/bar|] `shouldBe` $(mkRelDir "foo/bar")) it "[absfile|/home/chris/foo.txt|] == $(mkAbsFile \"/home/chris/foo.txt\")" ([absfile|/home/chris/foo.txt|] `shouldBe` $(mkAbsFile "/home/chris/foo.txt")) it "[relfile|foo|] == $(mkRelFile \"foo\")" ([relfile|foo|] `shouldBe` $(mkRelFile "foo")) it "[relfile|chris/foo.txt|] == $(mkRelFile \"chris/foo.txt\")" ([relfile|chris/foo.txt|] `shouldBe` $(mkRelFile "chris/foo.txt")) path-0.9.2/test/Windows.hs0000644000000000000000000003722714162173754013636 0ustar0000000000000000{-# LANGUAGE LambdaCase #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} -- | Test suite. module Windows (spec) where import Control.Applicative import Control.Monad import Data.Aeson import qualified Data.ByteString.Lazy.Char8 as LBS import Data.Maybe import Path.Windows import Path.Internal.Windows import Test.Hspec import Common.Windows (extensionOperations) -- | Test suite (Windows version). spec :: Spec spec = do describe "Parsing: Path Abs Dir" parseAbsDirSpec describe "Parsing: Path Rel Dir" parseRelDirSpec describe "Parsing: Path Abs File" parseAbsFileSpec describe "Parsing: Path Rel File" parseRelFileSpec describe "Operations: ()" operationAppend describe "Operations: toFilePath" operationToFilePath describe "Operations: stripProperPrefix" operationStripProperPrefix describe "Operations: isProperPrefixOf" operationIsProperPrefixOf describe "Operations: parent" operationParent describe "Operations: filename" operationFilename describe "Operations: dirname" operationDirname describe "Operations: extensions" (extensionOperations "C:\\") describe "Restrictions" restrictions describe "Aeson Instances" aesonInstances describe "QuasiQuotes" quasiquotes -- | Restricting the input of any tricks. restrictions :: Spec restrictions = do parseFails "..\\" parseFails ".." parseSucceeds "a.." (Path "a..\\") parseSucceeds "..a" (Path "..a\\") parseFails "\\.." parseFails "C:\\foo\\..\\bar\\" parseFails "C:\\foo\\bar\\.." where parseFails x = it (show x ++ " should be rejected") (isNothing (void (parseAbsDir x) <|> void (parseRelDir x) <|> void (parseAbsFile x) <|> void (parseRelFile x))) parseSucceeds x with = parserTest parseRelDir x (Just with) -- | The 'dirname' operation. operationDirname :: Spec operationDirname = do it "dirname ($(mkAbsDir parent) $(mkRelFile dirname)) == dirname $(mkRelFile dirname) (absolute)" (dirnamesShouldBeEqual ($(mkAbsDir "C:\\chris\\") $(mkRelDir "bar")) $(mkRelDir "bar")) it "dirname ($(mkRelDir parent) $(mkRelFile dirname)) == dirname $(mkRelFile dirname) (relative)" (dirnamesShouldBeEqual ($(mkRelDir "home\\chris\\") $(mkRelDir "bar")) $(mkRelDir "bar")) it "dirname ($(mkAbsDir parent) $(mkRelFile dirname)) == dirname $(mkRelFile dirname) (UNC)" (dirnamesShouldBeEqual ($(mkAbsDir "\\\\home\\chris\\") $(mkRelDir "bar")) $(mkRelDir "bar")) it "dirname ($(mkAbsDir parent) $(mkRelFile dirname)) == dirname $(mkRelFile dirname) (Unicode)" (dirnamesShouldBeEqual ($(mkAbsDir "\\\\?\\C:\\home\\chris\\") $(mkRelDir "bar")) $(mkRelDir "bar")) it "dirname $(mkRelDir .) == $(mkRelDir .)" (dirnamesShouldBeEqual $(mkRelDir ".") $(mkRelDir ".")) it "dirname C:\\ must be a Rel path" ((parseAbsDir $ show $ dirname (fromJust (parseAbsDir "C:\\")) :: Maybe (Path Abs Dir)) == Nothing) where dirnamesShouldBeEqual x y = dirname x == dirname y -- | The 'filename' operation. operationFilename :: Spec operationFilename = do it "filename ($(mkAbsDir parent) $(mkRelFile filename)) == filename $(mkRelFile filename) (absolute)" (filenamesShouldBeEqual ($(mkAbsDir "C:\\chris\\") $(mkRelFile "bar.txt")) $(mkRelFile "bar.txt")) it "filename ($(mkRelDir parent) $(mkRelFile filename)) == filename $(mkRelFile filename) (relative)" (filenamesShouldBeEqual ($(mkRelDir "home\\chris\\") $(mkRelFile "bar.txt")) $(mkRelFile "bar.txt")) it "filename ($(mkAbsDir parent) $(mkRelFile filename)) == filename $(mkRelFile filename) (UNC)" (filenamesShouldBeEqual ($(mkAbsDir "\\\\host\\share\\chris\\") $(mkRelFile "bar.txt")) $(mkRelFile "bar.txt")) it "filename ($(mkAbsDir parent) $(mkRelFile filename)) == filename $(mkRelFile filename) (Unicode)" (filenamesShouldBeEqual ($(mkAbsDir "\\\\?\\C:\\home\\chris\\") $(mkRelFile "bar.txt")) $(mkRelFile "bar.txt")) where filenamesShouldBeEqual x y = filename x == filename y -- | The 'parent' operation. operationParent :: Spec operationParent = do it "parent (parent child) == parent" (parent ($(mkAbsDir "C:\\foo") $(mkRelDir "bar")) == $(mkAbsDir "C:\\foo")) it "parent \"C:\\\" == \"C:\\\"" (parent $(mkAbsDir "C:\\") == $(mkAbsDir "C:\\")) it "parent \"C:\\x\" == \"C:\\\"" (parent $(mkAbsDir "C:\\x") == $(mkAbsDir "C:\\")) it "parent \"x\" == \".\"" (parent $(mkRelDir "x") == $(mkRelDir ".")) it "parent \".\" == \".\"" (parent $(mkRelDir ".") == $(mkRelDir ".")) -- | The 'isProperPrefixOf' operation. operationIsProperPrefixOf :: Spec operationIsProperPrefixOf = do it "isProperPrefixOf parent (parent child) (absolute)" (isProperPrefixOf $(mkAbsDir "C:\\\\\\bar\\") ($(mkAbsDir "C:\\\\\\bar\\") $(mkRelFile "bar\\foo.txt"))) it "isProperPrefixOf parent (parent child) (relative)" (isProperPrefixOf $(mkRelDir "bar\\") ($(mkRelDir "bar\\") $(mkRelFile "bob\\foo.txt"))) it "isProperPrefixOf parent (parent child) (UNC)" (isProperPrefixOf $(mkAbsDir "\\\\host\\share\\") ($(mkAbsDir "\\\\host\\share\\") $(mkRelFile "bob\\foo.txt"))) it "isProperPrefixOf parent (parent child) (Unicode)" (isProperPrefixOf $(mkAbsDir "\\\\?\\C:\\folder\\") ($(mkAbsDir "\\\\?\\C:\\folder\\") $(mkRelFile "bob\\foo.txt"))) it "not (x `isProperPrefixOf` x)" (not (isProperPrefixOf $(mkRelDir "x") $(mkRelDir "x"))) it "not (\\ `isProperPrefixOf` \\)" (not (isProperPrefixOf $(mkAbsDir "C:\\") $(mkAbsDir "C:\\"))) -- | The 'stripProperPrefix' operation. operationStripProperPrefix :: Spec operationStripProperPrefix = do it "stripProperPrefix parent (parent child) = child (absolute)" (remainingPathShouldBe $(mkAbsDir "C:\\\\\\bar\\") ($(mkAbsDir "C:\\\\\\bar\\") $(mkRelFile "bar\\foo.txt")) (Just $(mkRelFile "bar\\foo.txt"))) it "stripProperPrefix parent (parent child) = child (relative)" (remainingPathShouldBe $(mkRelDir "bar\\") ($(mkRelDir "bar\\") $(mkRelFile "bob\\foo.txt")) (Just $(mkRelFile "bob\\foo.txt"))) it "stripProperPrefix parent (parent child) = child (UNC)" (remainingPathShouldBe $(mkAbsDir "\\\\host\\share\\") ($(mkAbsDir "\\\\host\\share\\") $(mkRelFile "bob\\foo.txt")) (Just $(mkRelFile "bob\\foo.txt"))) it "stripProperPrefix parent (parent child) = child (Unicode)" (remainingPathShouldBe $(mkAbsDir "\\\\?\\C:\\folder\\") ($(mkAbsDir "\\\\?\\C:\\folder\\") $(mkRelFile "bob\\foo.txt")) (Just $(mkRelFile "bob\\foo.txt"))) it "stripProperPrefix parent parent = _|_" (remainingPathShouldBe $(mkAbsDir "C:\\home\\chris\\foo") $(mkAbsDir "C:\\home\\chris\\foo") Nothing) where remainingPathShouldBe prefix path suffix = stripProperPrefix prefix path == suffix -- | The '' operation. operationAppend :: Spec operationAppend = do it "AbsDir + RelDir = AbsDir" (shouldBe ($(mkAbsDir "C:\\home\\") $(mkRelDir "chris")) $(mkAbsDir "C:\\home\\chris\\")) it "AbsDir + RelFile = AbsFile" (shouldBe ($(mkAbsDir "C:\\home\\") $(mkRelFile "chris\\test.txt")) $(mkAbsFile "C:\\home\\chris\\test.txt")) it "RelDir + RelDir = RelDir" (shouldBe ($(mkRelDir "home\\") $(mkRelDir "chris")) $(mkRelDir "home\\chris")) it ". + . = ." (shouldBe ($(mkRelDir ".\\") $(mkRelDir ".")) $(mkRelDir ".")) it ". + x = x" (shouldBe ($(mkRelDir ".") $(mkRelDir "x")) $(mkRelDir "x")) it "x + . = x" (shouldBe ($(mkRelDir "x") $(mkRelDir ".\\")) $(mkRelDir "x")) it "RelDir + RelFile = RelFile" (shouldBe ($(mkRelDir "home\\") $(mkRelFile "chris\\test.txt")) $(mkRelFile "home\\chris\\test.txt")) it "AbsDir(UNC) + RelDir = AbsDir(UNC)" (shouldBe ($(mkAbsDir "\\\\host\\share\\") $(mkRelDir "folder\\")) $(mkAbsDir "\\\\host\\share\\folder\\")) it "AbsDir(UNC) + RelFile = AbsFile(UNC)" (shouldBe ($(mkAbsDir "\\\\host\\share\\") $(mkRelFile "folder\\file.txt")) $(mkAbsFile "\\\\host\\share\\folder\\file.txt")) it "AbsDir(Unicode) + RelDir = AbsDir(Unicode)" (shouldBe ($(mkAbsDir "\\\\?\\C:\\folder\\") $(mkRelDir "another\\")) $(mkAbsDir "\\\\?\\C:\\folder\\another\\")) it "AbsDir(Unicode) + RelFile = AbsFile(Unicode)" (shouldBe ($(mkAbsDir "\\\\?\\C:\\folder\\") $(mkRelFile "file.txt")) $(mkAbsFile "\\\\?\\C:\\folder\\file.txt")) operationToFilePath :: Spec operationToFilePath = do it "toFilePath $(mkRelDir \".\") == \"./\"" (toFilePath $(mkRelDir ".") == ".\\") it "show $(mkRelDir \".\") == \"\\\".\\\\\"\"" (show $(mkRelDir ".") == "\".\\\\\"") -- | Tests for the tokenizer. parseAbsDirSpec :: Spec parseAbsDirSpec = do failing "" failing ".\\" failing "foo.txt" failing "C:" succeeding "C:\\" (Path "C:\\") succeeding "C:\\\\" (Path "C:\\") succeeding "C:\\\\\\foo\\\\bar\\\\mu\\" (Path "C:\\foo\\bar\\mu\\") succeeding "C:\\\\\\foo\\\\bar\\\\mu" (Path "C:\\foo\\bar\\mu\\") succeeding "C:\\\\\\foo\\\\bar\\.\\\\mu" (Path "C:\\foo\\bar\\mu\\") succeeding "\\\\unchost\\share" (Path "\\\\unchost\\share\\") succeeding "\\/unchost\\share" (Path "\\\\unchost\\share\\") succeeding "\\\\unchost\\share\\\\folder\\" (Path "\\\\unchost\\share\\folder\\") succeeding "\\\\?\\C:\\" (Path "\\\\?\\C:\\") succeeding "/\\?\\C:\\" (Path "\\\\?\\C:\\") succeeding "\\\\?\\C:\\\\\\folder\\\\" (Path "\\\\?\\C:\\folder\\") where failing x = parserTest parseAbsDir x Nothing succeeding x with = parserTest parseAbsDir x (Just with) -- | Tests for the tokenizer. parseRelDirSpec :: Spec parseRelDirSpec = do failing "" failing "/" failing "//" failing "\\" failing "\\\\" failing "\\\\\\foo\\\\bar\\\\mu\\" failing "\\\\\\foo\\\\bar\\\\\\\\mu" failing "\\\\\\foo\\\\bar\\.\\\\mu" failing "\\\\unchost\\share" failing "\\\\?\\C:\\" succeeding ".\\" (Path "") succeeding ".\\.\\" (Path "") succeeding "..." (Path "...\\") succeeding "foo.bak" (Path "foo.bak\\") succeeding ".\\foo" (Path "foo\\") succeeding ".\\.\\foo" (Path "foo\\") succeeding ".\\foo\\.\\bar" (Path "foo\\bar\\") succeeding "foo\\\\bar\\\\mu\\\\" (Path "foo\\bar\\mu\\") succeeding "foo\\\\bar////mu" (Path "foo\\bar\\mu\\") succeeding "foo\\\\bar\\.\\\\mu" (Path "foo\\bar\\mu\\") where failing x = parserTest parseRelDir x Nothing succeeding x with = parserTest parseRelDir x (Just with) -- | Tests for the tokenizer. parseAbsFileSpec :: Spec parseAbsFileSpec = do failing "" failing ".\\" failing "\\." failing "\\foo\\bar\\." failing "~\\" failing ".\\foo.txt" failing "\\" failing "\\\\" failing "\\\\\\foo\\\\bar\\\\mu\\" failing "\\..." failing "\\foo.txt" succeeding "C:\\\\\\foo\\\\bar\\\\\\\\mu.txt" (Path "C:\\foo\\bar\\mu.txt") succeeding "C:\\\\\\foo\\\\bar\\.\\\\mu.txt" (Path "C:\\foo\\bar\\mu.txt") succeeding "\\\\unchost\\share\\\\file.txt" (Path "\\\\unchost\\share\\file.txt") succeeding "\\/unchost\\share\\\\file.txt" (Path "\\\\unchost\\share\\file.txt") succeeding "\\\\unchost\\share\\.\\folder\\\\\\file.txt" (Path "\\\\unchost\\share\\folder\\file.txt") succeeding "\\\\?\\C:\\file.txt" (Path "\\\\?\\C:\\file.txt") succeeding "/\\?\\C:\\file.txt" (Path "\\\\?\\C:\\file.txt") succeeding "\\\\?\\C:\\\\\\folder\\.\\\\file.txt" (Path "\\\\?\\C:\\folder\\file.txt") where failing x = parserTest parseAbsFile x Nothing succeeding x with = parserTest parseAbsFile x (Just with) -- | Tests for the tokenizer. parseRelFileSpec :: Spec parseRelFileSpec = do failing "" failing "\\" failing "\\\\" failing "~\\" failing "\\" failing ".\\" failing "a\\." failing "a\\..\\b" failing "a\\.." failing "..\\foo.txt" failing "\\\\" failing "\\\\\\foo\\\\bar\\\\mu\\" failing "\\\\\\foo\\\\bar\\\\\\\\mu" failing "\\\\\\foo\\\\bar\\.\\\\mu" failing "\\\\unchost\\share\\\\file.txt" failing "\\\\?\\C:\\file.txt" succeeding "a.." (Path "a..") succeeding "..." (Path "...") succeeding "foo.txt" (Path "foo.txt") succeeding ".\\foo.txt" (Path "foo.txt") succeeding ".\\.\\foo.txt" (Path "foo.txt") succeeding ".\\foo\\.\\bar.txt" (Path "foo\\bar.txt") succeeding "foo\\\\bar\\\\mu.txt" (Path "foo\\bar\\mu.txt") succeeding "foo\\\\bar\\\\\\\\mu.txt" (Path "foo\\bar\\mu.txt") succeeding "foo\\\\bar\\.\\\\mu.txt" (Path "foo\\bar\\mu.txt") where failing x = parserTest parseRelFile x Nothing succeeding x with = parserTest parseRelFile x (Just with) -- | Parser test. parserTest :: (Show a1,Show a,Eq a1) => (a -> Maybe a1) -> a -> Maybe a1 -> SpecWith () parserTest parser input expected = it ((case expected of Nothing -> "Failing: " Just{} -> "Succeeding: ") ++ "Parsing " ++ show input ++ " " ++ case expected of Nothing -> "should fail." Just x -> "should succeed with: " ++ show x) (actual `shouldBe` expected) where actual = parser input -- | Tests for the 'ToJSON' and 'FromJSON' instances -- -- Can't use overloaded strings due to some weird issue with bytestring-0.9.2.1 / ghc-7.4.2: -- https://travis-ci.org/sjakobi/path/jobs/138399072#L989 aesonInstances :: Spec aesonInstances = do it "Decoding \"[\"C:\\\\foo\\\\bar\"]\" as a [Path Abs Dir] should succeed." $ eitherDecode (LBS.pack "[\"C:\\\\foo\\\\bar\"]") `shouldBe` Right [Path "C:\\foo\\bar\\" :: Path Abs Dir] it "Decoding \"[\"C:\\foo\\bar\"]\" as a [Path Rel Dir] should fail." $ decode (LBS.pack "[\"C:\\foo\\bar\"]") `shouldBe` (Nothing :: Maybe [Path Rel Dir]) it "Encoding \"[\"C:\\foo\\bar\\mu.txt\"]\" should succeed." $ encode [Path "C:\\foo\\bar\\mu.txt" :: Path Abs File] `shouldBe` (LBS.pack "[\"C:\\\\foo\\\\bar\\\\mu.txt\"]") -- | Test QuasiQuoters. Make sure they work the same as the $(mk*) constructors. quasiquotes :: Spec quasiquotes = do it "[absdir|C:\\|] == $(mkAbsDir \"C:\\\")" ([absdir|C:\|] `shouldBe` $(mkAbsDir "C:\\")) it "[absdir|C:\\chris\\|] == $(mkAbsDir \"C:\\chris\\\")" ([absdir|C:\chris\|] `shouldBe` $(mkAbsDir "C:\\chris\\")) it "[reldir|foo|] == $(mkRelDir \"foo\")" ([reldir|foo|] `shouldBe` $(mkRelDir "foo")) it "[reldir|foo\\bar|] == $(mkRelDir \"foo\\bar\")" ([reldir|foo\bar|] `shouldBe` $(mkRelDir "foo\\bar")) it "[absfile|C:\\chris\\foo.txt|] == $(mkAbsFile \"C:\\chris\\foo.txt\")" ([absfile|C:\chris\foo.txt|] `shouldBe` $(mkAbsFile "C:\\chris\\foo.txt")) it "[relfile|foo.exe|] == $(mkRelFile \"foo.exe\")" ([relfile|foo.exe|] `shouldBe` $(mkRelFile "foo.exe")) it "[relfile|chris\\foo.txt|] == $(mkRelFile \"chris\\foo.txt\")" ([relfile|chris\foo.txt|] `shouldBe` $(mkRelFile "chris\\foo.txt")) path-0.9.2/test/Common/Posix.hs0000644000000000000000000000101414162173754014517 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE QuasiQuotes #-} #define PLATFORM_NAME Posix #define IS_WINDOWS False #include "Include.hs" qqAbsDir :: FilePath qqAbsDir = foo [absdir|/foo/|] qqAbsFile :: FilePath qqAbsFile = foo [absdir|/foo|] thAbsDir :: FilePath thAbsDir = foo $(mkAbsDir "/foo/") thAbsFile :: FilePath thAbsFile = foo $(mkAbsFile "/foo") liftAbsDir :: FilePath liftAbsDir = foo $(TH.lift (Path "/foo/" :: Path Abs Dir)) liftAbsFile :: FilePath liftAbsFile = foo $(TH.lift (Path "/foo" :: Path Abs File)) path-0.9.2/test/Common/Windows.hs0000644000000000000000000000103714162173754015054 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE QuasiQuotes #-} #define PLATFORM_NAME Windows #define IS_WINDOWS True #include "Include.hs" qqAbsDir :: FilePath qqAbsDir = foo [absdir|C:\foo\|] qqAbsFile :: FilePath qqAbsFile = foo [absdir|C:\foo|] thAbsDir :: FilePath thAbsDir = foo $(mkAbsDir "C:\\foo\\") thAbsFile :: FilePath thAbsFile = foo $(mkAbsFile "C:\\foo") liftAbsDir :: FilePath liftAbsDir = foo $(TH.lift (Path "C:\\foo\\" :: Path Abs Dir)) liftAbsFile :: FilePath liftAbsFile = foo $(TH.lift (Path "C:\\foo" :: Path Abs File)) path-0.9.2/README.md0000644000000000000000000004232514162173754012143 0ustar0000000000000000# Path ![CI](https://github.com/commercialhaskell/path/workflows/CI/badge.svg?branch=master) [![Hackage](https://img.shields.io/hackage/v/path.svg)](https://hackage.haskell.org/package/path) [![Stackage LTS](http://stackage.org/package/path/badge/lts)](http://stackage.org/lts/package/path) [![Stackage Nightly](http://stackage.org/package/path/badge/nightly)](http://stackage.org/nightly/package/path) Support for well-typed paths in Haskell. * [Motivation](#motivation) * [Approach](#approach) * [Solution](#solution) * [Implementation](#implementation) * [The data types](#the-data-types) * [Parsers](#parsers) * [Smart constructors](#smart-constructors) * [Overloaded stings](#overloaded-strings) * [Operations](#operations) * [Review](#review) * [Relative vs absolute confusion](#relative-vs-absolute-confusion) * [The equality problem](#the-equality-problem) * [Unpredictable concatenation issues](#unpredictable-concatenation-issues) * [Confusing files and directories](#confusing-files-and-directories) * [Self-documentation](#self-documentation) * [In practice](#in-practice) * [Doing I/O](#doing-io) * [Doing textual manipulations](#doing-textual-manipulations) * [Accepting user input](#accepting-user-input) * [Comparing with existing path libraries](#comparing-with-existing-path-libraries) * [filepath and system-filepath](#filepath-and-system-filepath) * [system-canonicalpath, canonical-filepath, directory-tree](#system-canonicalpath-canonical-filepath-directory-tree) * [pathtype](#pathtype) * [data-filepath](#data-filepath) * [Summary](#summary) ## Motivation It was after working on a number of projects at FP Complete that use file paths in various ways. We used the system-filepath package, which was supposed to solve many path problems by being an opaque path type. It occurred to me that the same kind of bugs kept cropping up: * Expected a path to be absolute but it was relative, or vice-versa. * Expected two equivalent paths to be equal or order the same, but they did not (`/home//foo` vs `/home/foo/` vs `/home/bar/../foo`, etc.). * Unpredictable behaviour with regards to concatenating paths. * Confusing files and directories. * Not knowing whether a path was a file or directory or relative or absolute based on the type alone was a drag. All of these bugs are preventable. ## Approach My approach to problems like this is to make a type that encodes the properties I want and then make it impossible to let those invariants be broken, without compromise or backdoors to let the wrong value “slip in”. Once I have a path, I want to be able to trust it fully. This theme will be seen throughout the things I lay out below. ## Solution After having to fix bugs due to these in our software, I put my foot down and made: * An opaque `Path` type (a newtype wrapper around `String`). * Smart constructors which are very stringent in the parsing. * Make the parsers highly normalizing. * Leave equality and concatenation to basic string equality and concatenation. * Include relativity (absolute/relative) and type (directory/file) in the type itself. * Use the already cross-platform [filepath](http://hackage.haskell.org/package/filepath) package for implementation details. ## Implementation ### The data types Here is the type: ```haskell newtype Path b t = Path FilePath deriving (Data, Typeable, Generic) ``` The type variables are: * `b` — base, the base location of the path; absolute or relative. * `t` — type, whether file or directory. The base types can be filled with these: ```haskell data Abs deriving (Typeable) data Rel deriving (Typeable) ``` And the type can be filled with these: ```haskell data File deriving (Typeable) data Dir deriving (Typeable) ``` (Why not use data kinds like `data Type = File | Dir`? Because that imposes an extension overhead of adding `{-# LANGUAGE DataKinds #-}` to every module you might want to write out a path type in. Given that one cannot construct paths of types other than these, via the operations in the module, it’s not a concern for me.) There is a conversion function to give you back the filepath: ```haskell toFilePath :: Path b t -> FilePath toFilePath (Path l) = l ``` Beginning from version 0.5.3, there are type-constrained versions of `toFilePath` with the following signatures: ```haskell fromAbsDir :: Path Abs Dir -> FilePath fromRelDir :: Path Rel Dir -> FilePath fromAbsFile :: Path Abs File -> FilePath fromRelFile :: Path Rel File -> FilePath ``` ### Parsers To get a `Path` value, you need to use one of the four parsers: ```haskell parseAbsDir :: MonadThrow m => FilePath -> m (Path Abs Dir) parseRelDir :: MonadThrow m => FilePath -> m (Path Rel Dir) parseAbsFile :: MonadThrow m => FilePath -> m (Path Abs File) parseRelFile :: MonadThrow m => FilePath -> m (Path Rel File) ``` The following properties apply: * Absolute parsers will reject non-absolute paths. * The only delimiter syntax accepted is the path separator; `/` on POSIX and `\` on Windows. * Any other delimiter is rejected; `..`, `~/`, `/./`, etc. * All parsers normalize into single separators: `/home//foo` → `/home/foo`. * Directory parsers always normalize with a final trailing `/`. So `/home/foo` parses into the string `/home/foo/`. It was discussed briefly whether we should just have a class for parsing rather than four separate parsing functions. In my experience so far, I have had type errors where I wrote something `like x <- parseAbsDir someAbsDirString` because `x` was then passed to a place that expected a relative directory. In this way, overloading the return value would’ve just been accepted. So I don’t think having a class is a good idea. Being explicit here doesn’t exactly waste our time, either. Why are these functions in `MonadThrow`? Because it means I can have it return an `Either`, or a `Maybe`, if I’m in pure code, and if I’m in `IO`, and I don’t expect parsing to ever fail, I can use it in IO like this: ```haskell do x <- parseRelFile (fromCabalFileName x) foo x … ``` That’s really convenient and we take advantage of this at FP Complete a lot. The instances Equality, ordering and printing are simply re-using the `String` instances: ```haskell instance Eq (Path b t) where (==) (Path x) (Path y) = x == y instance Ord (Path b t) where compare (Path x) (Path y) = compare x y instance Show (Path b t) where show (Path x) = show x ``` Which gives us for free the following equational properties: ```haskell toFilePath x == toFilePath y ≡ x == y -- Eq instance toFilePath x `compare` toFilePath y ≡ x `compare` y -- Ord instance toFilePath x == toFilePath y ≡ show x == show y -- Show instance ``` In other words, the representation and the path you get out at the end are the same. Two paths that are equal will always give you back the same thing. ### Smart constructors For when you know what a path will be at compile-time, there are constructors for that: ```haskell $(mkAbsDir "/home/chris") $(mkRelDir "chris") $(mkAbsFile "/home/chris/x.txt") $(mkRelFile "chris/x.txt") ``` With the [QuasiQuotes](https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html#ghc-flag--XQuasiQuotes) language extension, paths can be written as follows: ```haskell [absdir|/home/chris|] [reldir|chris|] [absfile|/home/chris/x.txt|] [relfile|chris/x.txt|] ``` These will run at compile-time and underneath use the appropriate parser. ### Overloaded strings No `IsString` instance is provided, because that has no way to statically determine whether the path is correct, and would otherwise have to be a partial function. In practice I have written the wrong path format in a `$(mk… "")` and been thankful it was caught early. ### Operations There is path concatenation: ```haskell () :: Path b Dir -> Path Rel t -> Path b t ``` Get the parent directory of a path: ```haskell parent :: Path Abs t -> Path Abs Dir ``` Get the filename of a file path: ```haskell filename :: Path b File -> Path Rel File ``` Get the directory name of a directory path: ```haskell dirname :: Path b Dir -> Path Rel Dir ``` Stripping the parent directory from a path: ```haskell stripProperPrefix :: MonadThrow m => Path b Dir -> Path b t -> m (Path Rel t) ``` ## Review Let’s review my initial list of complaints and see if they’ve been satisfied. ### Relative vs absolute confusion Paths now distinguish in the type system whether they are relative or absolute. You can’t append two absolute paths, for example: ```haskell λ> [absdir|/home/chris|][absdir|/home/chris|] :23:31-55: Couldn't match type ‘Abs’ with ‘Rel’ ``` ### The equality problem Paths are now stringently normalized. They have to be a valid path, and they only support single path separators, and all directories are suffixed with a trailing path separator: ```haskell λ> $(mkAbsDir "/home/chris//") == $(mkAbsDir "/./home//chris") True λ> toFilePath $(mkAbsDir "/home/chris//") == toFilePath $(mkAbsDir "/./home//chris") True λ> ($(mkAbsDir "/home/chris//"),toFilePath $(mkAbsDir "/./home//chris")) ("/home/chris/","/home/chris/") ``` ### Unpredictable concatenation issues Because of the stringent normalization, path concatenation, as seen above, is simply string concatenation. This is about as predictable as it can get: ```haskell λ> toFilePath $(mkAbsDir "/home/chris//") "/home/chris/" λ> toFilePath $(mkRelDir "foo//bar") "foo/bar/" λ> [absdir|/home/chris//|][reldir|foo//bar|] "/home/chris/foo/bar/" ``` ### Confusing files and directories Now that the path type is encoded in the type system, our `` operator prevents improper appending: ```haskell λ> [absdir|/home/chris/|][relfile|foo//bar|] "/home/chris/foo/bar" λ> [absfile|/home/chris|][relfile|foo//bar|] :35:1-26: Couldn't match type ‘File’ with ‘Dir’ ``` ### Self-documentation Now I can read the path like: ```haskell { fooPath :: Path Rel Dir, ... } ``` And know that this refers to the directory relative to some other path, meaning I should be careful to consider the current directory when using this in IO, or that I’ll probably need a parent to append to it at some point. ## In practice We’ve been using this at FP Complete in a number of packages for some months now, it’s turned out surprisingly sufficient for most of our path work with only one bug found. We weren’t sure initially whether it would just be too much of a pain to use, but really it’s quite acceptable given the advantages. You can see its use all over the [`stack`](https://github.com/commercialhaskell/stack) codebase. ## Doing I/O Currently any operations involving I/O can be done by using the existing I/O library: ```haskell doesFileExist (toFilePath fp) readFile (toFilePath fp) ``` etc. This has problems with respect to accidentally running something like: ```haskell doesFileExist $(mkRelDir "foo") ``` But I/O is currently outside the scope of what this package solves. Once you leave the realm of the `Path` type invariants are back to your responsibility. As with the original version of this library, we’re currently building up a set of functions in a `Path.IO` module over time that fits our real-world use-cases. It may or may not appear in the path package eventually. It’ll need cleaning up and considering what should really be included. **Edit:** There is now [`path-io`](https://hackage.haskell.org/package/path-io) package that complements the `path` library and includes complete well-typed interface to [`directory`](https://hackage.haskell.org/package/directory) and [`temporary`](https://hackage.haskell.org/package/temporary). There is work to add more generally useful functions from Stack's `Path.IO` to it and make Stack depend on the `path-io` package. ## Doing textual manipulations One problem that crops up sometimes is wanting to manipulate paths. Currently the way we do it is via the filepath library and re-parsing the path: ```haskell parseAbsFile . addExtension "/directory/path" "ext" . toFilePath ``` It doesn’t happen too often, in our experience, to the extent this needs to be more convenient. ## Accepting user input Sometimes you have user input that contains `../`. The solution we went with is to have a function like `resolveDir` (found in [`path-io`](http://hackage.haskell.org/package/path-io) package): ```haskell resolveDir :: (MonadIO m, MonadThrow m) => Path Abs Dir -> FilePath -> m (Path Abs Dir) ``` Which will call `canonicalizePath` which collapses and normalizes a path and then we parse with regular old `parseAbsDir` and we’re cooking with gas. This and others like it might get added to the `path` package. ## Comparing with existing path libraries ### filepath and system-filepath The [filepath](http://hackage.haskell.org/package/filepath) package is intended as the complimentary package to be used before parsing into a Path value, and/or after printing from a Path value. The package itself contains no type-safety, instead contains a range of cross-platform textual operations. Definitely reach for this library when you want to do more involved manipulations. The `system-filepath` package is deprecated in favour of `filepath`. ### system-canonicalpath, canonical-filepath, directory-tree The [`system-canonicalpath`](http://hackage.haskell.org/package/system-canonicalpath) and the [`canonical-filepath`](http://hackage.haskell.org/package/canonical-filepath) packages both are a kind of subset of `path`. They canonicalize a string into an opaque path, but neither distinguish directories from files or absolute/relative. Useful if you just want a canonical path but doesn’t do anything else. The [`directory-tree`](http://hackage.haskell.org/package/directory-tree) package contains a sum type of dir/file/etc but doesn’t distinguish in its operations relativity or path type. ### pathtype Finally, we come to a path library that path is similar to: the [`pathtype`](http://hackage.haskell.org/package/pathtype) library. There are the same types of `Path Abs File` / `Path Rel Dir`, etc. The points where this library isn’t enough for me are: * There is an `IsString` instance, which means people will use it, and will make mistakes. * Paths are not normalized into a predictable format, leading to me being unsure when equality will succeed. This is the same problem I encountered in `system-filepath`. The equality function normalizes, but according to what properties I can reason about? I don’t know. ```haskell System.Path.Posix> ("/tmp//" :: Path a Dir) == ("/tmp" :: Path a Dir) True System.Path.Posix> ("tmp" :: Path a Dir) == ("/tmp" :: Path a Dir) True System.Path.Posix> ("/etc/passwd/" :: Path a b) == ("/etc/passwd" :: Path a b) True System.Path.Posix> ("/tmp//" :: Path Abs Dir) == ("/tmp/./" :: Path Abs Dir) False System.Path.Posix> ("/tmp/../" :: Path Abs Dir) == ("/" :: Path Abs Dir) False ``` * Empty string should not be allowed, and introduction of `.` due to that gets weird: ```haskell System.Path.Posix> fmap getPathString (Right ("." :: Path Rel File)) Right "." System.Path.Posix> fmap getPathString (mkPathAbsOrRel "") Right "." System.Path.Posix> (Right ("." :: Path Rel File)) == (mkPathAbsOrRel "") False System.Path.Posix> takeDirectory ("tmp" :: Path Rel Dir) . System.Path.Posix> (getPathString ("." :: Path Rel File) == getPathString ("" :: Path Rel File)) True System.Path.Posix> (("." :: Path Rel File) == ("" :: Path Rel File)) False ``` * It has functions like `<.>/addExtension` which lets you insert an arbitrary string into a path. * Some functions let you produce nonsense (could be prevented by a stricter type), for example: ```haskell System.Path.Posix> takeFileName ("/tmp/" :: Path Abs Dir) tmp ``` I’m being a bit picky here, a bit unfair. But the point is really to show the kind of things I tried to avoid in `path`. In summary, it’s just hard to know where things can go wrong, similar to what was going on in `system-filepath`. ### data-filepath The [`data-filepath`](https://hackage.haskell.org/package/data-filepath) is also very similar, I discovered it after writing my own at work and was pleased to see it’s mostly the same. The main differences are: * Uses `DataKinds` for the relative/absolute and file/dir distinction which as I said above is an overhead. * Uses a GADT for the path type, which is fine. In my case I wanted to retain the original string which functions that work on the `FilePath` (`String`) type already deal with well. It does change the parsing step somewhat, because it parses into segments. * It’s more lenient at parsing (allowing `..` and trailing `.`). The API is a bit awkward to just parse a directory, requires a couple functions to get it (going via `WeakFilePath`), returning only an `Either`, and there are no functions like parent. But there’s not much to complain about. It’s a fine library, but I didn’t feel the need to drop my own in favor of it. Check it out and decide for yourself. ## Summary There’s a growing interest in making practical use of well-typed file path handling. I think everyone’s wanted it for a while, but few people have really committed to it in practice. Now that I’ve been using `path` for a while, I can’t really go back. It’ll be interesting to see what new packages crop up in the coming year, I expect there’ll be more. path-0.9.2/CHANGELOG0000644000000000000000000001036714162271745012076 0ustar00000000000000000.9.2 * Data instances for Rel, Abs, File, and Dir. * Bump hashable upper bound to <1.5. 0.9.1 * Support for genvalidity >=1.0.0.0 * `mapSomeBase` and `prjSomeBase` for modifying or projecting SomeBase. 0.9.0 * Fix inconsistencies on different platforms: [#166](https://github.com/commercialhaskell/path/issues/166) * `replaceProperPrefix` * Make it possible to use windows paths on posix and vice versa 0.8.0 * Rerelease of 0.7.1 with better version number 0.7.1: * Test with GHC 8.8.2, 8.8.3, 8.10.1. * Export SomeBase constructor. * Fix Lift severe Lift instance bug 0.7.0: * BREAKING CHANGE: "fileExtension" now throws an exception if the file has no extension. You can use the result as a "Maybe" in pure code or handle the exception appropriately in any other monad. * Old extension operations "addFileExtension" and "setFileExtension" have been deprecated and replaced by "addExtension" and "replaceExtension" respectively with new behavior. ADAPTING YOUR CODE TO THIS CHANGE: * Code that sets an extension not starting with a "." e.g. "foo", must be changed such that it starts with a "." i.e. ".foo". * Code that sets multiple extensions in one go e.g. ".tar.gz" must be changed to set them one at a time instead i.e. add ".tar" first and then add ".gz". * Code that sets an extension starting with multiple dots e.g. "..foo" must be changed such as to make the extra dots part of the file name instead. Details: The new operations "addExtension" and "replaceExtension" accept only "valid" extension forms which is exactly the same as what "fileExtension" returns. A valid extension starts with a @.@ followed by one or more characters not including @.@ followed by zero or more @.@s in trailing position. This change allows extension operations to be principled following these laws: * flip addExtension file >=> fileExtension == return * (fileExtension >=> flip replaceExtension file) file == return file * Add splitExtension operation such that: * uncurry addExtension . swap >=> splitExtension == return * splitExtension >=> uncurry addExtension . swap == return * fileExtension == (fmap snd) . splitExtension@ * Add 'Path.Posix' and 'Path.Windows' modules for manipulating Windows or Posix style paths independently of the current platform. * Add 'Lift' instance for 'Path'. * `Path.Windows` normalizes path separators throughout path, including immediately following drive letter. * `Path.Windows` handles UNC (`\\host\share\`) and Unicode (`\\?\C:\`) path without breaking the double-separator prefix. * Remove support for old GHC version. The oldest supported version is 8.2. 0.6.1: * Add 'addFileExtension' function and its operator form: (<.>). * Derive 'Eq' instance for 'PathException'. 0.6.0: * Deprecate PathParseException and rename it to PathException * Allow 'parent' to work on relative paths as well * Deprecate isParentOf and stripDir and rename them to isProperPrefixOf and stripProperPrefix respectively. * Allow "." as a valid relative dir path with the following rules: * "./" "./" = "./" * "./" "x/" = "x/" * "x/" "./" = "x/" * dirname "x" = "./" * dirname "/" = "./" * dirname "./" = "./" * Make dirname return "." instead of "/" (fixes #18). * Remove the 'validity' flag. * Add synonym for setFileExtension in the form of an operator: (-<.>). 0.5.13: * Add QuasiQuoters absdir, reldir, absfile, relfile 0.5.11: * Add replaceExtension and fileExtension 0.5.10: * Disallow /. for absolute file * Disallow foo/. for relative file 0.5.9: * Lifted ~ restriction from parser https://github.com/chrisdone/path/issues/19 0.5.8 * Add Aeson instances. 0.5.7: * Fix haddock problem. 0.5.6: * Reject only .. and . 0.5.5: * Use filepath's isValid function for additional sanity checks 0.5.4: * Disable parsing of path consisting only of "." * Add NFData instance for Path * Some typo/docs improvements * Add standard headers to modules 0.5.3: * Added conversion functions. 0.2.0: * Rename parentAbs to simply parent. * Add dirname. 0.3.0: * Removed Generic instance. 0.4.0: * Implemented stricter parsing, disabling use of "..". * Made stripDir generic over MonadThrow 0.5.0: * Fix stripDir p p /= Nothing bug. 0.5.2: * Removed unused DeriveGeneric. path-0.9.2/src/Path/Include.hs0000644000000000000000000007402614162271567014272 0ustar0000000000000000-- This template expects CPP definitions for: -- PLATFORM_NAME = Posix | Windows -- IS_WINDOWS = False | True -- | This library provides a well-typed representation of paths in a filesystem -- directory tree. -- -- __Note__: This module is for working with PLATFORM_NAME style paths. Importing -- "Path" is usually better. -- -- A path is represented by a number of path components separated by a path -- separator which is a @/@ on POSIX systems and can be a @/@ or @\\@ on Windows. -- The root of the tree is represented by a @/@ on POSIX and a drive letter -- followed by a @/@ or @\\@ on Windows (e.g. @C:\\@). Paths can be absolute -- or relative. An absolute path always starts from the root of the tree (e.g. -- @\/x/y@) whereas a relative path never starts with the root (e.g. @x/y@). -- Just like we represent the notion of an absolute root by "@/@", the same way -- we represent the notion of a relative root by "@.@". The relative root denotes -- the directory which contains the first component of a relative path. {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE EmptyDataDecls #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE PatternGuards #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TemplateHaskell #-} module Path.PLATFORM_NAME (-- * Types Path ,Abs ,Rel ,File ,Dir ,SomeBase(..) -- * Exceptions ,PathException(..) -- * QuasiQuoters -- | Using the following requires the QuasiQuotes language extension. -- -- __For Windows users__, the QuasiQuoters are especially beneficial because they -- prevent Haskell from treating @\\@ as an escape character. -- This makes Windows paths easier to write. -- -- @ -- [absfile|C:\\chris\\foo.txt|] -- @ ,absdir ,reldir ,absfile ,relfile -- * Operations ,() ,stripProperPrefix ,isProperPrefixOf ,replaceProperPrefix ,parent ,filename ,dirname ,addExtension ,splitExtension ,fileExtension ,replaceExtension ,mapSomeBase ,prjSomeBase -- * Parsing ,parseAbsDir ,parseRelDir ,parseAbsFile ,parseRelFile ,parseSomeDir ,parseSomeFile -- * Conversion ,toFilePath ,fromAbsDir ,fromRelDir ,fromAbsFile ,fromRelFile ,fromSomeDir ,fromSomeFile -- * TemplateHaskell constructors -- | These require the TemplateHaskell language extension. ,mkAbsDir ,mkRelDir ,mkAbsFile ,mkRelFile -- * Deprecated ,PathParseException ,stripDir ,isParentOf ,addFileExtension ,(<.>) ,setFileExtension ,(-<.>) ) where import Control.Applicative (Alternative(..)) import Control.DeepSeq (NFData (..)) import Control.Exception (Exception(..)) import Control.Monad (liftM, when) import Control.Monad.Catch (MonadThrow(..)) import Data.Aeson (FromJSON (..), FromJSONKey(..), ToJSON(..)) import qualified Data.Aeson.Types as Aeson import Data.Data import qualified Data.Text as T import Data.Hashable import qualified Data.List as L import Data.Maybe import GHC.Generics (Generic) import Language.Haskell.TH import Language.Haskell.TH.Syntax (lift) import Language.Haskell.TH.Quote (QuasiQuoter(..)) import Path.Internal.PLATFORM_NAME import qualified System.FilePath.PLATFORM_NAME as FilePath -------------------------------------------------------------------------------- -- Types -- | An absolute path. data Abs deriving (Typeable, Data) -- | A relative path; one without a root. Note that a @..@ path component to -- represent the parent directory is not allowed by this library. data Rel deriving (Typeable, Data) -- | A file path. data File deriving (Typeable, Data) -- | A directory path. data Dir deriving (Typeable, Data) instance FromJSON (Path Abs File) where parseJSON = parseJSONWith parseAbsFile {-# INLINE parseJSON #-} instance FromJSON (Path Rel File) where parseJSON = parseJSONWith parseRelFile {-# INLINE parseJSON #-} instance FromJSON (Path Abs Dir) where parseJSON = parseJSONWith parseAbsDir {-# INLINE parseJSON #-} instance FromJSON (Path Rel Dir) where parseJSON = parseJSONWith parseRelDir {-# INLINE parseJSON #-} parseJSONWith :: (Show e, FromJSON a) => (a -> Either e b) -> Aeson.Value -> Aeson.Parser b parseJSONWith f x = do fp <- parseJSON x case f fp of Right p -> return p Left e -> fail (show e) {-# INLINE parseJSONWith #-} instance FromJSONKey (Path Abs File) where fromJSONKey = fromJSONKeyWith parseAbsFile {-# INLINE fromJSONKey #-} instance FromJSONKey (Path Rel File) where fromJSONKey = fromJSONKeyWith parseRelFile {-# INLINE fromJSONKey #-} instance FromJSONKey (Path Abs Dir) where fromJSONKey = fromJSONKeyWith parseAbsDir {-# INLINE fromJSONKey #-} instance FromJSONKey (Path Rel Dir) where fromJSONKey = fromJSONKeyWith parseRelDir {-# INLINE fromJSONKey #-} fromJSONKeyWith :: (Show e) => (String -> Either e b) -> Aeson.FromJSONKeyFunction b fromJSONKeyWith f = Aeson.FromJSONKeyTextParser $ \t -> case f (T.unpack t) of Left e -> fail (show e) Right rf -> pure rf {-# INLINE fromJSONKeyWith #-} -- | Exceptions that can occur during path operations. -- -- @since 0.6.0 data PathException = InvalidAbsDir FilePath | InvalidRelDir FilePath | InvalidAbsFile FilePath | InvalidRelFile FilePath | InvalidFile FilePath | InvalidDir FilePath | NotAProperPrefix FilePath FilePath | HasNoExtension FilePath | InvalidExtension String deriving (Show,Eq,Typeable) instance Exception PathException where displayException (InvalidExtension ext) = concat [ "Invalid extension [" , ext , "]. A valid extension starts with a '.' followed by one or more " , "characters other than '.', and it must be a valid filename, " , "notably it cannot include a path separator." ] displayException x = show x -------------------------------------------------------------------------------- -- QuasiQuoters qq :: (String -> Q Exp) -> QuasiQuoter qq quoteExp' = QuasiQuoter { quoteExp = quoteExp' , quotePat = \_ -> fail "illegal QuasiQuote (allowed as expression only, used as a pattern)" , quoteType = \_ -> fail "illegal QuasiQuote (allowed as expression only, used as a type)" , quoteDec = \_ -> fail "illegal QuasiQuote (allowed as expression only, used as a declaration)" } -- | Construct a 'Path' 'Abs' 'Dir' using QuasiQuotes. -- -- @ -- [absdir|/|] -- -- [absdir|\/home\/chris|] -- @ -- -- Remember: due to the nature of absolute paths a path like @[absdir|\/home\/chris|]@ -- may compile on your platform, but it may not compile on another -- platform (Windows). -- -- @since 0.5.13 absdir :: QuasiQuoter absdir = qq mkAbsDir -- | Construct a 'Path' 'Rel' 'Dir' using QuasiQuotes. -- -- @ -- [absdir|\/home|]\<\/>[reldir|chris|] -- @ -- -- @since 0.5.13 reldir :: QuasiQuoter reldir = qq mkRelDir -- | Construct a 'Path' 'Abs' 'File' using QuasiQuotes. -- -- @ -- [absfile|\/home\/chris\/foo.txt|] -- @ -- -- Remember: due to the nature of absolute paths a path like @[absdir|\/home\/chris\/foo.txt|]@ -- may compile on your platform, but it may not compile on another -- platform (Windows). -- -- @since 0.5.13 absfile :: QuasiQuoter absfile = qq mkAbsFile -- | Construct a 'Path' 'Rel' 'File' using QuasiQuotes. -- -- @ -- [absdir|\/home\/chris|]\<\/>[relfile|foo.txt|] -- @ -- -- @since 0.5.13 relfile :: QuasiQuoter relfile = qq mkRelFile -------------------------------------------------------------------------------- -- Operations -- | Append two paths. -- -- The following cases are valid and the equalities hold: -- -- @$(mkAbsDir x) \<\/> $(mkRelDir y) = $(mkAbsDir (x ++ \"/\" ++ y))@ -- -- @$(mkAbsDir x) \<\/> $(mkRelFile y) = $(mkAbsFile (x ++ \"/\" ++ y))@ -- -- @$(mkRelDir x) \<\/> $(mkRelDir y) = $(mkRelDir (x ++ \"/\" ++ y))@ -- -- @$(mkRelDir x) \<\/> $(mkRelFile y) = $(mkRelFile (x ++ \"/\" ++ y))@ -- -- The following are proven not possible to express: -- -- @$(mkAbsFile …) \<\/> x@ -- -- @$(mkRelFile …) \<\/> x@ -- -- @x \<\/> $(mkAbsFile …)@ -- -- @x \<\/> $(mkAbsDir …)@ -- infixr 5 () :: Path b Dir -> Path Rel t -> Path b t () (Path a) (Path b) = Path (a ++ b) -- | If the directory in the first argument is a proper prefix of the path in -- the second argument strip it from the second argument, generating a path -- relative to the directory. -- Throws 'NotAProperPrefix' if the directory is not a proper prefix of the -- path. -- -- The following properties hold: -- -- @stripProperPrefix x (x \<\/> y) = y@ -- -- Cases which are proven not possible: -- -- @stripProperPrefix (a :: Path Abs …) (b :: Path Rel …)@ -- -- @stripProperPrefix (a :: Path Rel …) (b :: Path Abs …)@ -- -- In other words the bases must match. -- -- @since 0.6.0 stripProperPrefix :: MonadThrow m => Path b Dir -> Path b t -> m (Path Rel t) stripProperPrefix (Path p) (Path l) = case L.stripPrefix p l of Nothing -> throwM (NotAProperPrefix p l) Just "" -> throwM (NotAProperPrefix p l) Just ok -> return (Path ok) -- | Determines if the path in the first parameter is a proper prefix of the -- path in the second parameter. -- -- The following properties hold: -- -- @not (x \`isProperPrefixOf\` x)@ -- -- @x \`isProperPrefixOf\` (x \<\/\> y)@ -- -- @since 0.6.0 isProperPrefixOf :: Path b Dir -> Path b t -> Bool isProperPrefixOf p l = isJust (stripProperPrefix p l) -- | Change from one directory prefix to another. -- -- Throw 'NotAProperPrefix' if the first argument is not a proper prefix of the -- path. -- -- >>> replaceProperPrefix $(mkRelDir "foo") $(mkRelDir "bar") $(mkRelFile "foo/file.txt") == $(mkRelFile "bar/file.txt") replaceProperPrefix :: MonadThrow m => Path b Dir -> Path b' Dir -> Path b t -> m (Path b' t) replaceProperPrefix src dst fp = (dst ) <$> stripProperPrefix src fp -- | Take the parent path component from a path. -- -- The following properties hold: -- -- @ -- parent (x \<\/> y) == x -- parent \"\/x\" == \"\/\" -- parent \"x\" == \".\" -- @ -- -- On the root (absolute or relative), getting the parent is idempotent: -- -- @ -- parent \"\/\" = \"\/\" -- parent \"\.\" = \"\.\" -- @ -- parent :: Path b t -> Path b Dir parent (Path "") = Path "" parent (Path fp) | FilePath.isDrive fp = Path fp parent (Path fp) = Path $ normalizeDir $ FilePath.takeDirectory $ FilePath.dropTrailingPathSeparator fp -- | Extract the file part of a path. -- -- The following properties hold: -- -- @filename (p \<\/> a) == filename a@ -- filename :: Path b File -> Path Rel File filename (Path l) = Path (FilePath.takeFileName l) -- | Extract the last directory name of a path. -- -- The following properties hold: -- -- @dirname $(mkRelDir ".") == $(mkRelDir ".")@ -- -- @dirname (p \<\/> a) == dirname a@ -- dirname :: Path b Dir -> Path Rel Dir dirname (Path "") = Path "" dirname (Path l) | FilePath.isDrive l = Path "" dirname (Path l) = Path (last (FilePath.splitPath l)) -- | 'splitExtension' is the inverse of 'addExtension'. It splits the given -- file path into a valid filename and a valid extension. -- -- >>> splitExtension $(mkRelFile "name.foo" ) == Just ($(mkRelFile "name" ), ".foo" ) -- >>> splitExtension $(mkRelFile "name.foo." ) == Just ($(mkRelFile "name" ), ".foo." ) -- >>> splitExtension $(mkRelFile "name.foo.." ) == Just ($(mkRelFile "name" ), ".foo..") -- >>> splitExtension $(mkRelFile "name.bar.foo" ) == Just ($(mkRelFile "name.bar"), ".foo" ) -- >>> splitExtension $(mkRelFile ".name.foo" ) == Just ($(mkRelFile ".name" ), ".foo" ) -- >>> splitExtension $(mkRelFile "name..foo" ) == Just ($(mkRelFile "name." ), ".foo" ) -- >>> splitExtension $(mkRelFile "....foo" ) == Just ($(mkRelFile "..." ), ".foo" ) -- -- Throws 'HasNoExtension' exception if the filename does not have an extension -- or in other words it cannot be split into a valid filename and a valid -- extension. The following cases throw an exception, please note that "." and -- ".." are not valid filenames: -- -- >>> splitExtension $(mkRelFile "name" ) -- >>> splitExtension $(mkRelFile "name." ) -- >>> splitExtension $(mkRelFile "name.." ) -- >>> splitExtension $(mkRelFile ".name" ) -- >>> splitExtension $(mkRelFile "..name" ) -- >>> splitExtension $(mkRelFile "...name") -- -- 'splitExtension' and 'addExtension' are inverses of each other, the -- following laws hold: -- -- @ -- uncurry addExtension . swap >=> splitExtension == return -- splitExtension >=> uncurry addExtension . swap == return -- @ -- -- @since 0.7.0 splitExtension :: MonadThrow m => Path b File -> m (Path b File, String) splitExtension (Path fpath) = if nameDot == [] || ext == [] then throwM $ HasNoExtension fpath else let fname = init nameDot in if fname == [] || fname == "." || fname == ".." then throwM $ HasNoExtension fpath else return ( Path (normalizeDrive drv ++ dir ++ fname) , FilePath.extSeparator : ext ) where -- trailing separators are ignored for the split and considered part of the -- second component in the split. splitLast isSep str = let rstr = reverse str notSep = not . isSep name = (dropWhile notSep . dropWhile isSep) rstr trailingSeps = takeWhile isSep rstr xtn = (takeWhile notSep . dropWhile isSep) rstr in (reverse name, reverse xtn ++ trailingSeps) normalizeDrive | IS_WINDOWS = normalizeTrailingSeps | otherwise = id (drv, pth) = FilePath.splitDrive fpath (dir, file) = splitLast FilePath.isPathSeparator pth (nameDot, ext) = splitLast FilePath.isExtSeparator file -- | Get extension from given file path. Throws 'HasNoExtension' exception if -- the file does not have an extension. The following laws hold: -- -- @ -- flip addExtension file >=> fileExtension == return -- fileExtension == (fmap snd) . splitExtension -- @ -- -- @since 0.5.11 fileExtension :: MonadThrow m => Path b File -> m String fileExtension = (liftM snd) . splitExtension -- | Add extension to given file path. -- -- >>> addExtension ".foo" $(mkRelFile "name" ) == Just $(mkRelFile "name.foo" ) -- >>> addExtension ".foo." $(mkRelFile "name" ) == Just $(mkRelFile "name.foo." ) -- >>> addExtension ".foo.." $(mkRelFile "name" ) == Just $(mkRelFile "name.foo.." ) -- >>> addExtension ".foo" $(mkRelFile "name.bar" ) == Just $(mkRelFile "name.bar.foo") -- >>> addExtension ".foo" $(mkRelFile ".name" ) == Just $(mkRelFile ".name.foo" ) -- >>> addExtension ".foo" $(mkRelFile "name." ) == Just $(mkRelFile "name..foo" ) -- >>> addExtension ".foo" $(mkRelFile "..." ) == Just $(mkRelFile "....foo" ) -- -- Throws an 'InvalidExtension' exception if the extension is not valid. A -- valid extension starts with a @.@ followed by one or more characters not -- including @.@ followed by zero or more @.@ in trailing position. Moreover, -- an extension must be a valid filename, notably it cannot include path -- separators. Particularly, @.foo.bar@ is an invalid extension, instead you -- have to first set @.foo@ and then @.bar@ individually. Some examples of -- invalid extensions are: -- -- >>> addExtension "foo" $(mkRelFile "name") -- >>> addExtension "..foo" $(mkRelFile "name") -- >>> addExtension ".foo.bar" $(mkRelFile "name") -- >>> addExtension ".foo/bar" $(mkRelFile "name") -- -- @since 0.7.0 addExtension :: MonadThrow m => String -- ^ Extension to add -> Path b File -- ^ Old file name -> m (Path b File) -- ^ New file name with the desired extension added at the end addExtension ext (Path path) = do validateExtension ext return $ Path (path ++ ext) where validateExtension ex@(sep:xs) = do -- has to start with a "." when (not $ FilePath.isExtSeparator sep) $ throwM $ InvalidExtension ex -- just a "." is not a valid extension when (xs == []) $ throwM $ InvalidExtension ex -- cannot have path separators when (any FilePath.isPathSeparator xs) $ throwM $ InvalidExtension ex -- All "."s is not a valid extension let ys = dropWhile FilePath.isExtSeparator (reverse xs) when (ys == []) $ throwM $ InvalidExtension ex -- Cannot have "."s except in trailing position when (any FilePath.isExtSeparator ys) $ throwM $ InvalidExtension ex -- must be valid as a filename _ <- parseRelFile ex return () validateExtension ex = throwM $ InvalidExtension ex -- | Add extension to given file path. Throws if the -- resulting filename does not parse. -- -- >>> addFileExtension "txt $(mkRelFile "foo") -- "foo.txt" -- >>> addFileExtension "symbols" $(mkRelFile "Data.List") -- "Data.List.symbols" -- >>> addFileExtension ".symbols" $(mkRelFile "Data.List") -- "Data.List.symbols" -- >>> addFileExtension "symbols" $(mkRelFile "Data.List.") -- "Data.List..symbols" -- >>> addFileExtension ".symbols" $(mkRelFile "Data.List.") -- "Data.List..symbols" -- >>> addFileExtension "evil/" $(mkRelFile "Data.List") -- *** Exception: InvalidRelFile "Data.List.evil/" -- -- @since 0.6.1 {-# DEPRECATED addFileExtension "Please use addExtension instead." #-} addFileExtension :: MonadThrow m => String -- ^ Extension to add -> Path b File -- ^ Old file name -> m (Path b File) -- ^ New file name with the desired extension added at the end addFileExtension ext (Path path) = if FilePath.isAbsolute path then liftM coercePath (parseAbsFile (FilePath.addExtension path ext)) else liftM coercePath (parseRelFile (FilePath.addExtension path ext)) where coercePath :: Path a b -> Path a' b' coercePath (Path a) = Path a -- | A synonym for 'addFileExtension' in the form of an infix operator. -- See more examples there. -- -- >>> $(mkRelFile "Data.List") <.> "symbols" -- "Data.List.symbols" -- >>> $(mkRelFile "Data.List") <.> "evil/" -- *** Exception: InvalidRelFile "Data.List.evil/" -- -- @since 0.6.1 infixr 7 <.> {-# DEPRECATED (<.>) "Please use addExtension instead." #-} (<.>) :: MonadThrow m => Path b File -- ^ Old file name -> String -- ^ Extension to add -> m (Path b File) -- ^ New file name with the desired extension added at the end (<.>) = flip addFileExtension -- | If the file has an extension replace it with the given extension otherwise -- add the new extension to it. Throws an 'InvalidExtension' exception if the -- new extension is not a valid extension (see 'fileExtension' for validity -- rules). -- -- The following law holds: -- -- @(fileExtension >=> flip replaceExtension file) file == return file@ -- -- @since 0.7.0 replaceExtension :: MonadThrow m => String -- ^ Extension to set -> Path b File -- ^ Old file name -> m (Path b File) -- ^ New file name with the desired extension replaceExtension ext path = addExtension ext (maybe path fst $ splitExtension path) -- | Replace\/add extension to given file path. Throws if the -- resulting filename does not parse. -- -- @since 0.5.11 {-# DEPRECATED setFileExtension "Please use replaceExtension instead." #-} setFileExtension :: MonadThrow m => String -- ^ Extension to set -> Path b File -- ^ Old file name -> m (Path b File) -- ^ New file name with the desired extension setFileExtension ext (Path path) = if FilePath.isAbsolute path then liftM coercePath (parseAbsFile (FilePath.replaceExtension path ext)) else liftM coercePath (parseRelFile (FilePath.replaceExtension path ext)) where coercePath :: Path a b -> Path a' b' coercePath (Path a) = Path a -- | A synonym for 'setFileExtension' in the form of an operator. -- -- @since 0.6.0 infixr 7 -<.> {-# DEPRECATED (-<.>) "Please use replaceExtension instead." #-} (-<.>) :: MonadThrow m => Path b File -- ^ Old file name -> String -- ^ Extension to set -> m (Path b File) -- ^ New file name with the desired extension (-<.>) = flip setFileExtension -------------------------------------------------------------------------------- -- Parsers -- | Convert an absolute 'FilePath' to a normalized absolute dir 'Path'. -- -- Throws: 'InvalidAbsDir' when the supplied path: -- -- * is not an absolute path -- * contains a @..@ path component representing the parent directory -- * is not a valid path (See 'FilePath.isValid') -- parseAbsDir :: MonadThrow m => FilePath -> m (Path Abs Dir) parseAbsDir filepath = if FilePath.isAbsolute filepath && not (hasParentDir filepath) && FilePath.isValid filepath then return (Path (normalizeDir filepath)) else throwM (InvalidAbsDir filepath) -- | Convert a relative 'FilePath' to a normalized relative dir 'Path'. -- -- Throws: 'InvalidRelDir' when the supplied path: -- -- * is not a relative path -- * is @""@ -- * contains a @..@ path component representing the parent directory -- * is not a valid path (See 'FilePath.isValid') -- * is all path separators -- parseRelDir :: MonadThrow m => FilePath -> m (Path Rel Dir) parseRelDir filepath = if not (FilePath.isAbsolute filepath) && not (hasParentDir filepath) && not (null filepath) && not (all FilePath.isPathSeparator filepath) && FilePath.isValid filepath then return (Path (normalizeDir filepath)) else throwM (InvalidRelDir filepath) -- | Convert an absolute 'FilePath' to a normalized absolute file 'Path'. -- -- Throws: 'InvalidAbsFile' when the supplied path: -- -- * is not an absolute path -- * is a directory path i.e. -- -- * has a trailing path separator -- * is @.@ or ends in @/.@ -- -- * contains a @..@ path component representing the parent directory -- * is not a valid path (See 'FilePath.isValid') -- parseAbsFile :: MonadThrow m => FilePath -> m (Path Abs File) parseAbsFile filepath = case validAbsFile filepath of True | normalized <- normalizeFilePath filepath , validAbsFile normalized -> return (Path normalized) _ -> throwM (InvalidAbsFile filepath) -- | Is the string a valid absolute file? validAbsFile :: FilePath -> Bool validAbsFile filepath = FilePath.isAbsolute filepath && not (FilePath.hasTrailingPathSeparator filepath) && not (hasParentDir filepath) && FilePath.isValid filepath -- | Convert a relative 'FilePath' to a normalized relative file 'Path'. -- -- Throws: 'InvalidRelFile' when the supplied path: -- -- * is not a relative path -- * is @""@ -- * is a directory path i.e. -- -- * has a trailing path separator -- * is @.@ or ends in @/.@ -- -- * contains a @..@ path component representing the parent directory -- * is not a valid path (See 'FilePath.isValid') -- parseRelFile :: MonadThrow m => FilePath -> m (Path Rel File) parseRelFile filepath = case validRelFile filepath of True | normalized <- normalizeFilePath filepath , validRelFile normalized -> return (Path normalized) _ -> throwM (InvalidRelFile filepath) -- | Is the string a valid relative file? validRelFile :: FilePath -> Bool validRelFile filepath = not (FilePath.isAbsolute filepath || FilePath.hasTrailingPathSeparator filepath) && not (null filepath) && not (hasParentDir filepath) && filepath /= "." && FilePath.isValid filepath -------------------------------------------------------------------------------- -- Conversion -- | Convert absolute path to directory to 'FilePath' type. fromAbsDir :: Path Abs Dir -> FilePath fromAbsDir = toFilePath -- | Convert relative path to directory to 'FilePath' type. fromRelDir :: Path Rel Dir -> FilePath fromRelDir = toFilePath -- | Convert absolute path to file to 'FilePath' type. fromAbsFile :: Path Abs File -> FilePath fromAbsFile = toFilePath -- | Convert relative path to file to 'FilePath' type. fromRelFile :: Path Rel File -> FilePath fromRelFile = toFilePath -------------------------------------------------------------------------------- -- Constructors -- | Make a 'Path' 'Abs' 'Dir'. -- -- Remember: due to the nature of absolute paths this (e.g. @\/home\/foo@) -- may compile on your platform, but it may not compile on another -- platform (Windows). mkAbsDir :: FilePath -> Q Exp mkAbsDir = either (error . show) lift . parseAbsDir -- | Make a 'Path' 'Rel' 'Dir'. mkRelDir :: FilePath -> Q Exp mkRelDir = either (error . show) lift . parseRelDir -- | Make a 'Path' 'Abs' 'File'. -- -- Remember: due to the nature of absolute paths this (e.g. @\/home\/foo@) -- may compile on your platform, but it may not compile on another -- platform (Windows). mkAbsFile :: FilePath -> Q Exp mkAbsFile = either (error . show) lift . parseAbsFile -- | Make a 'Path' 'Rel' 'File'. mkRelFile :: FilePath -> Q Exp mkRelFile = either (error . show) lift . parseRelFile -------------------------------------------------------------------------------- -- Internal functions -- | Normalizes directory path with platform-specific rules. normalizeDir :: FilePath -> FilePath normalizeDir = normalizeRelDir . FilePath.addTrailingPathSeparator . normalizeFilePath where -- Represent a "." in relative dir path as "" internally so that it -- composes without having to renormalize the path. normalizeRelDir p | p == relRootFP = "" | otherwise = p -- | Replaces consecutive path seps with single sep and replaces alt sep with standard sep. normalizeAllSeps :: FilePath -> FilePath normalizeAllSeps = foldr normSeps [] where normSeps ch [] = [ch] normSeps ch path@(p0:_) | FilePath.isPathSeparator ch && FilePath.isPathSeparator p0 = path | FilePath.isPathSeparator ch = FilePath.pathSeparator:path | otherwise = ch:path -- | Normalizes seps in whole path, but if there are 2+ seps at the beginning, -- they are normalized to exactly 2 to preserve UNC and Unicode prefixed paths. normalizeWindowsSeps :: FilePath -> FilePath normalizeWindowsSeps path = normLeadingSeps ++ normalizeAllSeps rest where (leadingSeps, rest) = span FilePath.isPathSeparator path normLeadingSeps = replicate (min 2 (length leadingSeps)) FilePath.pathSeparator -- | Normalizes seps only at the beginning of a path. normalizeLeadingSeps :: FilePath -> FilePath normalizeLeadingSeps path = normLeadingSep ++ rest where (leadingSeps, rest) = span FilePath.isPathSeparator path normLeadingSep = replicate (min 1 (length leadingSeps)) FilePath.pathSeparator -- | Normalizes seps only at the end of a path. normalizeTrailingSeps :: FilePath -> FilePath normalizeTrailingSeps = reverse . normalizeLeadingSeps . reverse -- | Applies platform-specific sep normalization following @FilePath.normalise@. normalizeFilePath :: FilePath -> FilePath normalizeFilePath | IS_WINDOWS = normalizeWindowsSeps . FilePath.normalise | otherwise = normalizeLeadingSeps . FilePath.normalise -- | Path of some type. @t@ represents the type, whether file or -- directory. Pattern match to find whether the path is absolute or -- relative. data SomeBase t = Abs (Path Abs t) | Rel (Path Rel t) deriving (Typeable, Generic, Eq, Ord) instance NFData (SomeBase t) where rnf (Abs p) = rnf p rnf (Rel p) = rnf p instance Show (SomeBase t) where show = show . fromSomeBase instance ToJSON (SomeBase t) where toJSON = toJSON . fromSomeBase {-# INLINE toJSON #-} #if MIN_VERSION_aeson(0,10,0) toEncoding = toEncoding . fromSomeBase {-# INLINE toEncoding #-} #endif instance Hashable (SomeBase t) where -- See 'Hashable' 'Path' instance for details. hashWithSalt n path = hashWithSalt n (fromSomeBase path) instance FromJSON (SomeBase Dir) where parseJSON = parseJSONWith parseSomeDir {-# INLINE parseJSON #-} instance FromJSON (SomeBase File) where parseJSON = parseJSONWith parseSomeFile {-# INLINE parseJSON #-} -- | Helper to project the contents out of a SomeBase object. -- -- >>> prjSomeBase toFilePath (Abs [absfile|/foo/bar/cow.moo|]) == "/foo/bar/cow.moo" -- prjSomeBase :: (forall b . Path b t -> a) -> SomeBase t -> a prjSomeBase f = \case Abs a -> f a Rel r -> f r -- | Helper to apply a function to the SomeBase object -- -- >>> mapSomeBase parent (Abs [absfile|/foo/bar/cow.moo|]) == Abs [absdir|"/foo/bar"|] -- mapSomeBase :: (forall b . Path b t -> Path b t') -> SomeBase t -> SomeBase t' mapSomeBase f = \case Abs a -> Abs $ f a Rel r -> Rel $ f r -- | Convert a valid path to a 'FilePath'. fromSomeBase :: SomeBase t -> FilePath fromSomeBase = prjSomeBase toFilePath -- | Convert a valid directory to a 'FilePath'. fromSomeDir :: SomeBase Dir -> FilePath fromSomeDir = fromSomeBase -- | Convert a valid file to a 'FilePath'. fromSomeFile :: SomeBase File -> FilePath fromSomeFile = fromSomeBase -- | Convert an absolute or relative 'FilePath' to a normalized 'SomeBase' -- representing a directory. -- -- Throws: 'InvalidDir' when the supplied path: -- -- * contains a @..@ path component representing the parent directory -- * is not a valid path (See 'FilePath.isValid') parseSomeDir :: MonadThrow m => FilePath -> m (SomeBase Dir) parseSomeDir fp = maybe (throwM (InvalidDir fp)) pure $ (Abs <$> parseAbsDir fp) <|> (Rel <$> parseRelDir fp) -- | Convert an absolute or relative 'FilePath' to a normalized 'SomeBase' -- representing a file. -- -- Throws: 'InvalidFile' when the supplied path: -- -- * is a directory path i.e. -- -- * has a trailing path separator -- * is @.@ or ends in @/.@ -- -- * contains a @..@ path component representing the parent directory -- * is not a valid path (See 'FilePath.isValid') parseSomeFile :: MonadThrow m => FilePath -> m (SomeBase File) parseSomeFile fp = maybe (throwM (InvalidFile fp)) pure $ (Abs <$> parseAbsFile fp) <|> (Rel <$> parseRelFile fp) -------------------------------------------------------------------------------- -- Deprecated {-# DEPRECATED PathParseException "Please use PathException instead." #-} -- | Same as 'PathException'. type PathParseException = PathException {-# DEPRECATED stripDir "Please use stripProperPrefix instead." #-} -- | Same as 'stripProperPrefix'. stripDir :: MonadThrow m => Path b Dir -> Path b t -> m (Path Rel t) stripDir = stripProperPrefix {-# DEPRECATED isParentOf "Please use isProperPrefixOf instead." #-} -- | Same as 'isProperPrefixOf'. isParentOf :: Path b Dir -> Path b t -> Bool isParentOf = isProperPrefixOf path-0.9.2/src/Path/Internal/Include.hs0000644000000000000000000001030014162173754016026 0ustar0000000000000000-- This template expects CPP definitions for: -- PLATFORM_NAME = Posix | Windows -- IS_WINDOWS = False | True {-# LANGUAGE CPP #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} -- | Internal types and functions. module Path.Internal.PLATFORM_NAME ( Path(..) , relRootFP , toFilePath , hasParentDir ) where import Control.DeepSeq (NFData (..)) import Data.Aeson (ToJSON (..), ToJSONKey(..)) import Data.Aeson.Types (toJSONKeyText) import qualified Data.Text as T (pack) import GHC.Generics (Generic) import Data.Data import Data.Hashable import qualified Data.List as L import qualified Language.Haskell.TH.Syntax as TH import qualified System.FilePath.PLATFORM_NAME as FilePath -- | Path of some base and type. -- -- The type variables are: -- -- * @b@ — base, the base location of the path; absolute or relative. -- * @t@ — type, whether file or directory. -- -- Internally is a string. The string can be of two formats only: -- -- 1. File format: @file.txt@, @foo\/bar.txt@, @\/foo\/bar.txt@ -- 2. Directory format: @foo\/@, @\/foo\/bar\/@ -- -- All directories end in a trailing separator. There are no duplicate -- path separators @\/\/@, no @..@, no @.\/@, no @~\/@, etc. newtype Path b t = Path FilePath deriving (Data, Typeable, Generic) -- | String equality. -- -- The following property holds: -- -- @show x == show y ≡ x == y@ instance Eq (Path b t) where (==) (Path x) (Path y) = x == y -- | String ordering. -- -- The following property holds: -- -- @show x \`compare\` show y ≡ x \`compare\` y@ instance Ord (Path b t) where compare (Path x) (Path y) = compare x y -- | Normalized file path representation for the relative path root relRootFP :: FilePath relRootFP = '.' : [FilePath.pathSeparator] -- | Convert to a 'FilePath' type. -- -- All directories have a trailing slash, so if you want no trailing -- slash, you can use 'System.FilePath.dropTrailingPathSeparator' from -- the filepath package. toFilePath :: Path b t -> FilePath toFilePath (Path []) = relRootFP toFilePath (Path x) = x -- | Helper function: check if the filepath has any parent directories in it. -- This handles the logic of checking for different path separators on Windows. hasParentDir :: FilePath -> Bool hasParentDir filepath' = (filepath' == "..") || ("/.." `L.isSuffixOf` filepath) || ("/../" `L.isInfixOf` filepath) || ("../" `L.isPrefixOf` filepath) where filepath = case FilePath.pathSeparator of '/' -> filepath' x -> map (\y -> if x == y then '/' else y) filepath' -- | Same as 'show . Path.toFilePath'. -- -- The following property holds: -- -- @x == y ≡ show x == show y@ instance Show (Path b t) where show = show . toFilePath instance NFData (Path b t) where rnf (Path x) = rnf x instance ToJSON (Path b t) where toJSON = toJSON . toFilePath {-# INLINE toJSON #-} #if MIN_VERSION_aeson(0,10,0) toEncoding = toEncoding . toFilePath {-# INLINE toEncoding #-} #endif instance ToJSONKey (Path b t) where toJSONKey = toJSONKeyText $ T.pack . toFilePath instance Hashable (Path b t) where -- A "." is represented as an empty string ("") internally. Hashing "" -- results in a hash that is the same as the salt. To produce a more -- reasonable hash we use "toFilePath" before hashing so that a "" gets -- converted back to a ".". hashWithSalt n path = hashWithSalt n (toFilePath path) instance forall b t. (Typeable b, Typeable t) => TH.Lift (Path b t) where lift (Path str) = do let b = TH.ConT $ getTCName (Proxy :: Proxy b) t = TH.ConT $ getTCName (Proxy :: Proxy t) [|Path $(pure (TH.LitE (TH.StringL str))) :: Path $(pure b) $(pure t) |] where getTCName :: Typeable a => proxy a -> TH.Name getTCName a = TH.Name occ flav where tc = typeRepTyCon (typeRep a) occ = TH.OccName (tyConName tc) flav = TH.NameG TH.TcClsName (TH.PkgName (tyConPackage tc)) (TH.ModName (tyConModule tc)) #if MIN_VERSION_template_haskell(2,17,0) liftTyped = TH.unsafeCodeCoerce . TH.lift #elif MIN_VERSION_template_haskell(2,16,0) liftTyped = TH.unsafeTExpCoerce . TH.lift #endif path-0.9.2/test/Common/Include.hs0000644000000000000000000000717214162173754015013 0ustar0000000000000000-- This template expects CPP definitions for: -- PLATFORM_NAME = Posix | Windows -- IS_WINDOWS = False | True {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TemplateHaskell #-} -- | Test functions that are common to Posix and Windows module Common.PLATFORM_NAME (extensionOperations) where import Control.Monad import qualified Language.Haskell.TH.Syntax as TH import Path.Internal.PLATFORM_NAME import Path.PLATFORM_NAME import System.FilePath.PLATFORM_NAME (pathSeparator) import Test.Hspec class Foo a b where foo :: Path a b -> FilePath foo = toFilePath instance Foo Abs Dir instance Foo Abs File instance Foo Rel Dir instance Foo Rel File qqRelDir :: FilePath qqRelDir = foo [reldir|foo/|] qqRelFile :: FilePath qqRelFile = foo [relfile|foo|] thRelDir :: FilePath thRelDir = foo $(mkRelDir "foo/") thRelFile :: FilePath thRelFile = foo $(mkRelFile "foo") liftRelDir :: FilePath liftRelDir = foo $(TH.lift (Path "foo/" :: Path Rel Dir)) liftRelFile :: FilePath liftRelFile = foo $(TH.lift (Path "foo" :: Path Rel File)) validExtensionsSpec :: String -> Path b File -> Path b File -> Spec validExtensionsSpec ext file fext = do let f = show $ toFilePath file let fx = show $ toFilePath fext it ("addExtension " ++ show ext ++ " " ++ f ++ " == " ++ fx) $ addExtension ext file `shouldReturn` fext it ("fileExtension " ++ fx ++ " == " ++ ext) $ fileExtension fext `shouldReturn` ext it ("replaceExtension " ++ show ext ++ " " ++ fx ++ " == " ++ fx) $ replaceExtension ext fext `shouldReturn` fext extensionOperations :: String -> Spec extensionOperations rootDrive = do let extension = ".foo" let extensions = extension : [".foo.", ".foo.."] describe "Only filenames and extensions" $ forM_ extensions $ \ext -> forM_ filenames $ \f -> do runTests parseRelFile f ext describe "Relative dir paths" $ forM_ dirnames $ \d -> do forM_ filenames $ \f -> do let f1 = d ++ [pathSeparator] ++ f runTests parseRelFile f1 extension describe "Absolute dir paths" $ forM_ dirnames $ \d -> do forM_ filenames $ \f -> do let f1 = rootDrive ++ d ++ [pathSeparator] ++ f runTests parseAbsFile f1 extension -- Invalid extensions forM_ invalidExtensions $ \ext -> do it ("throws InvalidExtension when extension is [" ++ ext ++ "]") $ addExtension ext $(mkRelFile "name") `shouldThrow` (== InvalidExtension ext) where runTests parse file ext = do let maybePathFile = parse file let maybePathFileWithExt = parse (file ++ ext) case (maybePathFile, maybePathFileWithExt) of (Just pathFile, Just pathFileWithExt) -> validExtensionsSpec ext pathFile pathFileWithExt _ -> it ("Files " ++ show file ++ " and/or " ++ show (file ++ ext) ++ " should parse successfully.") $ expectationFailure $ show file ++ " parsed to " ++ show maybePathFile ++ ", " ++ show (file ++ ext) ++ " parsed to " ++ show maybePathFileWithExt filenames = [ "name" , "name." , "name.." , ".name" , "..name" , "name.name" , "name..name" , "..." ] dirnames = filenames ++ ["."] invalidExtensions = [ "" , "." , "x" , ".." , "..." , "xy" , "foo" , "foo." , "foo.." , "..foo" , "...foo" , ".foo.bar" , ".foo" ++ [pathSeparator] ++ "bar" ] path-0.9.2/LICENSE0000644000000000000000000000272414162173754011670 0ustar0000000000000000Copyright (c) 2015–2018, FP Complete All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: * Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. * Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. * Neither the name of paths nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. path-0.9.2/Setup.hs0000644000000000000000000000005614162173754012313 0ustar0000000000000000import Distribution.Simple main = defaultMain path-0.9.2/path.cabal0000644000000000000000000000631114162271704012571 0ustar0000000000000000name: path version: 0.9.2 synopsis: Support for well-typed paths description: Support for well-typed paths. license: BSD3 license-file: LICENSE author: Chris Done maintainer: Chris Done copyright: 2015–2018 FP Complete category: System, Filesystem build-type: Simple cabal-version: 1.18 tested-with: GHC==8.6.5, GHC==8.8.4, GHC==8.10.1 extra-source-files: README.md , CHANGELOG , src/Path/Include.hs , src/Path/Internal/Include.hs , test/Common/Include.hs flag dev description: Turn on development settings. manual: True default: False library hs-source-dirs: src exposed-modules: Path , Path.Posix , Path.Windows , Path.Internal , Path.Internal.Posix , Path.Internal.Windows build-depends: aeson , base >= 4.12 && < 5 , deepseq , exceptions >= 0.4 && < 0.11 , filepath < 1.2.0.1 || >= 1.3 , hashable >= 1.2 && < 1.5 , text , template-haskell if flag(dev) ghc-options: -Wall -Werror else ghc-options: -O2 -Wall if flag(dev) ghc-options: -Wcompat -Wincomplete-record-updates -Wincomplete-uni-patterns -Wnoncanonical-monad-instances default-language: Haskell2010 test-suite test type: exitcode-stdio-1.0 main-is: Main.hs other-modules: Posix , Windows , Common.Posix , Common.Windows hs-source-dirs: test build-depends: aeson , base >= 4.12 && < 5 , bytestring , filepath < 1.2.0.1 || >= 1.3 , hspec >= 2.0 && < 3 , mtl >= 2.0 && < 3 , path , template-haskell if flag(dev) ghc-options: -Wall -Werror else ghc-options: -O2 -Wall default-language: Haskell2010 test-suite validity-test type: exitcode-stdio-1.0 main-is: ValidityTest.hs other-modules: Path.Gen hs-source-dirs: test build-depends: QuickCheck , aeson , base >= 4.12 && < 5 , bytestring , filepath < 1.2.0.1 || >= 1.3 , genvalidity >= 1.0 , genvalidity-property >= 0.4 , genvalidity-hspec >= 0.7 , hspec >= 2.0 && < 3 , mtl >= 2.0 && < 3 , path , validity >= 0.8.0.0 default-language: Haskell2010 ghc-options: -threaded -rtsopts -with-rtsopts=-N source-repository head type: git location: https://github.com/commercialhaskell/path.git