1
- {-# LANGUAGE MultiWayIf #-}
2
- {-# LANGUAGE TypeApplications #-}
3
- {-# LANGUAGE LambdaCase #-}
4
1
{-# LANGUAGE RankNTypes #-}
5
2
{-# LANGUAGE ScopedTypeVariables #-}
3
+ {-# LANGUAGE ViewPatterns #-}
4
+
6
5
{-# OPTIONS_HADDOCK hide #-}
6
+ {-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
7
+ {-# HLINT ignore "Avoid restricted function" #-}
8
+
7
9
-----------------------------------------------------------------------------
8
10
-- |
9
11
-- Module : Codec.Archive.Tar
@@ -28,16 +30,20 @@ module Codec.Archive.Tar.Pack (
28
30
) where
29
31
30
32
import Codec.Archive.Tar.LongNames
33
+ import Codec.Archive.Tar.PackAscii (filePathToOsPath , osPathToFilePath )
31
34
import Codec.Archive.Tar.Types
35
+
32
36
import Control.Monad (join , when , forM , (>=>) )
37
+ import Data.Bifunctor (bimap )
33
38
import qualified Data.ByteString as B
34
39
import qualified Data.ByteString.Lazy as BL
35
40
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
39
45
( addTrailingPathSeparator , hasTrailingPathSeparator , splitDirectories )
40
- import System.Directory
46
+ import System.Directory.OsPath
41
47
( listDirectory , doesDirectoryExist , getModificationTime
42
48
, pathIsSymbolicLink , getSymbolicLinkTarget
43
49
, Permissions (.. ), getPermissions , getFileSize )
@@ -46,7 +52,7 @@ import Data.Time.Clock
46
52
import Data.Time.Clock.POSIX
47
53
( utcTimeToPOSIXSeconds )
48
54
import System.IO
49
- ( IOMode (ReadMode ), openBinaryFile , hFileSize )
55
+ ( IOMode (ReadMode ), hFileSize )
50
56
import System.IO.Unsafe (unsafeInterleaveIO )
51
57
import Control.Exception (throwIO , SomeException )
52
58
import Codec.Archive.Tar.Check.Internal (checkEntrySecurity )
@@ -81,40 +87,42 @@ packAndCheck
81
87
-> FilePath -- ^ Base directory
82
88
-> [FilePath ] -- ^ Files and directories to pack, relative to the base dir
83
89
-> IO [Entry ]
84
- packAndCheck secCB baseDir relpaths = do
90
+ packAndCheck secCB (filePathToOsPath -> baseDir) ( map filePathToOsPath -> relpaths) = do
85
91
paths <- preparePaths baseDir relpaths
86
- entries <- packPaths baseDir paths
92
+ entries' <- packPaths baseDir paths
93
+ let entries = map (bimap osPathToFilePath osPathToFilePath) entries'
87
94
traverse_ (maybe (pure () ) throwIO . secCB) entries
88
95
pure $ concatMap encodeLongNames entries
89
96
90
- preparePaths :: FilePath -> [FilePath ] -> IO [FilePath ]
97
+ preparePaths :: OsPath -> [OsPath ] -> IO [OsPath ]
91
98
preparePaths baseDir = fmap concat . interleave . map go
92
99
where
100
+ go :: OsPath -> IO [OsPath ]
93
101
go relpath = do
94
102
let abspath = baseDir </> relpath
95
103
isDir <- doesDirectoryExist abspath
96
104
isSymlink <- pathIsSymbolicLink abspath
97
105
if isDir && not isSymlink then do
98
106
entries <- getDirectoryContentsRecursive abspath
99
107
let entries' = map (relpath </> ) entries
100
- return $ if null relpath
108
+ return $ if relpath == mempty
101
109
then entries'
102
110
else FilePath.Native. addTrailingPathSeparator relpath : entries'
103
111
else return [relpath]
104
112
105
113
-- | Pack paths while accounting for overlong filepaths.
106
114
packPaths
107
- :: FilePath
108
- -> [FilePath ]
109
- -> IO [GenEntry FilePath FilePath ]
115
+ :: OsPath
116
+ -> [OsPath ]
117
+ -> IO [GenEntry OsPath OsPath ]
110
118
packPaths baseDir paths = interleave $ flip map paths $ \ relpath -> do
111
119
let isDir = FilePath.Native. hasTrailingPathSeparator abspath
112
120
abspath = baseDir </> relpath
113
121
isSymlink <- pathIsSymbolicLink abspath
114
122
let mkEntry
115
- | isSymlink = packSymlinkEntry
116
- | isDir = packDirectoryEntry
117
- | otherwise = packFileEntry
123
+ | isSymlink = packSymlinkEntry'
124
+ | isDir = packDirectoryEntry'
125
+ | otherwise = packFileEntry'
118
126
mkEntry abspath relpath
119
127
120
128
interleave :: [IO a ] -> IO [a ]
@@ -138,7 +146,13 @@ packFileEntry
138
146
:: FilePath -- ^ Full path to find the file on the local disk
139
147
-> tarPath -- ^ Path to use for the tar 'GenEntry' in the archive
140
148
-> 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
142
156
mtime <- getModTime filepath
143
157
perms <- getPermissions filepath
144
158
-- Get file size without opening it.
@@ -148,7 +162,7 @@ packFileEntry filepath tarpath = do
148
162
-- If file is short enough, just read it strictly
149
163
-- so that no file handle dangles around indefinitely.
150
164
then do
151
- cnt <- B. readFile filepath
165
+ cnt <- readFile' filepath
152
166
pure (BL. fromStrict cnt, fromIntegral $ B. length cnt)
153
167
else do
154
168
hndl <- openBinaryFile filepath ReadMode
@@ -178,7 +192,13 @@ packDirectoryEntry
178
192
:: FilePath -- ^ Full path to find the file on the local disk
179
193
-> tarPath -- ^ Path to use for the tar 'GenEntry' in the archive
180
194
-> 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
182
202
mtime <- getModTime filepath
183
203
return (directoryEntry tarpath) {
184
204
entryTime = mtime
@@ -193,7 +213,13 @@ packSymlinkEntry
193
213
:: FilePath -- ^ Full path to find the file on the local disk
194
214
-> tarPath -- ^ Path to use for the tar 'GenEntry' in the archive
195
215
-> 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
197
223
linkTarget <- getSymbolicLinkTarget filepath
198
224
pure $ symlinkEntry tarpath linkTarget
199
225
@@ -215,11 +241,11 @@ packSymlinkEntry filepath tarpath = do
215
241
-- If the source directory structure changes before the result is used in full,
216
242
-- the behaviour is undefined.
217
243
--
218
- getDirectoryContentsRecursive :: FilePath -> IO [FilePath ]
244
+ getDirectoryContentsRecursive :: OsPath -> IO [OsPath ]
219
245
getDirectoryContentsRecursive dir0 =
220
- fmap (drop 1 ) (recurseDirectories dir0 [" " ])
246
+ fmap (drop 1 ) (recurseDirectories dir0 [mempty ])
221
247
222
- recurseDirectories :: FilePath -> [FilePath ] -> IO [FilePath ]
248
+ recurseDirectories :: OsPath -> [OsPath ] -> IO [OsPath ]
223
249
recurseDirectories _ [] = return []
224
250
recurseDirectories base (dir: dirs) = unsafeInterleaveIO $ do
225
251
(files, dirs') <- collect [] [] =<< listDirectory (base </> dir)
@@ -238,7 +264,7 @@ recurseDirectories base (dir:dirs) = unsafeInterleaveIO $ do
238
264
then collect files (dirEntry': dirs') entries
239
265
else collect (dirEntry: files) dirs' entries
240
266
241
- getModTime :: FilePath -> IO EpochTime
267
+ getModTime :: OsPath -> IO EpochTime
242
268
getModTime path = do
243
269
-- The directory package switched to the new time package
244
270
t <- getModificationTime path
0 commit comments