3
3
{-# LANGUAGE ViewPatterns #-}
4
4
{-# LANGUAGE RankNTypes #-}
5
5
{-# LANGUAGE ScopedTypeVariables #-}
6
+ {-# LANGUAGE QuasiQuotes #-}
7
+ {-# LANGUAGE MultiWayIf #-}
6
8
{-# OPTIONS_GHC -Wno-orphans #-}
7
9
{-# OPTIONS_HADDOCK hide #-}
8
10
-----------------------------------------------------------------------------
@@ -50,6 +52,17 @@ import qualified System.FilePath as FilePath.Native
50
52
import qualified System.FilePath.Windows as FilePath.Windows
51
53
import qualified System.FilePath.Posix as FilePath.Posix
52
54
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
+
53
66
54
67
--------------------------
55
68
-- Security
@@ -78,57 +91,79 @@ import qualified System.FilePath.Posix as FilePath.Posix
78
91
-- such as exhaustion of file handlers.
79
92
checkSecurity
80
93
:: Entries e
81
- -> GenEntries FilePath FilePath (Either (Either e DecodeLongNamesError ) FileNameError )
94
+ -> GenEntries PosixPath PosixPath (Either (Either e DecodeLongNamesError ) FileNameError )
82
95
checkSecurity = checkEntries checkEntrySecurity . decodeLongNames
83
96
84
97
-- | Worker of 'Codec.Archive.Tar.Check.checkSecurity'.
85
98
--
86
99
-- @since 0.6.0.0
87
- checkEntrySecurity :: GenEntry FilePath FilePath -> Maybe FileNameError
100
+ checkEntrySecurity :: GenEntry PosixPath PosixPath -> Maybe FileNameError
88
101
checkEntrySecurity e =
89
102
check (entryTarPath e) <|>
90
103
case entryContent e of
91
104
HardLink link ->
92
105
check link
93
106
SymbolicLink link ->
94
- check (FilePath.Posix. takeDirectory (entryTarPath e) FilePath.Posix . </> link)
107
+ check (PFP. takeDirectory (entryTarPath e) PFP . </> link)
95
108
_ -> Nothing
96
109
where
110
+ checkPosix :: PosixPath -> Maybe FileNameError
97
111
checkPosix name
98
- | FilePath.Posix. isAbsolute name
99
- = Just $ AbsoluteFileName name
100
- | not (FilePath.Posix. isValid name)
101
- = Just $ InvalidFileName name
102
- | not (isInsideBaseDir (FilePath.Posix. splitDirectories name))
103
- = Just $ UnsafeLinkTarget name
104
- | otherwise = Nothing
105
-
106
- checkNative (fromFilePathToNative -> name)
107
- | FilePath.Native. isAbsolute name || FilePath.Native. hasDrive name
112
+ | PFP. isAbsolute name
108
113
= Just $ AbsoluteFileName name
109
- | not (FilePath.Native . isValid name)
114
+ | not (PFP . isValid name)
110
115
= Just $ InvalidFileName name
111
- | not (isInsideBaseDir (FilePath.Native . splitDirectories name))
116
+ | not (isInsideBaseDir (PFP . splitDirectories name))
112
117
= Just $ UnsafeLinkTarget name
113
118
| otherwise = Nothing
114
119
115
- check name = checkPosix name <|> checkNative (fromFilePathToNative name)
116
-
117
- isInsideBaseDir :: [FilePath ] -> Bool
120
+ checkNative :: PosixPath -> Maybe FileNameError
121
+ checkNative name'
122
+ | (Just name) <- fromPosixPath name' =
123
+ if | OSP. isAbsolute name || OSP. hasDrive name
124
+ -> Just $ AbsoluteFileName name'
125
+ | not (OSP. isValid name)
126
+ -> Just $ InvalidFileName name'
127
+ | not (isInsideBaseDir' (OSP. splitDirectories name))
128
+ -> Just $ UnsafeLinkTarget name'
129
+ | otherwise
130
+ -> Nothing
131
+ | otherwise = Just $ FileNameDecodingFailure name'
132
+
133
+ check name = checkPosix name <|> checkNative name
134
+
135
+ isInsideBaseDir :: [PosixPath ] -> Bool
118
136
isInsideBaseDir = go 0
119
137
where
120
- go :: Word -> [FilePath ] -> Bool
138
+ go :: Word -> [PosixPath ] -> Bool
139
+ go ! _ [] = True
140
+ go 0 (x : _)
141
+ | x == [pstr |..|] = False
142
+ go lvl (x : xs)
143
+ | x == [pstr |..|] = go (lvl - 1 ) xs
144
+ go lvl (x : xs)
145
+ | x == [pstr |.|] = go lvl xs
146
+ go lvl (_ : xs) = go (lvl + 1 ) xs
147
+
148
+ isInsideBaseDir' :: [OsPath ] -> Bool
149
+ isInsideBaseDir' = go 0
150
+ where
151
+ go :: Word -> [OsPath ] -> Bool
121
152
go ! _ [] = True
122
- go 0 (" .." : _) = False
123
- go lvl (" .." : xs) = go (lvl - 1 ) xs
124
- go lvl (" ." : xs) = go lvl xs
153
+ go 0 (x : _)
154
+ | x == [osstr |..|] = False
155
+ go lvl (x : xs)
156
+ | x == [osstr |..|] = go (lvl - 1 ) xs
157
+ go lvl (x : xs)
158
+ | x == [osstr |.|] = go lvl xs
125
159
go lvl (_ : xs) = go (lvl + 1 ) xs
126
160
127
161
-- | Errors arising from tar file names being in some way invalid or dangerous
128
162
data FileNameError
129
- = InvalidFileName FilePath
130
- | AbsoluteFileName FilePath
131
- | UnsafeLinkTarget FilePath
163
+ = InvalidFileName PosixPath
164
+ | AbsoluteFileName PosixPath
165
+ | UnsafeLinkTarget PosixPath
166
+ | FileNameDecodingFailure PosixPath
132
167
-- ^ @since 0.6.0.0
133
168
deriving (Typeable )
134
169
@@ -142,6 +177,7 @@ showFileNameError mb_plat err = case err of
142
177
InvalidFileName path -> " Invalid" ++ plat ++ " file name in tar archive: " ++ show path
143
178
AbsoluteFileName path -> " Absolute" ++ plat ++ " file name in tar archive: " ++ show path
144
179
UnsafeLinkTarget path -> " Unsafe" ++ plat ++ " link target in tar archive: " ++ show path
180
+ FileNameDecodingFailure path -> " Decoding failure of path " ++ show path
145
181
where plat = maybe " " (' ' : ) mb_plat
146
182
147
183
@@ -167,17 +203,17 @@ showFileNameError mb_plat err = case err of
167
203
-- Not only it is faster, but also alleviates issues with lazy I/O
168
204
-- such as exhaustion of file handlers.
169
205
checkTarbomb
170
- :: FilePath
206
+ :: PosixPath
171
207
-> Entries e
172
- -> GenEntries FilePath FilePath (Either (Either e DecodeLongNamesError ) TarBombError )
208
+ -> GenEntries PosixPath PosixPath (Either (Either e DecodeLongNamesError ) TarBombError )
173
209
checkTarbomb expectedTopDir
174
210
= checkEntries (checkEntryTarbomb expectedTopDir)
175
211
. decodeLongNames
176
212
177
213
-- | Worker of 'checkTarbomb'.
178
214
--
179
215
-- @since 0.6.0.0
180
- checkEntryTarbomb :: FilePath -> GenEntry FilePath linkTarget -> Maybe TarBombError
216
+ checkEntryTarbomb :: PosixPath -> GenEntry PosixPath linkTarget -> Maybe TarBombError
181
217
checkEntryTarbomb expectedTopDir entry = do
182
218
case entryContent entry of
183
219
-- Global extended header aka XGLTYPE aka pax_global_header
@@ -186,18 +222,18 @@ checkEntryTarbomb expectedTopDir entry = do
186
222
-- Extended header referring to the next file in the archive aka XHDTYPE
187
223
OtherEntryType ' x' _ _ -> Nothing
188
224
_ ->
189
- case FilePath.Posix . splitDirectories (entryTarPath entry) of
225
+ case PFP . splitDirectories (entryTarPath entry) of
190
226
(topDir: _) | topDir == expectedTopDir -> Nothing
191
227
_ -> Just $ TarBombError expectedTopDir (entryTarPath entry)
192
228
193
229
-- | An error that occurs if a tar file is a \"tar bomb\" that would extract
194
230
-- files outside of the intended directory.
195
231
data TarBombError
196
232
= TarBombError
197
- FilePath -- ^ Path inside archive.
233
+ PosixPath -- ^ Path inside archive.
198
234
--
199
235
-- @since 0.6.0.0
200
- FilePath -- ^ Expected top directory.
236
+ PosixPath -- ^ Expected top directory.
201
237
deriving (Typeable )
202
238
203
239
instance Exception TarBombError
@@ -236,43 +272,45 @@ instance Show TarBombError where
236
272
-- such as exhaustion of file handlers.
237
273
checkPortability
238
274
:: Entries e
239
- -> GenEntries FilePath FilePath (Either (Either e DecodeLongNamesError ) PortabilityError )
275
+ -> GenEntries PosixPath PosixPath (Either (Either e DecodeLongNamesError ) PortabilityError )
240
276
checkPortability = checkEntries checkEntryPortability . decodeLongNames
241
277
242
278
-- | Worker of 'checkPortability'.
243
279
--
244
280
-- @since 0.6.0.0
245
- checkEntryPortability :: GenEntry FilePath linkTarget -> Maybe PortabilityError
281
+ checkEntryPortability :: GenEntry PosixPath linkTarget -> Maybe PortabilityError
246
282
checkEntryPortability entry
247
- | entryFormat entry `elem` [V7Format , GnuFormat ]
248
- = Just $ NonPortableFormat (entryFormat entry)
283
+ | (Just windowsPath) <- toWindowsPath posixPath =
284
+ if | entryFormat entry `elem` [V7Format , GnuFormat ]
285
+ -> Just $ NonPortableFormat (entryFormat entry)
249
286
250
- | not (portableFileType (entryContent entry))
251
- = Just NonPortableFileType
287
+ | not (portableFileType (entryContent entry))
288
+ -> Just NonPortableFileType
252
289
253
- | not (all portableChar posixPath)
254
- = Just $ NonPortableEntryNameChar posixPath
290
+ | not (PS. all portableChar posixPath)
291
+ -> Just $ NonPortableEntryNameChar posixPath
255
292
256
- | not (FilePath.Posix . isValid posixPath)
257
- = Just $ NonPortableFileName " unix" (InvalidFileName posixPath)
258
- | not (FilePath.Windows . isValid windowsPath)
259
- = Just $ NonPortableFileName " windows" (InvalidFileName windowsPath )
293
+ | not (PFP . isValid posixPath)
294
+ -> Just $ NonPortableFileName " unix" (InvalidFileName posixPath)
295
+ | not (WFP . isValid windowsPath)
296
+ -> Just $ NonPortableFileName " windows" (InvalidFileName posixPath )
260
297
261
- | FilePath.Posix . isAbsolute posixPath
262
- = Just $ NonPortableFileName " unix" (AbsoluteFileName posixPath)
263
- | FilePath.Windows . isAbsolute windowsPath
264
- = Just $ NonPortableFileName " windows" (AbsoluteFileName windowsPath )
298
+ | PFP . isAbsolute posixPath
299
+ -> Just $ NonPortableFileName " unix" (AbsoluteFileName posixPath)
300
+ | WFP . isAbsolute windowsPath
301
+ -> Just $ NonPortableFileName " windows" (AbsoluteFileName posixPath )
265
302
266
- | any (== " .. " ) (FilePath.Posix . splitDirectories posixPath)
267
- = Just $ NonPortableFileName " unix" (InvalidFileName posixPath)
268
- | any (== " .. " ) (FilePath.Windows . splitDirectories windowsPath)
269
- = Just $ NonPortableFileName " windows" (InvalidFileName windowsPath )
303
+ | any (== [ PS. pstr |..|] ) (PFP . splitDirectories posixPath)
304
+ -> Just $ NonPortableFileName " unix" (InvalidFileName posixPath)
305
+ | any (== [ WS. pstr |..|] ) (WFP . splitDirectories windowsPath)
306
+ -> Just $ NonPortableFileName " windows" (InvalidFileName posixPath )
270
307
271
- | otherwise = Nothing
308
+ | otherwise
309
+ -> Nothing
310
+ | otherwise = Just $ NonPortableDecodingFailure posixPath
272
311
273
312
where
274
- posixPath = entryTarPath entry
275
- windowsPath = fromFilePathToWindowsPath posixPath
313
+ posixPath = entryTarPath entry
276
314
277
315
portableFileType ftype = case ftype of
278
316
NormalFile {} -> True
@@ -281,14 +319,15 @@ checkEntryPortability entry
281
319
Directory -> True
282
320
_ -> False
283
321
284
- portableChar c = c <= '\ 127 '
322
+ portableChar c = PS. toChar c <= '\ 127 '
285
323
286
324
-- | Portability problems in a tar archive
287
325
data PortabilityError
288
326
= NonPortableFormat Format
289
327
| NonPortableFileType
290
- | NonPortableEntryNameChar FilePath
328
+ | NonPortableEntryNameChar PosixPath
291
329
| NonPortableFileName PortabilityPlatform FileNameError
330
+ | NonPortableDecodingFailure PosixPath
292
331
deriving (Typeable )
293
332
294
333
-- | The name of a platform that portability issues arise from
@@ -306,6 +345,8 @@ instance Show PortabilityError where
306
345
= " Non-portable character in archive entry name: " ++ show posixPath
307
346
show (NonPortableFileName platform err)
308
347
= showFileNameError (Just platform) err
348
+ show (NonPortableDecodingFailure posixPath)
349
+ = " Decoding failure of path " ++ show posixPath
309
350
310
351
--------------------------
311
352
-- Utils
0 commit comments