Skip to content

Commit e84ccea

Browse files
committed
Pack: migrate internally to OsPath
1 parent 9f832d6 commit e84ccea

File tree

4 files changed

+64
-29
lines changed

4 files changed

+64
-29
lines changed

Codec/Archive/Tar/Pack.hs

Lines changed: 52 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,11 @@
1-
{-# LANGUAGE MultiWayIf #-}
2-
{-# LANGUAGE TypeApplications #-}
3-
{-# LANGUAGE LambdaCase #-}
41
{-# LANGUAGE RankNTypes #-}
52
{-# LANGUAGE ScopedTypeVariables #-}
3+
{-# LANGUAGE ViewPatterns #-}
4+
65
{-# OPTIONS_HADDOCK hide #-}
6+
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
7+
{-# HLINT ignore "Avoid restricted function" #-}
8+
79
-----------------------------------------------------------------------------
810
-- |
911
-- Module : Codec.Archive.Tar
@@ -28,16 +30,20 @@ module Codec.Archive.Tar.Pack (
2830
) where
2931

3032
import Codec.Archive.Tar.LongNames
33+
import Codec.Archive.Tar.PackAscii (filePathToOsPath, osPathToFilePath)
3134
import Codec.Archive.Tar.Types
35+
3236
import Control.Monad (join, when, forM, (>=>))
37+
import Data.Bifunctor (bimap)
3338
import qualified Data.ByteString as B
3439
import qualified Data.ByteString.Lazy as BL
3540
import Data.Foldable
36-
import System.FilePath
37-
( (</>) )
38-
import qualified System.FilePath as FilePath.Native
41+
import System.File.OsPath
42+
import System.OsPath
43+
( OsPath, (</>) )
44+
import qualified System.OsPath as FilePath.Native
3945
( addTrailingPathSeparator, hasTrailingPathSeparator, splitDirectories )
40-
import System.Directory
46+
import System.Directory.OsPath
4147
( listDirectory, doesDirectoryExist, getModificationTime
4248
, pathIsSymbolicLink, getSymbolicLinkTarget
4349
, Permissions(..), getPermissions, getFileSize )
@@ -46,7 +52,7 @@ import Data.Time.Clock
4652
import Data.Time.Clock.POSIX
4753
( utcTimeToPOSIXSeconds )
4854
import System.IO
49-
( IOMode(ReadMode), openBinaryFile, hFileSize )
55+
( IOMode(ReadMode), hFileSize )
5056
import System.IO.Unsafe (unsafeInterleaveIO)
5157
import Control.Exception (throwIO, SomeException)
5258
import Codec.Archive.Tar.Check.Internal (checkEntrySecurity)
@@ -81,40 +87,42 @@ packAndCheck
8187
-> FilePath -- ^ Base directory
8288
-> [FilePath] -- ^ Files and directories to pack, relative to the base dir
8389
-> IO [Entry]
84-
packAndCheck secCB baseDir relpaths = do
90+
packAndCheck secCB (filePathToOsPath -> baseDir) (map filePathToOsPath -> relpaths) = do
8591
paths <- preparePaths baseDir relpaths
86-
entries <- packPaths baseDir paths
92+
entries' <- packPaths baseDir paths
93+
let entries = map (bimap osPathToFilePath osPathToFilePath) entries'
8794
traverse_ (maybe (pure ()) throwIO . secCB) entries
8895
pure $ concatMap encodeLongNames entries
8996

90-
preparePaths :: FilePath -> [FilePath] -> IO [FilePath]
97+
preparePaths :: OsPath -> [OsPath] -> IO [OsPath]
9198
preparePaths baseDir = fmap concat . interleave . map go
9299
where
100+
go :: OsPath -> IO [OsPath]
93101
go relpath = do
94102
let abspath = baseDir </> relpath
95103
isDir <- doesDirectoryExist abspath
96104
isSymlink <- pathIsSymbolicLink abspath
97105
if isDir && not isSymlink then do
98106
entries <- getDirectoryContentsRecursive abspath
99107
let entries' = map (relpath </>) entries
100-
return $ if null relpath
108+
return $ if relpath == mempty
101109
then entries'
102110
else FilePath.Native.addTrailingPathSeparator relpath : entries'
103111
else return [relpath]
104112

105113
-- | Pack paths while accounting for overlong filepaths.
106114
packPaths
107-
:: FilePath
108-
-> [FilePath]
109-
-> IO [GenEntry FilePath FilePath]
115+
:: OsPath
116+
-> [OsPath]
117+
-> IO [GenEntry OsPath OsPath]
110118
packPaths baseDir paths = interleave $ flip map paths $ \relpath -> do
111119
let isDir = FilePath.Native.hasTrailingPathSeparator abspath
112120
abspath = baseDir </> relpath
113121
isSymlink <- pathIsSymbolicLink abspath
114122
let mkEntry
115-
| isSymlink = packSymlinkEntry
116-
| isDir = packDirectoryEntry
117-
| otherwise = packFileEntry
123+
| isSymlink = packSymlinkEntry'
124+
| isDir = packDirectoryEntry'
125+
| otherwise = packFileEntry'
118126
mkEntry abspath relpath
119127

120128
interleave :: [IO a] -> IO [a]
@@ -138,7 +146,13 @@ packFileEntry
138146
:: FilePath -- ^ Full path to find the file on the local disk
139147
-> tarPath -- ^ Path to use for the tar 'GenEntry' in the archive
140148
-> IO (GenEntry tarPath linkTarget)
141-
packFileEntry filepath tarpath = do
149+
packFileEntry = packFileEntry' . filePathToOsPath
150+
151+
packFileEntry'
152+
:: OsPath -- ^ Full path to find the file on the local disk
153+
-> tarPath -- ^ Path to use for the tar 'GenEntry' in the archive
154+
-> IO (GenEntry tarPath linkTarget)
155+
packFileEntry' filepath tarpath = do
142156
mtime <- getModTime filepath
143157
perms <- getPermissions filepath
144158
-- Get file size without opening it.
@@ -148,7 +162,7 @@ packFileEntry filepath tarpath = do
148162
-- If file is short enough, just read it strictly
149163
-- so that no file handle dangles around indefinitely.
150164
then do
151-
cnt <- B.readFile filepath
165+
cnt <- readFile' filepath
152166
pure (BL.fromStrict cnt, fromIntegral $ B.length cnt)
153167
else do
154168
hndl <- openBinaryFile filepath ReadMode
@@ -178,7 +192,13 @@ packDirectoryEntry
178192
:: FilePath -- ^ Full path to find the file on the local disk
179193
-> tarPath -- ^ Path to use for the tar 'GenEntry' in the archive
180194
-> IO (GenEntry tarPath linkTarget)
181-
packDirectoryEntry filepath tarpath = do
195+
packDirectoryEntry = packDirectoryEntry' . filePathToOsPath
196+
197+
packDirectoryEntry'
198+
:: OsPath -- ^ Full path to find the file on the local disk
199+
-> tarPath -- ^ Path to use for the tar 'GenEntry' in the archive
200+
-> IO (GenEntry tarPath linkTarget)
201+
packDirectoryEntry' filepath tarpath = do
182202
mtime <- getModTime filepath
183203
return (directoryEntry tarpath) {
184204
entryTime = mtime
@@ -193,7 +213,13 @@ packSymlinkEntry
193213
:: FilePath -- ^ Full path to find the file on the local disk
194214
-> tarPath -- ^ Path to use for the tar 'GenEntry' in the archive
195215
-> IO (GenEntry tarPath FilePath)
196-
packSymlinkEntry filepath tarpath = do
216+
packSymlinkEntry = ((fmap (fmap osPathToFilePath) .) . packSymlinkEntry') . filePathToOsPath
217+
218+
packSymlinkEntry'
219+
:: OsPath -- ^ Full path to find the file on the local disk
220+
-> tarPath -- ^ Path to use for the tar 'GenEntry' in the archive
221+
-> IO (GenEntry tarPath OsPath)
222+
packSymlinkEntry' filepath tarpath = do
197223
linkTarget <- getSymbolicLinkTarget filepath
198224
pure $ symlinkEntry tarpath linkTarget
199225

@@ -215,11 +241,11 @@ packSymlinkEntry filepath tarpath = do
215241
-- If the source directory structure changes before the result is used in full,
216242
-- the behaviour is undefined.
217243
--
218-
getDirectoryContentsRecursive :: FilePath -> IO [FilePath]
244+
getDirectoryContentsRecursive :: OsPath -> IO [OsPath]
219245
getDirectoryContentsRecursive dir0 =
220-
fmap (drop 1) (recurseDirectories dir0 [""])
246+
fmap (drop 1) (recurseDirectories dir0 [mempty])
221247

222-
recurseDirectories :: FilePath -> [FilePath] -> IO [FilePath]
248+
recurseDirectories :: OsPath -> [OsPath] -> IO [OsPath]
223249
recurseDirectories _ [] = return []
224250
recurseDirectories base (dir:dirs) = unsafeInterleaveIO $ do
225251
(files, dirs') <- collect [] [] =<< listDirectory (base </> dir)
@@ -238,7 +264,7 @@ recurseDirectories base (dir:dirs) = unsafeInterleaveIO $ do
238264
then collect files (dirEntry':dirs') entries
239265
else collect (dirEntry:files) dirs' entries
240266

241-
getModTime :: FilePath -> IO EpochTime
267+
getModTime :: OsPath -> IO EpochTime
242268
getModTime path = do
243269
-- The directory package switched to the new time package
244270
t <- getModificationTime path

Codec/Archive/Tar/PackAscii.hs

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,8 @@
11
{-# LANGUAGE PackageImports #-}
2+
23
{-# OPTIONS_HADDOCK hide #-}
4+
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
5+
{-# HLINT ignore "Avoid restricted function" #-}
36

47
module Codec.Archive.Tar.PackAscii
58
( toPosixString
@@ -8,6 +11,7 @@ module Codec.Archive.Tar.PackAscii
811
, byteToPosixString
912
, packAscii
1013
, filePathToOsPath
14+
, osPathToFilePath
1115
) where
1216

1317
import Data.ByteString (ByteString)
@@ -40,3 +44,6 @@ packAscii xs
4044

4145
filePathToOsPath :: FilePath -> OS.OsPath
4246
filePathToOsPath = unsafePerformIO . OS.encodeFS
47+
48+
osPathToFilePath :: OS.OsPath -> FilePath
49+
osPathToFilePath = unsafePerformIO . OS.decodeFS

Codec/Archive/Tar/Unpack.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,9 +3,10 @@
33
{-# LANGUAGE ScopedTypeVariables #-}
44
{-# LANGUAGE RankNTypes #-}
55

6-
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
76
{-# OPTIONS_HADDOCK hide #-}
7+
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
88
{-# HLINT ignore "Use for_" #-}
9+
{-# HLINT ignore "Avoid restricted function" #-}
910

1011
-----------------------------------------------------------------------------
1112
-- |

test/Codec/Archive/Tar/Pack/Tests.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -21,6 +21,7 @@ import Data.Char
2121
import Data.FileEmbed
2222
import qualified Codec.Archive.Tar as Tar
2323
import qualified Codec.Archive.Tar.Pack as Pack
24+
import Codec.Archive.Tar.PackAscii (filePathToOsPath)
2425
import qualified Codec.Archive.Tar.Read as Read
2526
import Codec.Archive.Tar.Types (GenEntries(..), Entries, simpleEntry, toTarPath, GenEntry (entryTarPath))
2627
import qualified Codec.Archive.Tar.Unpack as Unpack
@@ -109,8 +110,8 @@ prop_roundtrip n' xss cnt
109110
pure $ cnt === cnt'
110111
else do
111112
-- Forcing the result, otherwise lazy IO misbehaves.
112-
recFiles <- Pack.getDirectoryContentsRecursive baseDir >>= evaluate . force
113-
pure $ counterexample ("File " ++ absFile ++ " does not exist; instead found\n" ++ unlines recFiles) False
113+
recFiles <- Pack.getDirectoryContentsRecursive (filePathToOsPath baseDir) >>= evaluate . force
114+
pure $ counterexample ("File " ++ absFile ++ " does not exist; instead found\n" ++ unlines (map show recFiles)) False
114115

115116
| otherwise = discard
116117

0 commit comments

Comments
 (0)