{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE ViewPatterns      #-}

-- | Extra Path utilities.


module Path.Extra
  ( toFilePathNoTrailingSep
  , dropRoot
  , parseCollapsedAbsDir
  , parseCollapsedAbsFile
  , concatAndCollapseAbsDir
  , rejectMissingFile
  , rejectMissingDir
  , pathToByteString
  , pathToLazyByteString
  , pathToText
  , tryGetModificationTime
  ) where

import           Data.Time ( UTCTime )
import           Path
import           Path.IO
import           Path.Internal ( Path (..) )
import           RIO
import           System.IO.Error ( isDoesNotExistError )
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString.Lazy.Char8 as BSL
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified System.FilePath as FP

-- | Convert to FilePath but don't add a trailing slash.

toFilePathNoTrailingSep :: Path loc Dir -> FilePath
toFilePathNoTrailingSep :: forall loc. Path loc Dir -> FilePath
toFilePathNoTrailingSep = FilePath -> FilePath
FP.dropTrailingPathSeparator forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b t. Path b t -> FilePath
toFilePath

-- | Collapse intermediate "." and ".." directories from path, then parse

-- it with 'parseAbsDir'.

-- (probably should be moved to the Path module)

parseCollapsedAbsDir :: MonadThrow m => FilePath -> m (Path Abs Dir)
parseCollapsedAbsDir :: forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs Dir)
parseCollapsedAbsDir = forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs Dir)
parseAbsDir forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
collapseFilePath

-- | Collapse intermediate "." and ".." directories from path, then parse

-- it with 'parseAbsFile'.

-- (probably should be moved to the Path module)

parseCollapsedAbsFile :: MonadThrow m => FilePath -> m (Path Abs File)
parseCollapsedAbsFile :: forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs File)
parseCollapsedAbsFile = forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs File)
parseAbsFile forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
collapseFilePath

-- | Add a relative FilePath to the end of a Path

-- We can't parse the FilePath first because we need to account for ".."

-- in the FilePath (#2895)

concatAndCollapseAbsDir :: MonadThrow m => Path Abs Dir -> FilePath -> m (Path Abs Dir)
concatAndCollapseAbsDir :: forall (m :: * -> *).
MonadThrow m =>
Path Abs Dir -> FilePath -> m (Path Abs Dir)
concatAndCollapseAbsDir Path Abs Dir
base FilePath
rel = forall (m :: * -> *). MonadThrow m => FilePath -> m (Path Abs Dir)
parseCollapsedAbsDir (forall b t. Path b t -> FilePath
toFilePath Path Abs Dir
base FilePath -> FilePath -> FilePath
FP.</> FilePath
rel)

-- | Collapse intermediate "." and ".." directories from a path.

--

-- > collapseFilePath "./foo" == "foo"

-- > collapseFilePath "/bar/../baz" == "/baz"

-- > collapseFilePath "/../baz" == "/../baz"

-- > collapseFilePath "parent/foo/baz/../bar" ==  "parent/foo/bar"

-- > collapseFilePath "parent/foo/baz/../../bar" ==  "parent/bar"

-- > collapseFilePath "parent/foo/.." ==  "parent"

-- > collapseFilePath "/parent/foo/../../bar" ==  "/bar"

--

-- (adapted from @Text.Pandoc.Shared@)

collapseFilePath :: FilePath -> FilePath
collapseFilePath :: FilePath -> FilePath
collapseFilePath = [FilePath] -> FilePath
FP.joinPath forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' [FilePath] -> FilePath -> [FilePath]
go [] forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> [FilePath]
FP.splitDirectories
  where
    go :: [FilePath] -> FilePath -> [FilePath]
go [FilePath]
rs FilePath
"." = [FilePath]
rs
    go r :: [FilePath]
r@(FilePath
p:[FilePath]
rs) FilePath
".." = case FilePath
p of
                            FilePath
".." -> FilePath
".."forall a. a -> [a] -> [a]
:[FilePath]
r
                            (FilePath -> Bool
checkPathSeparator -> Bool
True) -> FilePath
".."forall a. a -> [a] -> [a]
:[FilePath]
r
                            FilePath
_ -> [FilePath]
rs
    go [FilePath]
_ (FilePath -> Bool
checkPathSeparator -> Bool
True) = [[Char
FP.pathSeparator]]
    go [FilePath]
rs FilePath
x = FilePath
xforall a. a -> [a] -> [a]
:[FilePath]
rs
    checkPathSeparator :: FilePath -> Bool
checkPathSeparator [Char
x] = Char -> Bool
FP.isPathSeparator Char
x
    checkPathSeparator FilePath
_ = Bool
False

-- | Drop the root (either @\/@ on POSIX or @C:\\@, @D:\\@, etc. on

-- Windows).

dropRoot :: Path Abs t -> Path Rel t
dropRoot :: forall t. Path Abs t -> Path Rel t
dropRoot (Path FilePath
l) = forall b t. FilePath -> Path b t
Path (FilePath -> FilePath
FP.dropDrive FilePath
l)

-- | If given file in 'Maybe' does not exist, ensure we have 'Nothing'. This

-- is to be used in conjunction with 'forgivingAbsence' and

-- 'resolveFile'.

--

-- Previously the idiom @forgivingAbsence (resolveFile …)@ alone was used,

-- which relied on 'canonicalizePath' throwing 'isDoesNotExistError' when

-- path does not exist. As it turns out, this behavior is actually not

-- intentional and unreliable, see

-- <https://github.com/haskell/directory/issues/44>. This was “fixed” in

-- version @1.2.3.0@ of @directory@ package (now it never throws). To make

-- it work with all versions, we need to use the following idiom:

--

-- > forgivingAbsence (resolveFile …) >>= rejectMissingFile


rejectMissingFile :: MonadIO m
  => Maybe (Path Abs File)
  -> m (Maybe (Path Abs File))
rejectMissingFile :: forall (m :: * -> *).
MonadIO m =>
Maybe (Path Abs File) -> m (Maybe (Path Abs File))
rejectMissingFile Maybe (Path Abs File)
Nothing = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
rejectMissingFile (Just Path Abs File
p) = forall a. a -> a -> Bool -> a
bool forall a. Maybe a
Nothing (forall a. a -> Maybe a
Just Path Abs File
p) forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` forall (m :: * -> *) b. MonadIO m => Path b File -> m Bool
doesFileExist Path Abs File
p

-- | See 'rejectMissingFile'.


rejectMissingDir :: MonadIO m
  => Maybe (Path Abs Dir)
  -> m (Maybe (Path Abs Dir))
rejectMissingDir :: forall (m :: * -> *).
MonadIO m =>
Maybe (Path Abs Dir) -> m (Maybe (Path Abs Dir))
rejectMissingDir Maybe (Path Abs Dir)
Nothing = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
rejectMissingDir (Just Path Abs Dir
p) = forall a. a -> a -> Bool -> a
bool forall a. Maybe a
Nothing (forall a. a -> Maybe a
Just Path Abs Dir
p) forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` forall (m :: * -> *) b. MonadIO m => Path b Dir -> m Bool
doesDirExist Path Abs Dir
p

-- | Convert to a lazy ByteString using toFilePath and UTF8.

pathToLazyByteString :: Path b t -> BSL.ByteString
pathToLazyByteString :: forall b t. Path b t -> ByteString
pathToLazyByteString = ByteString -> ByteString
BSL.fromStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b t. Path b t -> ByteString
pathToByteString

-- | Convert to a ByteString using toFilePath and UTF8.

pathToByteString :: Path b t -> BS.ByteString
pathToByteString :: forall b t. Path b t -> ByteString
pathToByteString = Text -> ByteString
T.encodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b t. Path b t -> Text
pathToText

pathToText :: Path b t -> T.Text
pathToText :: forall b t. Path b t -> Text
pathToText = FilePath -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b t. Path b t -> FilePath
toFilePath

tryGetModificationTime :: MonadIO m => Path Abs File -> m (Either () UTCTime)
tryGetModificationTime :: forall (m :: * -> *).
MonadIO m =>
Path Abs File -> m (Either () UTCTime)
tryGetModificationTime = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) e b a.
(MonadUnliftIO m, Exception e) =>
(e -> Maybe b) -> m a -> m (Either b a)
tryJust (forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall b c a. (b -> c) -> (a -> b) -> a -> c
. IOError -> Bool
isDoesNotExistError) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) b t. MonadIO m => Path b t -> m UTCTime
getModificationTime