Skip to content

Commit 35ca6b0

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

File tree

13 files changed

+510
-363
lines changed

13 files changed

+510
-363
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: 76 additions & 44 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
{-# LANGUAGE TypeApplications #-}
55
{-# LANGUAGE RankNTypes #-}
66
{-# LANGUAGE ScopedTypeVariables #-}
7+
{-# LANGUAGE QuasiQuotes #-}
78
{-# OPTIONS_GHC -Wno-orphans #-}
89
-----------------------------------------------------------------------------
910
-- |
@@ -50,6 +51,17 @@ import qualified System.FilePath as FilePath.Native
5051
import qualified System.FilePath.Windows as FilePath.Windows
5152
import qualified System.FilePath.Posix as FilePath.Posix
5253

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

5466
--------------------------
5567
-- Security
@@ -72,57 +84,77 @@ import qualified System.FilePath.Posix as FilePath.Posix
7284
--
7385
checkSecurity
7486
:: Entries e
75-
-> GenEntries FilePath FilePath (Either (Either e DecodeLongNamesError) FileNameError)
87+
-> GenEntries PosixPath PosixPath (Either (Either e DecodeLongNamesError) FileNameError)
7688
checkSecurity = checkEntries checkEntrySecurity . decodeLongNames
7789

7890
-- | Worker of 'checkSecurity'.
7991
--
8092
-- @since 0.6.0.0
81-
checkEntrySecurity :: GenEntry FilePath FilePath -> Maybe FileNameError
93+
checkEntrySecurity :: GenEntry PosixPath PosixPath -> Maybe FileNameError
8294
checkEntrySecurity e =
8395
check (entryTarPath e) <|>
8496
case entryContent e of
8597
HardLink link ->
8698
check link
8799
SymbolicLink link ->
88-
check (FilePath.Posix.takeDirectory (entryTarPath e) FilePath.Posix.</> link)
100+
check (PFP.takeDirectory (entryTarPath e) PFP.</> link)
89101
_ -> Nothing
90102
where
103+
checkPosix :: PosixPath -> Maybe FileNameError
91104
checkPosix name
92-
| FilePath.Posix.isAbsolute name
105+
| PFP.isAbsolute name
93106
= Just $ AbsoluteFileName name
94-
| not (FilePath.Posix.isValid name)
107+
| not (PFP.isValid name)
95108
= Just $ InvalidFileName name
96-
| not (isInsideBaseDir (FilePath.Posix.splitDirectories name))
109+
| not (isInsideBaseDir (PFP.splitDirectories name))
97110
= Just $ UnsafeLinkTarget name
98111
| otherwise = Nothing
99112

100-
checkNative (fromFilePathToNative -> name)
101-
| FilePath.Native.isAbsolute name || FilePath.Native.hasDrive name
102-
= Just $ AbsoluteFileName name
103-
| not (FilePath.Native.isValid name)
104-
= Just $ InvalidFileName name
105-
| not (isInsideBaseDir (FilePath.Native.splitDirectories name))
106-
= Just $ UnsafeLinkTarget name
113+
checkNative :: PosixPath -> Maybe FileNameError
114+
checkNative name'
115+
| OSP.isAbsolute name || OSP.hasDrive name
116+
= Just $ AbsoluteFileName name'
117+
| not (OSP.isValid name)
118+
= Just $ InvalidFileName name'
119+
| not (isInsideBaseDir' (OSP.splitDirectories name))
120+
= Just $ UnsafeLinkTarget name'
107121
| otherwise = Nothing
122+
where
123+
(Just name) = fromPosixPath name'
108124

109-
check name = checkPosix name <|> checkNative (fromFilePathToNative name)
125+
check name = checkPosix name <|> checkNative name
110126

111-
isInsideBaseDir :: [FilePath] -> Bool
127+
isInsideBaseDir :: [PosixPath] -> Bool
112128
isInsideBaseDir = go 0
113129
where
114-
go :: Word -> [FilePath] -> Bool
130+
go :: Word -> [PosixPath] -> Bool
131+
go !_ [] = True
132+
go 0 (x : _)
133+
| x == [pstr|..|] = False
134+
go lvl (x : xs)
135+
| x == [pstr|..|] = go (lvl - 1) xs
136+
go lvl (x : xs)
137+
| x == [pstr|.|] = go lvl xs
138+
go lvl (_ : xs) = go (lvl + 1) xs
139+
140+
isInsideBaseDir' :: [OsPath] -> Bool
141+
isInsideBaseDir' = go 0
142+
where
143+
go :: Word -> [OsPath] -> Bool
115144
go !_ [] = True
116-
go 0 (".." : _) = False
117-
go lvl (".." : xs) = go (lvl - 1) xs
118-
go lvl ("." : xs) = go lvl xs
145+
go 0 (x : _)
146+
| x == [osstr|..|] = False
147+
go lvl (x : xs)
148+
| x == [osstr|..|] = go (lvl - 1) xs
149+
go lvl (x : xs)
150+
| x == [osstr|.|] = go lvl xs
119151
go lvl (_ : xs) = go (lvl + 1) xs
120152

121153
-- | Errors arising from tar file names being in some way invalid or dangerous
122154
data FileNameError
123-
= InvalidFileName FilePath
124-
| AbsoluteFileName FilePath
125-
| UnsafeLinkTarget FilePath
155+
= InvalidFileName PosixPath
156+
| AbsoluteFileName PosixPath
157+
| UnsafeLinkTarget PosixPath
126158
-- ^ @since 0.6.0.0
127159
deriving (Typeable)
128160

@@ -155,17 +187,17 @@ showFileNameError mb_plat err = case err of
155187
-- (or 'checkPortability').
156188
--
157189
checkTarbomb
158-
:: FilePath
190+
:: PosixPath
159191
-> Entries e
160-
-> GenEntries FilePath FilePath (Either (Either e DecodeLongNamesError) TarBombError)
192+
-> GenEntries PosixPath PosixPath (Either (Either e DecodeLongNamesError) TarBombError)
161193
checkTarbomb expectedTopDir
162194
= checkEntries (checkEntryTarbomb expectedTopDir)
163195
. decodeLongNames
164196

165197
-- | Worker of 'checkTarbomb'.
166198
--
167199
-- @since 0.6.0.0
168-
checkEntryTarbomb :: FilePath -> GenEntry FilePath linkTarget -> Maybe TarBombError
200+
checkEntryTarbomb :: PosixPath -> GenEntry PosixPath linkTarget -> Maybe TarBombError
169201
checkEntryTarbomb expectedTopDir entry = do
170202
case entryContent entry of
171203
-- Global extended header aka XGLTYPE aka pax_global_header
@@ -174,18 +206,18 @@ checkEntryTarbomb expectedTopDir entry = do
174206
-- Extended header referring to the next file in the archive aka XHDTYPE
175207
OtherEntryType 'x' _ _ -> Nothing
176208
_ ->
177-
case FilePath.Posix.splitDirectories (entryTarPath entry) of
209+
case PFP.splitDirectories (entryTarPath entry) of
178210
(topDir:_) | topDir == expectedTopDir -> Nothing
179211
_ -> Just $ TarBombError expectedTopDir (entryTarPath entry)
180212

181213
-- | An error that occurs if a tar file is a \"tar bomb\" that would extract
182214
-- files outside of the intended directory.
183215
data TarBombError
184216
= TarBombError
185-
FilePath -- ^ Path inside archive.
217+
PosixPath -- ^ Path inside archive.
186218
--
187219
-- @since 0.6.0.0
188-
FilePath -- ^ Expected top directory.
220+
PosixPath -- ^ Expected top directory.
189221
deriving (Typeable)
190222

191223
instance Exception TarBombError
@@ -219,43 +251,43 @@ instance Show TarBombError where
219251
--
220252
checkPortability
221253
:: Entries e
222-
-> GenEntries FilePath FilePath (Either (Either e DecodeLongNamesError) PortabilityError)
254+
-> GenEntries PosixPath PosixPath (Either (Either e DecodeLongNamesError) PortabilityError)
223255
checkPortability = checkEntries checkEntryPortability . decodeLongNames
224256

225257
-- | Worker of 'checkPortability'.
226258
--
227259
-- @since 0.6.0.0
228-
checkEntryPortability :: GenEntry FilePath linkTarget -> Maybe PortabilityError
260+
checkEntryPortability :: GenEntry PosixPath linkTarget -> Maybe PortabilityError
229261
checkEntryPortability entry
230262
| entryFormat entry `elem` [V7Format, GnuFormat]
231263
= Just $ NonPortableFormat (entryFormat entry)
232264

233265
| not (portableFileType (entryContent entry))
234266
= Just NonPortableFileType
235267

236-
| not (all portableChar posixPath)
268+
| not (PS.all portableChar posixPath)
237269
= Just $ NonPortableEntryNameChar posixPath
238270

239-
| not (FilePath.Posix.isValid posixPath)
271+
| not (PFP.isValid posixPath)
240272
= Just $ NonPortableFileName "unix" (InvalidFileName posixPath)
241-
| not (FilePath.Windows.isValid windowsPath)
242-
= Just $ NonPortableFileName "windows" (InvalidFileName windowsPath)
273+
| not (WFP.isValid windowsPath)
274+
= Just $ NonPortableFileName "windows" (InvalidFileName posixPath)
243275

244-
| FilePath.Posix.isAbsolute posixPath
276+
| PFP.isAbsolute posixPath
245277
= Just $ NonPortableFileName "unix" (AbsoluteFileName posixPath)
246-
| FilePath.Windows.isAbsolute windowsPath
247-
= Just $ NonPortableFileName "windows" (AbsoluteFileName windowsPath)
278+
| WFP.isAbsolute windowsPath
279+
= Just $ NonPortableFileName "windows" (AbsoluteFileName posixPath)
248280

249-
| any (=="..") (FilePath.Posix.splitDirectories posixPath)
281+
| any (== [PS.pstr|..|]) (PFP.splitDirectories posixPath)
250282
= Just $ NonPortableFileName "unix" (InvalidFileName posixPath)
251-
| any (=="..") (FilePath.Windows.splitDirectories windowsPath)
252-
= Just $ NonPortableFileName "windows" (InvalidFileName windowsPath)
283+
| any (== [WS.pstr|..|]) (WFP.splitDirectories windowsPath)
284+
= Just $ NonPortableFileName "windows" (InvalidFileName posixPath)
253285

254286
| otherwise = Nothing
255287

256288
where
257-
posixPath = entryTarPath entry
258-
windowsPath = fromFilePathToWindowsPath posixPath
289+
posixPath = entryTarPath entry
290+
(Just windowsPath) = toWindowsPath posixPath
259291

260292
portableFileType ftype = case ftype of
261293
NormalFile {} -> True
@@ -264,13 +296,13 @@ checkEntryPortability entry
264296
Directory -> True
265297
_ -> False
266298

267-
portableChar c = c <= '\127'
299+
portableChar c = PS.toChar c <= '\127'
268300

269301
-- | Portability problems in a tar archive
270302
data PortabilityError
271303
= NonPortableFormat Format
272304
| NonPortableFileType
273-
| NonPortableEntryNameChar FilePath
305+
| NonPortableEntryNameChar PosixPath
274306
| NonPortableFileName PortabilityPlatform FileNameError
275307
deriving (Typeable)
276308

0 commit comments

Comments
 (0)