Skip to content

Commit 62794b9

Browse files
committed
Implement Unicode support by utilizing PosixString and friends
Fixes #78
1 parent 6dd1a8d commit 62794b9

File tree

20 files changed

+672
-474
lines changed

20 files changed

+672
-474
lines changed

Codec/Archive/Tar.hs

Lines changed: 15 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -165,9 +165,12 @@ import Codec.Archive.Tar.Check
165165

166166
import Control.Exception (Exception, throw, catch)
167167
import qualified Data.ByteString.Lazy as BS
168-
import System.IO (withFile, IOMode(..))
168+
import System.IO (IOMode(..))
169169
import Prelude hiding (read)
170170

171+
import System.OsPath (OsPath)
172+
import qualified System.File.OsPath as OSP
173+
171174
-- | Create a new @\".tar\"@ file from a directory of files.
172175
--
173176
-- It is equivalent to calling the standard @tar@ program like so:
@@ -199,11 +202,11 @@ import Prelude hiding (read)
199202
--
200203
-- * @rwxr-xr-x@ for directories
201204
--
202-
create :: FilePath -- ^ Path of the \".tar\" file to write.
203-
-> FilePath -- ^ Base directory
204-
-> [FilePath] -- ^ Files and directories to archive, relative to base dir
205+
create :: OsPath -- ^ Path of the \".tar\" file to write.
206+
-> OsPath -- ^ Base directory
207+
-> [OsPath] -- ^ Files and directories to archive, relative to base dir
205208
-> IO ()
206-
create tar base paths = BS.writeFile tar . write =<< pack base paths
209+
create tar base paths = OSP.writeFile tar . write =<< pack base paths
207210

208211
-- | Extract all the files contained in a @\".tar\"@ file.
209212
--
@@ -233,22 +236,22 @@ create tar base paths = BS.writeFile tar . write =<< pack base paths
233236
-- containing entries that point outside of the tarball (either absolute paths
234237
-- or relative paths) will be caught and an exception will be thrown.
235238
--
236-
extract :: FilePath -- ^ Destination directory
237-
-> FilePath -- ^ Tarball
239+
extract :: OsPath -- ^ Destination directory
240+
-> OsPath -- ^ Tarball
238241
-> IO ()
239-
extract dir tar = unpack dir . read =<< BS.readFile tar
242+
extract dir tar = unpack dir . read =<< OSP.readFile tar
240243

241244
-- | Append new entries to a @\".tar\"@ file from a directory of files.
242245
--
243246
-- This is much like 'create', except that all the entries are added to the
244247
-- end of an existing tar file. Or if the file does not already exists then
245248
-- it behaves the same as 'create'.
246249
--
247-
append :: FilePath -- ^ Path of the \".tar\" file to write.
248-
-> FilePath -- ^ Base directory
249-
-> [FilePath] -- ^ Files and directories to archive, relative to base dir
250+
append :: OsPath -- ^ Path of the \".tar\" file to write.
251+
-> OsPath -- ^ Base directory
252+
-> [OsPath] -- ^ Files and directories to archive, relative to base dir
250253
-> IO ()
251254
append tar base paths =
252-
withFile tar ReadWriteMode $ \hnd -> do
255+
OSP.withFile tar ReadWriteMode $ \hnd -> do
253256
_ <- hSeekEndEntryOffset hnd Nothing
254257
BS.hPut hnd . write =<< pack base paths

Codec/Archive/Tar/Check/Internal.hs

Lines changed: 97 additions & 56 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,8 @@
44
{-# LANGUAGE TypeApplications #-}
55
{-# LANGUAGE RankNTypes #-}
66
{-# LANGUAGE ScopedTypeVariables #-}
7+
{-# LANGUAGE QuasiQuotes #-}
8+
{-# LANGUAGE MultiWayIf #-}
79
{-# OPTIONS_GHC -Wno-orphans #-}
810
-----------------------------------------------------------------------------
911
-- |
@@ -50,6 +52,17 @@ import qualified System.FilePath as FilePath.Native
5052
import qualified System.FilePath.Windows as FilePath.Windows
5153
import qualified System.FilePath.Posix as FilePath.Posix
5254

55+
import System.OsPath (OsPath)
56+
import System.OsPath.Posix (PosixPath)
57+
import qualified System.OsPath as OSP
58+
import qualified System.OsPath.Posix as PFP
59+
import qualified System.OsPath.Windows as WFP
60+
61+
import System.OsString.Posix (pstr)
62+
import System.OsString (osstr)
63+
import qualified System.OsString.Posix as PS
64+
import qualified System.OsString.Windows as WS
65+
5366

5467
--------------------------
5568
-- Security
@@ -72,57 +85,79 @@ import qualified System.FilePath.Posix as FilePath.Posix
7285
--
7386
checkSecurity
7487
:: Entries e
75-
-> GenEntries FilePath FilePath (Either (Either e DecodeLongNamesError) FileNameError)
88+
-> GenEntries PosixPath PosixPath (Either (Either e DecodeLongNamesError) FileNameError)
7689
checkSecurity = checkEntries checkEntrySecurity . decodeLongNames
7790

7891
-- | Worker of 'checkSecurity'.
7992
--
8093
-- @since 0.6.0.0
81-
checkEntrySecurity :: GenEntry FilePath FilePath -> Maybe FileNameError
94+
checkEntrySecurity :: GenEntry PosixPath PosixPath -> Maybe FileNameError
8295
checkEntrySecurity e =
8396
check (entryTarPath e) <|>
8497
case entryContent e of
8598
HardLink link ->
8699
check link
87100
SymbolicLink link ->
88-
check (FilePath.Posix.takeDirectory (entryTarPath e) FilePath.Posix.</> link)
101+
check (PFP.takeDirectory (entryTarPath e) PFP.</> link)
89102
_ -> Nothing
90103
where
104+
checkPosix :: PosixPath -> Maybe FileNameError
91105
checkPosix name
92-
| FilePath.Posix.isAbsolute name
93-
= Just $ AbsoluteFileName name
94-
| not (FilePath.Posix.isValid name)
95-
= Just $ InvalidFileName name
96-
| not (isInsideBaseDir (FilePath.Posix.splitDirectories name))
97-
= Just $ UnsafeLinkTarget name
98-
| otherwise = Nothing
99-
100-
checkNative (fromFilePathToNative -> name)
101-
| FilePath.Native.isAbsolute name || FilePath.Native.hasDrive name
106+
| PFP.isAbsolute name
102107
= Just $ AbsoluteFileName name
103-
| not (FilePath.Native.isValid name)
108+
| not (PFP.isValid name)
104109
= Just $ InvalidFileName name
105-
| not (isInsideBaseDir (FilePath.Native.splitDirectories name))
110+
| not (isInsideBaseDir (PFP.splitDirectories name))
106111
= Just $ UnsafeLinkTarget name
107112
| otherwise = Nothing
108113

109-
check name = checkPosix name <|> checkNative (fromFilePathToNative name)
110-
111-
isInsideBaseDir :: [FilePath] -> Bool
114+
checkNative :: PosixPath -> Maybe FileNameError
115+
checkNative name'
116+
| (Just name) <- fromPosixPath name' =
117+
if | OSP.isAbsolute name || OSP.hasDrive name
118+
-> Just $ AbsoluteFileName name'
119+
| not (OSP.isValid name)
120+
-> Just $ InvalidFileName name'
121+
| not (isInsideBaseDir' (OSP.splitDirectories name))
122+
-> Just $ UnsafeLinkTarget name'
123+
| otherwise
124+
-> Nothing
125+
| otherwise = Just $ FileNameDecodingFailure name'
126+
127+
check name = checkPosix name <|> checkNative name
128+
129+
isInsideBaseDir :: [PosixPath] -> Bool
112130
isInsideBaseDir = go 0
113131
where
114-
go :: Word -> [FilePath] -> Bool
132+
go :: Word -> [PosixPath] -> Bool
133+
go !_ [] = True
134+
go 0 (x : _)
135+
| x == [pstr|..|] = False
136+
go lvl (x : xs)
137+
| x == [pstr|..|] = go (lvl - 1) xs
138+
go lvl (x : xs)
139+
| x == [pstr|.|] = go lvl xs
140+
go lvl (_ : xs) = go (lvl + 1) xs
141+
142+
isInsideBaseDir' :: [OsPath] -> Bool
143+
isInsideBaseDir' = go 0
144+
where
145+
go :: Word -> [OsPath] -> Bool
115146
go !_ [] = True
116-
go 0 (".." : _) = False
117-
go lvl (".." : xs) = go (lvl - 1) xs
118-
go lvl ("." : xs) = go lvl xs
147+
go 0 (x : _)
148+
| x == [osstr|..|] = False
149+
go lvl (x : xs)
150+
| x == [osstr|..|] = go (lvl - 1) xs
151+
go lvl (x : xs)
152+
| x == [osstr|.|] = go lvl xs
119153
go lvl (_ : xs) = go (lvl + 1) xs
120154

121155
-- | Errors arising from tar file names being in some way invalid or dangerous
122156
data FileNameError
123-
= InvalidFileName FilePath
124-
| AbsoluteFileName FilePath
125-
| UnsafeLinkTarget FilePath
157+
= InvalidFileName PosixPath
158+
| AbsoluteFileName PosixPath
159+
| UnsafeLinkTarget PosixPath
160+
| FileNameDecodingFailure PosixPath
126161
-- ^ @since 0.6.0.0
127162
deriving (Typeable)
128163

@@ -136,6 +171,7 @@ showFileNameError mb_plat err = case err of
136171
InvalidFileName path -> "Invalid" ++ plat ++ " file name in tar archive: " ++ show path
137172
AbsoluteFileName path -> "Absolute" ++ plat ++ " file name in tar archive: " ++ show path
138173
UnsafeLinkTarget path -> "Unsafe" ++ plat ++ " link target in tar archive: " ++ show path
174+
FileNameDecodingFailure path -> "Decoding failure of path " ++ show path
139175
where plat = maybe "" (' ':) mb_plat
140176

141177

@@ -155,17 +191,17 @@ showFileNameError mb_plat err = case err of
155191
-- (or 'checkPortability').
156192
--
157193
checkTarbomb
158-
:: FilePath
194+
:: PosixPath
159195
-> Entries e
160-
-> GenEntries FilePath FilePath (Either (Either e DecodeLongNamesError) TarBombError)
196+
-> GenEntries PosixPath PosixPath (Either (Either e DecodeLongNamesError) TarBombError)
161197
checkTarbomb expectedTopDir
162198
= checkEntries (checkEntryTarbomb expectedTopDir)
163199
. decodeLongNames
164200

165201
-- | Worker of 'checkTarbomb'.
166202
--
167203
-- @since 0.6.0.0
168-
checkEntryTarbomb :: FilePath -> GenEntry FilePath linkTarget -> Maybe TarBombError
204+
checkEntryTarbomb :: PosixPath -> GenEntry PosixPath linkTarget -> Maybe TarBombError
169205
checkEntryTarbomb expectedTopDir entry = do
170206
case entryContent entry of
171207
-- Global extended header aka XGLTYPE aka pax_global_header
@@ -174,18 +210,18 @@ checkEntryTarbomb expectedTopDir entry = do
174210
-- Extended header referring to the next file in the archive aka XHDTYPE
175211
OtherEntryType 'x' _ _ -> Nothing
176212
_ ->
177-
case FilePath.Posix.splitDirectories (entryTarPath entry) of
213+
case PFP.splitDirectories (entryTarPath entry) of
178214
(topDir:_) | topDir == expectedTopDir -> Nothing
179215
_ -> Just $ TarBombError expectedTopDir (entryTarPath entry)
180216

181217
-- | An error that occurs if a tar file is a \"tar bomb\" that would extract
182218
-- files outside of the intended directory.
183219
data TarBombError
184220
= TarBombError
185-
FilePath -- ^ Path inside archive.
221+
PosixPath -- ^ Path inside archive.
186222
--
187223
-- @since 0.6.0.0
188-
FilePath -- ^ Expected top directory.
224+
PosixPath -- ^ Expected top directory.
189225
deriving (Typeable)
190226

191227
instance Exception TarBombError
@@ -219,43 +255,45 @@ instance Show TarBombError where
219255
--
220256
checkPortability
221257
:: Entries e
222-
-> GenEntries FilePath FilePath (Either (Either e DecodeLongNamesError) PortabilityError)
258+
-> GenEntries PosixPath PosixPath (Either (Either e DecodeLongNamesError) PortabilityError)
223259
checkPortability = checkEntries checkEntryPortability . decodeLongNames
224260

225261
-- | Worker of 'checkPortability'.
226262
--
227263
-- @since 0.6.0.0
228-
checkEntryPortability :: GenEntry FilePath linkTarget -> Maybe PortabilityError
264+
checkEntryPortability :: GenEntry PosixPath linkTarget -> Maybe PortabilityError
229265
checkEntryPortability entry
230-
| entryFormat entry `elem` [V7Format, GnuFormat]
231-
= Just $ NonPortableFormat (entryFormat entry)
266+
| (Just windowsPath) <- toWindowsPath posixPath =
267+
if | entryFormat entry `elem` [V7Format, GnuFormat]
268+
-> Just $ NonPortableFormat (entryFormat entry)
232269

233-
| not (portableFileType (entryContent entry))
234-
= Just NonPortableFileType
270+
| not (portableFileType (entryContent entry))
271+
-> Just NonPortableFileType
235272

236-
| not (all portableChar posixPath)
237-
= Just $ NonPortableEntryNameChar posixPath
273+
| not (PS.all portableChar posixPath)
274+
-> Just $ NonPortableEntryNameChar posixPath
238275

239-
| not (FilePath.Posix.isValid posixPath)
240-
= Just $ NonPortableFileName "unix" (InvalidFileName posixPath)
241-
| not (FilePath.Windows.isValid windowsPath)
242-
= Just $ NonPortableFileName "windows" (InvalidFileName windowsPath)
276+
| not (PFP.isValid posixPath)
277+
-> Just $ NonPortableFileName "unix" (InvalidFileName posixPath)
278+
| not (WFP.isValid windowsPath)
279+
-> Just $ NonPortableFileName "windows" (InvalidFileName posixPath)
243280

244-
| FilePath.Posix.isAbsolute posixPath
245-
= Just $ NonPortableFileName "unix" (AbsoluteFileName posixPath)
246-
| FilePath.Windows.isAbsolute windowsPath
247-
= Just $ NonPortableFileName "windows" (AbsoluteFileName windowsPath)
281+
| PFP.isAbsolute posixPath
282+
-> Just $ NonPortableFileName "unix" (AbsoluteFileName posixPath)
283+
| WFP.isAbsolute windowsPath
284+
-> Just $ NonPortableFileName "windows" (AbsoluteFileName posixPath)
248285

249-
| any (=="..") (FilePath.Posix.splitDirectories posixPath)
250-
= Just $ NonPortableFileName "unix" (InvalidFileName posixPath)
251-
| any (=="..") (FilePath.Windows.splitDirectories windowsPath)
252-
= Just $ NonPortableFileName "windows" (InvalidFileName windowsPath)
286+
| any (== [PS.pstr|..|]) (PFP.splitDirectories posixPath)
287+
-> Just $ NonPortableFileName "unix" (InvalidFileName posixPath)
288+
| any (== [WS.pstr|..|]) (WFP.splitDirectories windowsPath)
289+
-> Just $ NonPortableFileName "windows" (InvalidFileName posixPath)
253290

254-
| otherwise = Nothing
291+
| otherwise
292+
-> Nothing
293+
| otherwise = Just $ NonPortableDecodingFailure posixPath
255294

256295
where
257-
posixPath = entryTarPath entry
258-
windowsPath = fromFilePathToWindowsPath posixPath
296+
posixPath = entryTarPath entry
259297

260298
portableFileType ftype = case ftype of
261299
NormalFile {} -> True
@@ -264,14 +302,15 @@ checkEntryPortability entry
264302
Directory -> True
265303
_ -> False
266304

267-
portableChar c = c <= '\127'
305+
portableChar c = PS.toChar c <= '\127'
268306

269307
-- | Portability problems in a tar archive
270308
data PortabilityError
271309
= NonPortableFormat Format
272310
| NonPortableFileType
273-
| NonPortableEntryNameChar FilePath
311+
| NonPortableEntryNameChar PosixPath
274312
| NonPortableFileName PortabilityPlatform FileNameError
313+
| NonPortableDecodingFailure PosixPath
275314
deriving (Typeable)
276315

277316
-- | The name of a platform that portability issues arise from
@@ -289,6 +328,8 @@ instance Show PortabilityError where
289328
= "Non-portable character in archive entry name: " ++ show posixPath
290329
show (NonPortableFileName platform err)
291330
= showFileNameError (Just platform) err
331+
show (NonPortableDecodingFailure posixPath)
332+
= "Decoding failure of path " ++ show posixPath
292333

293334
--------------------------
294335
-- Utils

0 commit comments

Comments
 (0)