4
4
{-# LANGUAGE TypeApplications #-}
5
5
{-# LANGUAGE RankNTypes #-}
6
6
{-# LANGUAGE ScopedTypeVariables #-}
7
+ {-# LANGUAGE QuasiQuotes #-}
8
+ {-# LANGUAGE MultiWayIf #-}
7
9
{-# OPTIONS_GHC -Wno-orphans #-}
8
10
-----------------------------------------------------------------------------
9
11
-- |
@@ -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
@@ -72,57 +85,79 @@ import qualified System.FilePath.Posix as FilePath.Posix
72
85
--
73
86
checkSecurity
74
87
:: Entries e
75
- -> GenEntries FilePath FilePath (Either (Either e DecodeLongNamesError ) FileNameError )
88
+ -> GenEntries PosixPath PosixPath (Either (Either e DecodeLongNamesError ) FileNameError )
76
89
checkSecurity = checkEntries checkEntrySecurity . decodeLongNames
77
90
78
91
-- | Worker of 'checkSecurity'.
79
92
--
80
93
-- @since 0.6.0.0
81
- checkEntrySecurity :: GenEntry FilePath FilePath -> Maybe FileNameError
94
+ checkEntrySecurity :: GenEntry PosixPath PosixPath -> Maybe FileNameError
82
95
checkEntrySecurity e =
83
96
check (entryTarPath e) <|>
84
97
case entryContent e of
85
98
HardLink link ->
86
99
check link
87
100
SymbolicLink link ->
88
- check (FilePath.Posix. takeDirectory (entryTarPath e) FilePath.Posix . </> link)
101
+ check (PFP. takeDirectory (entryTarPath e) PFP . </> link)
89
102
_ -> Nothing
90
103
where
104
+ checkPosix :: PosixPath -> Maybe FileNameError
91
105
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
102
107
= Just $ AbsoluteFileName name
103
- | not (FilePath.Native . isValid name)
108
+ | not (PFP . isValid name)
104
109
= Just $ InvalidFileName name
105
- | not (isInsideBaseDir (FilePath.Native . splitDirectories name))
110
+ | not (isInsideBaseDir (PFP . splitDirectories name))
106
111
= Just $ UnsafeLinkTarget name
107
112
| otherwise = Nothing
108
113
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
112
130
isInsideBaseDir = go 0
113
131
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
115
146
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
119
153
go lvl (_ : xs) = go (lvl + 1 ) xs
120
154
121
155
-- | Errors arising from tar file names being in some way invalid or dangerous
122
156
data FileNameError
123
- = InvalidFileName FilePath
124
- | AbsoluteFileName FilePath
125
- | UnsafeLinkTarget FilePath
157
+ = InvalidFileName PosixPath
158
+ | AbsoluteFileName PosixPath
159
+ | UnsafeLinkTarget PosixPath
160
+ | FileNameDecodingFailure PosixPath
126
161
-- ^ @since 0.6.0.0
127
162
deriving (Typeable )
128
163
@@ -136,6 +171,7 @@ showFileNameError mb_plat err = case err of
136
171
InvalidFileName path -> " Invalid" ++ plat ++ " file name in tar archive: " ++ show path
137
172
AbsoluteFileName path -> " Absolute" ++ plat ++ " file name in tar archive: " ++ show path
138
173
UnsafeLinkTarget path -> " Unsafe" ++ plat ++ " link target in tar archive: " ++ show path
174
+ FileNameDecodingFailure path -> " Decoding failure of path " ++ show path
139
175
where plat = maybe " " (' ' : ) mb_plat
140
176
141
177
@@ -155,17 +191,17 @@ showFileNameError mb_plat err = case err of
155
191
-- (or 'checkPortability').
156
192
--
157
193
checkTarbomb
158
- :: FilePath
194
+ :: PosixPath
159
195
-> Entries e
160
- -> GenEntries FilePath FilePath (Either (Either e DecodeLongNamesError ) TarBombError )
196
+ -> GenEntries PosixPath PosixPath (Either (Either e DecodeLongNamesError ) TarBombError )
161
197
checkTarbomb expectedTopDir
162
198
= checkEntries (checkEntryTarbomb expectedTopDir)
163
199
. decodeLongNames
164
200
165
201
-- | Worker of 'checkTarbomb'.
166
202
--
167
203
-- @since 0.6.0.0
168
- checkEntryTarbomb :: FilePath -> GenEntry FilePath linkTarget -> Maybe TarBombError
204
+ checkEntryTarbomb :: PosixPath -> GenEntry PosixPath linkTarget -> Maybe TarBombError
169
205
checkEntryTarbomb expectedTopDir entry = do
170
206
case entryContent entry of
171
207
-- Global extended header aka XGLTYPE aka pax_global_header
@@ -174,18 +210,18 @@ checkEntryTarbomb expectedTopDir entry = do
174
210
-- Extended header referring to the next file in the archive aka XHDTYPE
175
211
OtherEntryType ' x' _ _ -> Nothing
176
212
_ ->
177
- case FilePath.Posix . splitDirectories (entryTarPath entry) of
213
+ case PFP . splitDirectories (entryTarPath entry) of
178
214
(topDir: _) | topDir == expectedTopDir -> Nothing
179
215
_ -> Just $ TarBombError expectedTopDir (entryTarPath entry)
180
216
181
217
-- | An error that occurs if a tar file is a \"tar bomb\" that would extract
182
218
-- files outside of the intended directory.
183
219
data TarBombError
184
220
= TarBombError
185
- FilePath -- ^ Path inside archive.
221
+ PosixPath -- ^ Path inside archive.
186
222
--
187
223
-- @since 0.6.0.0
188
- FilePath -- ^ Expected top directory.
224
+ PosixPath -- ^ Expected top directory.
189
225
deriving (Typeable )
190
226
191
227
instance Exception TarBombError
@@ -219,43 +255,45 @@ instance Show TarBombError where
219
255
--
220
256
checkPortability
221
257
:: Entries e
222
- -> GenEntries FilePath FilePath (Either (Either e DecodeLongNamesError ) PortabilityError )
258
+ -> GenEntries PosixPath PosixPath (Either (Either e DecodeLongNamesError ) PortabilityError )
223
259
checkPortability = checkEntries checkEntryPortability . decodeLongNames
224
260
225
261
-- | Worker of 'checkPortability'.
226
262
--
227
263
-- @since 0.6.0.0
228
- checkEntryPortability :: GenEntry FilePath linkTarget -> Maybe PortabilityError
264
+ checkEntryPortability :: GenEntry PosixPath linkTarget -> Maybe PortabilityError
229
265
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)
232
269
233
- | not (portableFileType (entryContent entry))
234
- = Just NonPortableFileType
270
+ | not (portableFileType (entryContent entry))
271
+ -> Just NonPortableFileType
235
272
236
- | not (all portableChar posixPath)
237
- = Just $ NonPortableEntryNameChar posixPath
273
+ | not (PS. all portableChar posixPath)
274
+ -> Just $ NonPortableEntryNameChar posixPath
238
275
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 )
243
280
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 )
248
285
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 )
253
290
254
- | otherwise = Nothing
291
+ | otherwise
292
+ -> Nothing
293
+ | otherwise = Just $ NonPortableDecodingFailure posixPath
255
294
256
295
where
257
- posixPath = entryTarPath entry
258
- windowsPath = fromFilePathToWindowsPath posixPath
296
+ posixPath = entryTarPath entry
259
297
260
298
portableFileType ftype = case ftype of
261
299
NormalFile {} -> True
@@ -264,14 +302,15 @@ checkEntryPortability entry
264
302
Directory -> True
265
303
_ -> False
266
304
267
- portableChar c = c <= '\ 127 '
305
+ portableChar c = PS. toChar c <= '\ 127 '
268
306
269
307
-- | Portability problems in a tar archive
270
308
data PortabilityError
271
309
= NonPortableFormat Format
272
310
| NonPortableFileType
273
- | NonPortableEntryNameChar FilePath
311
+ | NonPortableEntryNameChar PosixPath
274
312
| NonPortableFileName PortabilityPlatform FileNameError
313
+ | NonPortableDecodingFailure PosixPath
275
314
deriving (Typeable )
276
315
277
316
-- | The name of a platform that portability issues arise from
@@ -289,6 +328,8 @@ instance Show PortabilityError where
289
328
= " Non-portable character in archive entry name: " ++ show posixPath
290
329
show (NonPortableFileName platform err)
291
330
= showFileNameError (Just platform) err
331
+ show (NonPortableDecodingFailure posixPath)
332
+ = " Decoding failure of path " ++ show posixPath
292
333
293
334
--------------------------
294
335
-- Utils
0 commit comments