module Path
(
Path
,Abs
,Rel
,File
,Dir
,parseAbsDir
,parseRelDir
,parseAbsFile
,parseRelFile
,PathParseException
,mkAbsDir
,mkRelDir
,mkAbsFile
,mkRelFile
,(</>)
,stripDir
,isParentOf
,parent
,filename
,dirname
,fileExtension
,setFileExtension
,toFilePath
,fromAbsDir
,fromRelDir
,fromAbsFile
,fromRelFile
)
where
import Control.Exception (Exception)
import Control.Monad.Catch (MonadThrow(..))
import Data.Aeson (FromJSON (..))
import qualified Data.Aeson.Types as Aeson
import Data.Coerce
import Data.Data
import Data.List
import Data.Maybe
import Language.Haskell.TH
import Path.Internal
import qualified System.FilePath as FilePath
data Abs deriving (Typeable)
data Rel deriving (Typeable)
data File deriving (Typeable)
data Dir deriving (Typeable)
instance FromJSON (Path Abs File) where
parseJSON = parseJSONWith parseAbsFile
instance FromJSON (Path Rel File) where
parseJSON = parseJSONWith parseRelFile
instance FromJSON (Path Abs Dir) where
parseJSON = parseJSONWith parseAbsDir
instance FromJSON (Path Rel Dir) where
parseJSON = parseJSONWith parseRelDir
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)
data PathParseException
= InvalidAbsDir FilePath
| InvalidRelDir FilePath
| InvalidAbsFile FilePath
| InvalidRelFile FilePath
| Couldn'tStripPrefixDir FilePath FilePath
deriving (Show,Typeable)
instance Exception PathParseException
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)
parseRelDir :: MonadThrow m
=> FilePath -> m (Path Rel Dir)
parseRelDir filepath =
if not (FilePath.isAbsolute filepath) &&
not (hasParentDir filepath) &&
not (null filepath) &&
filepath /= "." &&
normalizeFilePath filepath /= curDirNormalizedFP &&
filepath /= ".." &&
FilePath.isValid filepath
then return (Path (normalizeDir filepath))
else throwM (InvalidRelDir filepath)
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)
validAbsFile :: FilePath -> Bool
validAbsFile filepath =
FilePath.isAbsolute filepath &&
not (FilePath.hasTrailingPathSeparator filepath) &&
not (hasParentDir filepath) &&
FilePath.isValid filepath
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)
validRelFile :: FilePath -> Bool
validRelFile filepath =
not
(FilePath.isAbsolute filepath || FilePath.hasTrailingPathSeparator filepath) &&
not (null filepath) &&
not (hasParentDir filepath) &&
filepath /= "." && filepath /= ".." && FilePath.isValid filepath
hasParentDir :: FilePath -> Bool
hasParentDir filepath' =
("/.." `isSuffixOf` filepath) ||
("/../" `isInfixOf` filepath) ||
("../" `isPrefixOf` filepath)
where
filepath =
case FilePath.pathSeparator of
'/' -> filepath'
x -> map (\y -> if x == y then '/' else y) filepath'
mkAbsDir :: FilePath -> Q Exp
mkAbsDir s =
case parseAbsDir s of
Left err -> error (show err)
Right (Path str) ->
[|Path $(return (LitE (StringL str))) :: Path Abs Dir|]
mkRelDir :: FilePath -> Q Exp
mkRelDir s =
case parseRelDir s of
Left err -> error (show err)
Right (Path str) ->
[|Path $(return (LitE (StringL str))) :: Path Rel Dir|]
mkAbsFile :: FilePath -> Q Exp
mkAbsFile s =
case parseAbsFile s of
Left err -> error (show err)
Right (Path str) ->
[|Path $(return (LitE (StringL str))) :: Path Abs File|]
mkRelFile :: FilePath -> Q Exp
mkRelFile s =
case parseRelFile s of
Left err -> error (show err)
Right (Path str) ->
[|Path $(return (LitE (StringL str))) :: Path Rel File|]
toFilePath :: Path b t -> FilePath
toFilePath (Path l) = l
fromAbsDir :: Path Abs Dir -> FilePath
fromAbsDir = toFilePath
fromRelDir :: Path Rel Dir -> FilePath
fromRelDir = toFilePath
fromAbsFile :: Path Abs File -> FilePath
fromAbsFile = toFilePath
fromRelFile :: Path Rel File -> FilePath
fromRelFile = toFilePath
(</>) :: Path b Dir -> Path Rel t -> Path b t
(</>) (Path a) (Path b) = Path (a ++ b)
stripDir :: MonadThrow m
=> Path b Dir -> Path b t -> m (Path Rel t)
stripDir (Path p) (Path l) =
case stripPrefix p l of
Nothing -> throwM (Couldn'tStripPrefixDir p l)
Just "" -> throwM (Couldn'tStripPrefixDir p l)
Just ok -> return (Path ok)
isParentOf :: Path b Dir -> Path b t -> Bool
isParentOf p l =
isJust (stripDir p l)
parent :: Path Abs t -> Path Abs Dir
parent (Path fp) =
Path (normalizeDir (FilePath.takeDirectory (FilePath.dropTrailingPathSeparator fp)))
filename :: Path b File -> Path Rel File
filename (Path l) =
Path (FilePath.takeFileName l)
dirname :: Path b Dir -> Path Rel Dir
dirname (Path l) =
Path (last (FilePath.splitPath l))
fileExtension :: Path b File -> String
fileExtension = FilePath.takeExtension . toFilePath
setFileExtension :: MonadThrow m
=> String
-> Path b File
-> m (Path b File)
setFileExtension ext (Path path) =
if FilePath.isAbsolute path
then fmap coerce (parseAbsFile (FilePath.replaceExtension path ext))
else fmap coerce (parseRelFile (FilePath.replaceExtension path ext))
curDirNormalizedFP :: FilePath
curDirNormalizedFP = '.' : [FilePath.pathSeparator]
normalizeDir :: FilePath -> FilePath
normalizeDir = FilePath.addTrailingPathSeparator . normalizeFilePath
normalizeFilePath :: FilePath -> FilePath
#if defined(mingw32_HOST_OS) || defined(__MINGW32__) || MIN_VERSION_filepath(1,4,0)
normalizeFilePath = FilePath.normalise
#else
normalizeFilePath = normalizeLeadingSeparators . FilePath.normalise
where
sep = FilePath.pathSeparator
normalizeLeadingSeparators (x1:x2:xs) | x1 == sep && x2 == sep
= normalizeLeadingSeparators (sep:xs)
normalizeLeadingSeparators x = x
#endif