{-# LANGUAGE CPP #-}
module Hackage.Security.Util.Path (
Path(..)
, castRoot
, takeDirectory
, takeFileName
, (<.>)
, splitExtension
, takeExtension
, Unrooted
, (</>)
, rootPath
, unrootPath
, toUnrootedFilePath
, fromUnrootedFilePath
, fragment
, joinFragments
, splitFragments
, isPathPrefixOf
, Relative
, Absolute
, HomeDir
, FsRoot(..)
, FsPath(..)
, toFilePath
, fromFilePath
, makeAbsolute
, fromAbsoluteFilePath
, withFile
, openTempFile'
, readLazyByteString
, readStrictByteString
, writeLazyByteString
, writeStrictByteString
, copyFile
, createDirectory
, createDirectoryIfMissing
, removeDirectory
, doesFileExist
, doesDirectoryExist
, getModificationTime
, removeFile
, getTemporaryDirectory
, getDirectoryContents
, getRecursiveContents
, renameFile
, getCurrentDirectory
, Tar
, tarIndexLookup
, tarAppend
, Web
, toURIPath
, fromURIPath
, uriPath
, modifyUriPath
, IOMode(..)
, BufferMode(..)
, Handle
, SeekMode(..)
, IO.hSetBuffering
, IO.hClose
, IO.hFileSize
, IO.hSeek
) where
import MyPrelude
import Control.Monad
import Data.List (isPrefixOf)
import System.IO (IOMode(..), BufferMode(..), Handle, SeekMode(..))
import System.IO.Unsafe (unsafeInterleaveIO)
#if MIN_VERSION_directory(1,2,0)
import Data.Time (UTCTime)
#else
import System.Time (ClockTime)
#endif
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BS.L
import qualified System.FilePath as FP.Native
import qualified System.FilePath.Posix as FP.Posix
import qualified System.IO as IO
import qualified System.Directory as Dir
import qualified Codec.Archive.Tar as Tar
import qualified Codec.Archive.Tar.Index as TarIndex
import qualified Network.URI as URI
import Hackage.Security.Util.Pretty
newtype Path a = Path FilePath
deriving (Int -> Path a -> ShowS
forall a. Int -> Path a -> ShowS
forall a. [Path a] -> ShowS
forall a. Path a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Path a] -> ShowS
$cshowList :: forall a. [Path a] -> ShowS
show :: Path a -> String
$cshow :: forall a. Path a -> String
showsPrec :: Int -> Path a -> ShowS
$cshowsPrec :: forall a. Int -> Path a -> ShowS
Show, Path a -> Path a -> Bool
forall a. Path a -> Path a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Path a -> Path a -> Bool
$c/= :: forall a. Path a -> Path a -> Bool
== :: Path a -> Path a -> Bool
$c== :: forall a. Path a -> Path a -> Bool
Eq, Path a -> Path a -> Bool
Path a -> Path a -> Ordering
Path a -> Path a -> Path a
forall a. Eq (Path a)
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Path a -> Path a -> Bool
forall a. Path a -> Path a -> Ordering
forall a. Path a -> Path a -> Path a
min :: Path a -> Path a -> Path a
$cmin :: forall a. Path a -> Path a -> Path a
max :: Path a -> Path a -> Path a
$cmax :: forall a. Path a -> Path a -> Path a
>= :: Path a -> Path a -> Bool
$c>= :: forall a. Path a -> Path a -> Bool
> :: Path a -> Path a -> Bool
$c> :: forall a. Path a -> Path a -> Bool
<= :: Path a -> Path a -> Bool
$c<= :: forall a. Path a -> Path a -> Bool
< :: Path a -> Path a -> Bool
$c< :: forall a. Path a -> Path a -> Bool
compare :: Path a -> Path a -> Ordering
$ccompare :: forall a. Path a -> Path a -> Ordering
Ord)
mkPathNative :: FilePath -> Path a
mkPathNative :: forall a. String -> Path a
mkPathNative = forall a. String -> Path a
Path forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
FP.Posix.joinPath forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
FP.Native.splitDirectories
unPathNative :: Path a -> FilePath
unPathNative :: forall a. Path a -> String
unPathNative (Path String
fp) = [String] -> String
FP.Native.joinPath forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
FP.Posix.splitDirectories forall a b. (a -> b) -> a -> b
$ String
fp
mkPathPosix :: FilePath -> Path a
mkPathPosix :: forall a. String -> Path a
mkPathPosix = forall a. String -> Path a
Path
unPathPosix :: Path a -> FilePath
unPathPosix :: forall a. Path a -> String
unPathPosix (Path String
fp) = String
fp
castRoot :: Path root -> Path root'
castRoot :: forall root root'. Path root -> Path root'
castRoot (Path String
fp) = forall a. String -> Path a
Path String
fp
takeDirectory :: Path a -> Path a
takeDirectory :: forall a. Path a -> Path a
takeDirectory = forall a b. ShowS -> Path a -> Path b
liftFP ShowS
FP.Posix.takeDirectory
takeFileName :: Path a -> String
takeFileName :: forall a. Path a -> String
takeFileName = forall x a. (String -> x) -> Path a -> x
liftFromFP ShowS
FP.Posix.takeFileName
(<.>) :: Path a -> String -> Path a
Path a
fp <.> :: forall a. Path a -> String -> Path a
<.> String
ext = forall a b. ShowS -> Path a -> Path b
liftFP (String -> ShowS
FP.Posix.<.> String
ext) Path a
fp
splitExtension :: Path a -> (Path a, String)
splitExtension :: forall a. Path a -> (Path a, String)
splitExtension (Path String
fp) = (forall a. String -> Path a
Path String
fp', String
ext)
where
(String
fp', String
ext) = String -> (String, String)
FP.Posix.splitExtension String
fp
takeExtension :: Path a -> String
takeExtension :: forall a. Path a -> String
takeExtension (Path String
fp) = ShowS
FP.Posix.takeExtension String
fp
data Unrooted
instance Pretty (Path Unrooted) where
pretty :: Path Unrooted -> String
pretty (Path String
fp) = String
fp
(</>) :: Path a -> Path Unrooted -> Path a
</> :: forall a. Path a -> Path Unrooted -> Path a
(</>) = forall a b c. (String -> ShowS) -> Path a -> Path b -> Path c
liftFP2 String -> ShowS
(FP.Posix.</>)
rootPath :: Path Unrooted -> Path root
rootPath :: forall root. Path Unrooted -> Path root
rootPath (Path String
fp) = forall a. String -> Path a
Path String
fp
unrootPath :: Path root -> Path Unrooted
unrootPath :: forall root. Path root -> Path Unrooted
unrootPath (Path String
fp) = forall a. String -> Path a
Path String
fp
toUnrootedFilePath :: Path Unrooted -> FilePath
toUnrootedFilePath :: Path Unrooted -> String
toUnrootedFilePath = forall a. Path a -> String
unPathPosix
fromUnrootedFilePath :: FilePath -> Path Unrooted
fromUnrootedFilePath :: String -> Path Unrooted
fromUnrootedFilePath = forall a. String -> Path a
mkPathPosix
fragment :: String -> Path Unrooted
fragment :: String -> Path Unrooted
fragment = forall a. String -> Path a
Path
joinFragments :: [String] -> Path Unrooted
joinFragments :: [String] -> Path Unrooted
joinFragments = forall x a. (x -> String) -> x -> Path a
liftToFP [String] -> String
FP.Posix.joinPath
splitFragments :: Path Unrooted -> [String]
splitFragments :: Path Unrooted -> [String]
splitFragments (Path String
fp) = String -> [String]
FP.Posix.splitDirectories String
fp
isPathPrefixOf :: Path Unrooted -> Path Unrooted -> Bool
isPathPrefixOf :: Path Unrooted -> Path Unrooted -> Bool
isPathPrefixOf = forall x a b. (String -> String -> x) -> Path a -> Path b -> x
liftFromFP2 forall a. Eq a => [a] -> [a] -> Bool
isPrefixOf
data Relative
data Absolute
data HomeDir
instance Pretty (Path Absolute) where
pretty :: Path Absolute -> String
pretty (Path String
fp) = String
fp
instance Pretty (Path Relative) where
pretty :: Path Relative -> String
pretty (Path String
fp) = String
"./" forall a. [a] -> [a] -> [a]
++ String
fp
instance Pretty (Path HomeDir) where
pretty :: Path HomeDir -> String
pretty (Path String
fp) = String
"~/" forall a. [a] -> [a] -> [a]
++ String
fp
class FsRoot root where
toAbsoluteFilePath :: Path root -> IO FilePath
instance FsRoot Relative where
toAbsoluteFilePath :: Path Relative -> IO String
toAbsoluteFilePath Path Relative
p = String -> IO String
go (forall a. Path a -> String
unPathNative Path Relative
p)
where
go :: FilePath -> IO FilePath
#if MIN_VERSION_directory(1,2,2)
go :: String -> IO String
go = String -> IO String
Dir.makeAbsolute
#else
go = (FP.Native.normalise <$>) . absolutize
absolutize path
| FP.Native.isRelative path
= (FP.Native.</> path)
. FP.Native.addTrailingPathSeparator <$>
Dir.getCurrentDirectory
| otherwise = return path
#endif
instance FsRoot Absolute where
toAbsoluteFilePath :: Path Absolute -> IO String
toAbsoluteFilePath = forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Path a -> String
unPathNative
instance FsRoot HomeDir where
toAbsoluteFilePath :: Path HomeDir -> IO String
toAbsoluteFilePath Path HomeDir
p = do
String
home <- IO String
Dir.getHomeDirectory
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ String
home String -> ShowS
FP.Native.</> forall a. Path a -> String
unPathNative Path HomeDir
p
data FsPath = forall root. FsRoot root => FsPath (Path root)
toFilePath :: Path Absolute -> FilePath
toFilePath :: Path Absolute -> String
toFilePath = forall a. Path a -> String
unPathNative
fromFilePath :: FilePath -> FsPath
fromFilePath :: String -> FsPath
fromFilePath String
fp
| String -> Bool
FP.Native.isAbsolute String
fp = forall root. FsRoot root => Path root -> FsPath
FsPath (forall a. String -> Path a
mkPathNative String
fp :: Path Absolute)
| Just String
fp' <- String -> Maybe String
atHome String
fp = forall root. FsRoot root => Path root -> FsPath
FsPath (forall a. String -> Path a
mkPathNative String
fp' :: Path HomeDir)
| Bool
otherwise = forall root. FsRoot root => Path root -> FsPath
FsPath (forall a. String -> Path a
mkPathNative String
fp :: Path Relative)
where
atHome :: FilePath -> Maybe FilePath
atHome :: String -> Maybe String
atHome String
"~" = forall a. a -> Maybe a
Just String
""
atHome (Char
'~':Char
sep:String
fp') | Char -> Bool
FP.Native.isPathSeparator Char
sep = forall a. a -> Maybe a
Just String
fp'
atHome String
_otherwise = forall a. Maybe a
Nothing
makeAbsolute :: FsPath -> IO (Path Absolute)
makeAbsolute :: FsPath -> IO (Path Absolute)
makeAbsolute (FsPath Path root
p) = forall a. String -> Path a
mkPathNative forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall root. FsRoot root => Path root -> IO String
toAbsoluteFilePath Path root
p
fromAbsoluteFilePath :: FilePath -> Path Absolute
fromAbsoluteFilePath :: String -> Path Absolute
fromAbsoluteFilePath String
fp
| String -> Bool
FP.Native.isAbsolute String
fp = forall a. String -> Path a
mkPathNative String
fp
| Bool
otherwise = forall a. HasCallStack => String -> a
error (String
"fromAbsoluteFilePath: not an absolute path: " forall a. [a] -> [a] -> [a]
++ String
fp)
withFile :: FsRoot root => Path root -> IOMode -> (Handle -> IO r) -> IO r
withFile :: forall root r.
FsRoot root =>
Path root -> IOMode -> (Handle -> IO r) -> IO r
withFile Path root
path IOMode
mode Handle -> IO r
callback = do
String
filePath <- forall root. FsRoot root => Path root -> IO String
toAbsoluteFilePath Path root
path
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
IO.withFile String
filePath IOMode
mode Handle -> IO r
callback
openTempFile' :: FsRoot root => Path root -> String -> IO (Path Absolute, Handle)
openTempFile' :: forall root.
FsRoot root =>
Path root -> String -> IO (Path Absolute, Handle)
openTempFile' Path root
path String
template = do
String
filePath <- forall root. FsRoot root => Path root -> IO String
toAbsoluteFilePath Path root
path
(String
tempFilePath, Handle
h) <- String -> String -> IO (String, Handle)
IO.openBinaryTempFileWithDefaultPermissions String
filePath String
template
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Path Absolute
fromAbsoluteFilePath String
tempFilePath, Handle
h)
readLazyByteString :: FsRoot root => Path root -> IO BS.L.ByteString
readLazyByteString :: forall root. FsRoot root => Path root -> IO ByteString
readLazyByteString Path root
path = do
String
filePath <- forall root. FsRoot root => Path root -> IO String
toAbsoluteFilePath Path root
path
String -> IO ByteString
BS.L.readFile String
filePath
readStrictByteString :: FsRoot root => Path root -> IO BS.ByteString
readStrictByteString :: forall root. FsRoot root => Path root -> IO ByteString
readStrictByteString Path root
path = do
String
filePath <- forall root. FsRoot root => Path root -> IO String
toAbsoluteFilePath Path root
path
String -> IO ByteString
BS.readFile String
filePath
writeLazyByteString :: FsRoot root => Path root -> BS.L.ByteString -> IO ()
writeLazyByteString :: forall root. FsRoot root => Path root -> ByteString -> IO ()
writeLazyByteString Path root
path ByteString
bs = do
String
filePath <- forall root. FsRoot root => Path root -> IO String
toAbsoluteFilePath Path root
path
String -> ByteString -> IO ()
BS.L.writeFile String
filePath ByteString
bs
writeStrictByteString :: FsRoot root => Path root -> BS.ByteString -> IO ()
writeStrictByteString :: forall root. FsRoot root => Path root -> ByteString -> IO ()
writeStrictByteString Path root
path ByteString
bs = do
String
filePath <- forall root. FsRoot root => Path root -> IO String
toAbsoluteFilePath Path root
path
String -> ByteString -> IO ()
BS.writeFile String
filePath ByteString
bs
copyFile :: (FsRoot root, FsRoot root') => Path root -> Path root' -> IO ()
copyFile :: forall root root'.
(FsRoot root, FsRoot root') =>
Path root -> Path root' -> IO ()
copyFile Path root
src Path root'
dst = do
String
src' <- forall root. FsRoot root => Path root -> IO String
toAbsoluteFilePath Path root
src
String
dst' <- forall root. FsRoot root => Path root -> IO String
toAbsoluteFilePath Path root'
dst
String -> String -> IO ()
Dir.copyFile String
src' String
dst'
createDirectory :: FsRoot root => Path root -> IO ()
createDirectory :: forall root. FsRoot root => Path root -> IO ()
createDirectory Path root
path = String -> IO ()
Dir.createDirectory forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall root. FsRoot root => Path root -> IO String
toAbsoluteFilePath Path root
path
createDirectoryIfMissing :: FsRoot root => Bool -> Path root -> IO ()
createDirectoryIfMissing :: forall root. FsRoot root => Bool -> Path root -> IO ()
createDirectoryIfMissing Bool
createParents Path root
path = do
String
filePath <- forall root. FsRoot root => Path root -> IO String
toAbsoluteFilePath Path root
path
Bool -> String -> IO ()
Dir.createDirectoryIfMissing Bool
createParents String
filePath
removeDirectory :: FsRoot root => Path root -> IO ()
removeDirectory :: forall root. FsRoot root => Path root -> IO ()
removeDirectory Path root
path = String -> IO ()
Dir.removeDirectory forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall root. FsRoot root => Path root -> IO String
toAbsoluteFilePath Path root
path
doesFileExist :: FsRoot root => Path root -> IO Bool
doesFileExist :: forall root. FsRoot root => Path root -> IO Bool
doesFileExist Path root
path = do
String
filePath <- forall root. FsRoot root => Path root -> IO String
toAbsoluteFilePath Path root
path
String -> IO Bool
Dir.doesFileExist String
filePath
doesDirectoryExist :: FsRoot root => Path root -> IO Bool
doesDirectoryExist :: forall root. FsRoot root => Path root -> IO Bool
doesDirectoryExist Path root
path = do
String
filePath <- forall root. FsRoot root => Path root -> IO String
toAbsoluteFilePath Path root
path
String -> IO Bool
Dir.doesDirectoryExist String
filePath
#if MIN_VERSION_directory(1,2,0)
getModificationTime :: FsRoot root => Path root -> IO UTCTime
#else
getModificationTime :: FsRoot root => Path root -> IO ClockTime
#endif
getModificationTime :: forall root. FsRoot root => Path root -> IO UTCTime
getModificationTime Path root
path = do
String
filePath <- forall root. FsRoot root => Path root -> IO String
toAbsoluteFilePath Path root
path
String -> IO UTCTime
Dir.getModificationTime String
filePath
removeFile :: FsRoot root => Path root -> IO ()
removeFile :: forall root. FsRoot root => Path root -> IO ()
removeFile Path root
path = do
String
filePath <- forall root. FsRoot root => Path root -> IO String
toAbsoluteFilePath Path root
path
String -> IO ()
Dir.removeFile String
filePath
getTemporaryDirectory :: IO (Path Absolute)
getTemporaryDirectory :: IO (Path Absolute)
getTemporaryDirectory = String -> Path Absolute
fromAbsoluteFilePath forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO String
Dir.getTemporaryDirectory
getDirectoryContents :: FsRoot root => Path root -> IO [Path Unrooted]
getDirectoryContents :: forall root. FsRoot root => Path root -> IO [Path Unrooted]
getDirectoryContents Path root
path = do
String
filePath <- forall root. FsRoot root => Path root -> IO String
toAbsoluteFilePath Path root
path
[String] -> [Path Unrooted]
fragments forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO [String]
Dir.getDirectoryContents String
filePath
where
fragments :: [String] -> [Path Unrooted]
fragments :: [String] -> [Path Unrooted]
fragments = forall a b. (a -> b) -> [a] -> [b]
map String -> Path Unrooted
fragment forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Bool
skip)
skip :: String -> Bool
skip :: String -> Bool
skip String
"." = Bool
True
skip String
".." = Bool
True
skip String
_ = Bool
False
getRecursiveContents :: FsRoot root => Path root -> IO [Path Unrooted]
getRecursiveContents :: forall root. FsRoot root => Path root -> IO [Path Unrooted]
getRecursiveContents Path root
root = Path Unrooted -> IO [Path Unrooted]
go Path Unrooted
emptyPath
where
go :: Path Unrooted -> IO [Path Unrooted]
go :: Path Unrooted -> IO [Path Unrooted]
go Path Unrooted
subdir = forall a. IO a -> IO a
unsafeInterleaveIO forall a b. (a -> b) -> a -> b
$ do
[Path Unrooted]
entries <- forall root. FsRoot root => Path root -> IO [Path Unrooted]
getDirectoryContents (Path root
root forall a. Path a -> Path Unrooted -> Path a
</> Path Unrooted
subdir)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [Path Unrooted]
entries forall a b. (a -> b) -> a -> b
$ \Path Unrooted
entry -> do
let path :: Path Unrooted
path = Path Unrooted
subdir forall a. Path a -> Path Unrooted -> Path a
</> Path Unrooted
entry
Bool
isDirectory <- forall root. FsRoot root => Path root -> IO Bool
doesDirectoryExist (Path root
root forall a. Path a -> Path Unrooted -> Path a
</> Path Unrooted
path)
if Bool
isDirectory then Path Unrooted -> IO [Path Unrooted]
go Path Unrooted
path
else forall (m :: * -> *) a. Monad m => a -> m a
return [Path Unrooted
path]
emptyPath :: Path Unrooted
emptyPath :: Path Unrooted
emptyPath = [String] -> Path Unrooted
joinFragments []
renameFile :: (FsRoot root, FsRoot root')
=> Path root
-> Path root'
-> IO ()
renameFile :: forall root root'.
(FsRoot root, FsRoot root') =>
Path root -> Path root' -> IO ()
renameFile Path root
old Path root'
new = do
String
old' <- forall root. FsRoot root => Path root -> IO String
toAbsoluteFilePath Path root
old
String
new' <- forall root. FsRoot root => Path root -> IO String
toAbsoluteFilePath Path root'
new
String -> String -> IO ()
Dir.renameFile String
old' String
new'
getCurrentDirectory :: IO (Path Absolute)
getCurrentDirectory :: IO (Path Absolute)
getCurrentDirectory = do
String
cwd <- IO String
Dir.getCurrentDirectory
FsPath -> IO (Path Absolute)
makeAbsolute forall a b. (a -> b) -> a -> b
$ String -> FsPath
fromFilePath String
cwd
data Tar
instance Pretty (Path Tar) where
pretty :: Path Tar -> String
pretty (Path String
fp) = String
"<tarball>/" forall a. [a] -> [a] -> [a]
++ String
fp
tarIndexLookup :: TarIndex.TarIndex -> Path Tar -> Maybe TarIndex.TarIndexEntry
tarIndexLookup :: TarIndex -> Path Tar -> Maybe TarIndexEntry
tarIndexLookup TarIndex
index Path Tar
path = TarIndex -> String -> Maybe TarIndexEntry
TarIndex.lookup TarIndex
index String
path'
where
path' :: FilePath
path' :: String
path' = Path Unrooted -> String
toUnrootedFilePath forall a b. (a -> b) -> a -> b
$ forall root. Path root -> Path Unrooted
unrootPath Path Tar
path
tarAppend :: (FsRoot root, FsRoot root')
=> Path root
-> Path root'
-> [Path Tar]
-> IO ()
tarAppend :: forall root root'.
(FsRoot root, FsRoot root') =>
Path root -> Path root' -> [Path Tar] -> IO ()
tarAppend Path root
tarFile Path root'
baseDir [Path Tar]
contents = do
String
tarFile' <- forall root. FsRoot root => Path root -> IO String
toAbsoluteFilePath Path root
tarFile
String
baseDir' <- forall root. FsRoot root => Path root -> IO String
toAbsoluteFilePath Path root'
baseDir
String -> String -> [String] -> IO ()
Tar.append String
tarFile' String
baseDir' [String]
contents'
where
contents' :: [FilePath]
contents' :: [String]
contents' = forall a b. (a -> b) -> [a] -> [b]
map (forall a. Path a -> String
unPathNative forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall root. Path root -> Path Unrooted
unrootPath) [Path Tar]
contents
data Web
toURIPath :: FilePath -> Path Web
toURIPath :: String -> Path Web
toURIPath = forall root. Path Unrooted -> Path root
rootPath forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Path Unrooted
fromUnrootedFilePath
fromURIPath :: Path Web -> FilePath
fromURIPath :: Path Web -> String
fromURIPath = Path Unrooted -> String
toUnrootedFilePath forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall root. Path root -> Path Unrooted
unrootPath
uriPath :: URI.URI -> Path Web
uriPath :: URI -> Path Web
uriPath = String -> Path Web
toURIPath forall b c a. (b -> c) -> (a -> b) -> a -> c
. URI -> String
URI.uriPath
modifyUriPath :: URI.URI -> (Path Web -> Path Web) -> URI.URI
modifyUriPath :: URI -> (Path Web -> Path Web) -> URI
modifyUriPath URI
uri Path Web -> Path Web
f = URI
uri { uriPath :: String
URI.uriPath = ShowS
f' (URI -> String
URI.uriPath URI
uri) }
where
f' :: FilePath -> FilePath
f' :: ShowS
f' = Path Web -> String
fromURIPath forall b c a. (b -> c) -> (a -> b) -> a -> c
. Path Web -> Path Web
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Path Web
toURIPath
liftFP :: (FilePath -> FilePath) -> Path a -> Path b
liftFP :: forall a b. ShowS -> Path a -> Path b
liftFP ShowS
f (Path String
fp) = forall a. String -> Path a
Path (ShowS
f String
fp)
liftFP2 :: (FilePath -> FilePath -> FilePath) -> Path a -> Path b -> Path c
liftFP2 :: forall a b c. (String -> ShowS) -> Path a -> Path b -> Path c
liftFP2 String -> ShowS
f (Path String
fp) (Path String
fp') = forall a. String -> Path a
Path (String -> ShowS
f String
fp String
fp')
liftFromFP :: (FilePath -> x) -> Path a -> x
liftFromFP :: forall x a. (String -> x) -> Path a -> x
liftFromFP String -> x
f (Path String
fp) = String -> x
f String
fp
liftFromFP2 :: (FilePath -> FilePath -> x) -> Path a -> Path b -> x
liftFromFP2 :: forall x a b. (String -> String -> x) -> Path a -> Path b -> x
liftFromFP2 String -> String -> x
f (Path String
fp) (Path String
fp') = String -> String -> x
f String
fp String
fp'
liftToFP :: (x -> FilePath) -> x -> Path a
liftToFP :: forall x a. (x -> String) -> x -> Path a
liftToFP x -> String
f x
x = forall a. String -> Path a
Path (x -> String
f x
x)