4
4
{-# LANGUAGE TypeApplications #-}
5
5
{-# LANGUAGE RankNTypes #-}
6
6
{-# LANGUAGE ScopedTypeVariables #-}
7
+ {-# LANGUAGE QuasiQuotes #-}
7
8
{-# OPTIONS_GHC -Wno-orphans #-}
8
9
-----------------------------------------------------------------------------
9
10
-- |
@@ -50,6 +51,17 @@ import qualified System.FilePath as FilePath.Native
50
51
import qualified System.FilePath.Windows as FilePath.Windows
51
52
import qualified System.FilePath.Posix as FilePath.Posix
52
53
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
+
53
65
54
66
--------------------------
55
67
-- Security
@@ -72,57 +84,77 @@ import qualified System.FilePath.Posix as FilePath.Posix
72
84
--
73
85
checkSecurity
74
86
:: Entries e
75
- -> GenEntries FilePath FilePath (Either (Either e DecodeLongNamesError ) FileNameError )
87
+ -> GenEntries PosixPath PosixPath (Either (Either e DecodeLongNamesError ) FileNameError )
76
88
checkSecurity = checkEntries checkEntrySecurity . decodeLongNames
77
89
78
90
-- | Worker of 'checkSecurity'.
79
91
--
80
92
-- @since 0.6.0.0
81
- checkEntrySecurity :: GenEntry FilePath FilePath -> Maybe FileNameError
93
+ checkEntrySecurity :: GenEntry PosixPath PosixPath -> Maybe FileNameError
82
94
checkEntrySecurity e =
83
95
check (entryTarPath e) <|>
84
96
case entryContent e of
85
97
HardLink link ->
86
98
check link
87
99
SymbolicLink link ->
88
- check (FilePath.Posix. takeDirectory (entryTarPath e) FilePath.Posix . </> link)
100
+ check (PFP. takeDirectory (entryTarPath e) PFP . </> link)
89
101
_ -> Nothing
90
102
where
103
+ checkPosix :: PosixPath -> Maybe FileNameError
91
104
checkPosix name
92
- | FilePath.Posix . isAbsolute name
105
+ | PFP . isAbsolute name
93
106
= Just $ AbsoluteFileName name
94
- | not (FilePath.Posix . isValid name)
107
+ | not (PFP . isValid name)
95
108
= Just $ InvalidFileName name
96
- | not (isInsideBaseDir (FilePath.Posix . splitDirectories name))
109
+ | not (isInsideBaseDir (PFP . splitDirectories name))
97
110
= Just $ UnsafeLinkTarget name
98
111
| otherwise = Nothing
99
112
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'
107
121
| otherwise = Nothing
122
+ where
123
+ (Just name) = fromPosixPath name'
108
124
109
- check name = checkPosix name <|> checkNative (fromFilePathToNative name)
125
+ check name = checkPosix name <|> checkNative name
110
126
111
- isInsideBaseDir :: [FilePath ] -> Bool
127
+ isInsideBaseDir :: [PosixPath ] -> Bool
112
128
isInsideBaseDir = go 0
113
129
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
115
144
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
119
151
go lvl (_ : xs) = go (lvl + 1 ) xs
120
152
121
153
-- | Errors arising from tar file names being in some way invalid or dangerous
122
154
data FileNameError
123
- = InvalidFileName FilePath
124
- | AbsoluteFileName FilePath
125
- | UnsafeLinkTarget FilePath
155
+ = InvalidFileName PosixPath
156
+ | AbsoluteFileName PosixPath
157
+ | UnsafeLinkTarget PosixPath
126
158
-- ^ @since 0.6.0.0
127
159
deriving (Typeable )
128
160
@@ -155,17 +187,17 @@ showFileNameError mb_plat err = case err of
155
187
-- (or 'checkPortability').
156
188
--
157
189
checkTarbomb
158
- :: FilePath
190
+ :: PosixPath
159
191
-> Entries e
160
- -> GenEntries FilePath FilePath (Either (Either e DecodeLongNamesError ) TarBombError )
192
+ -> GenEntries PosixPath PosixPath (Either (Either e DecodeLongNamesError ) TarBombError )
161
193
checkTarbomb expectedTopDir
162
194
= checkEntries (checkEntryTarbomb expectedTopDir)
163
195
. decodeLongNames
164
196
165
197
-- | Worker of 'checkTarbomb'.
166
198
--
167
199
-- @since 0.6.0.0
168
- checkEntryTarbomb :: FilePath -> GenEntry FilePath linkTarget -> Maybe TarBombError
200
+ checkEntryTarbomb :: PosixPath -> GenEntry PosixPath linkTarget -> Maybe TarBombError
169
201
checkEntryTarbomb expectedTopDir entry = do
170
202
case entryContent entry of
171
203
-- Global extended header aka XGLTYPE aka pax_global_header
@@ -174,18 +206,18 @@ checkEntryTarbomb expectedTopDir entry = do
174
206
-- Extended header referring to the next file in the archive aka XHDTYPE
175
207
OtherEntryType ' x' _ _ -> Nothing
176
208
_ ->
177
- case FilePath.Posix . splitDirectories (entryTarPath entry) of
209
+ case PFP . splitDirectories (entryTarPath entry) of
178
210
(topDir: _) | topDir == expectedTopDir -> Nothing
179
211
_ -> Just $ TarBombError expectedTopDir (entryTarPath entry)
180
212
181
213
-- | An error that occurs if a tar file is a \"tar bomb\" that would extract
182
214
-- files outside of the intended directory.
183
215
data TarBombError
184
216
= TarBombError
185
- FilePath -- ^ Path inside archive.
217
+ PosixPath -- ^ Path inside archive.
186
218
--
187
219
-- @since 0.6.0.0
188
- FilePath -- ^ Expected top directory.
220
+ PosixPath -- ^ Expected top directory.
189
221
deriving (Typeable )
190
222
191
223
instance Exception TarBombError
@@ -219,43 +251,43 @@ instance Show TarBombError where
219
251
--
220
252
checkPortability
221
253
:: Entries e
222
- -> GenEntries FilePath FilePath (Either (Either e DecodeLongNamesError ) PortabilityError )
254
+ -> GenEntries PosixPath PosixPath (Either (Either e DecodeLongNamesError ) PortabilityError )
223
255
checkPortability = checkEntries checkEntryPortability . decodeLongNames
224
256
225
257
-- | Worker of 'checkPortability'.
226
258
--
227
259
-- @since 0.6.0.0
228
- checkEntryPortability :: GenEntry FilePath linkTarget -> Maybe PortabilityError
260
+ checkEntryPortability :: GenEntry PosixPath linkTarget -> Maybe PortabilityError
229
261
checkEntryPortability entry
230
262
| entryFormat entry `elem` [V7Format , GnuFormat ]
231
263
= Just $ NonPortableFormat (entryFormat entry)
232
264
233
265
| not (portableFileType (entryContent entry))
234
266
= Just NonPortableFileType
235
267
236
- | not (all portableChar posixPath)
268
+ | not (PS. all portableChar posixPath)
237
269
= Just $ NonPortableEntryNameChar posixPath
238
270
239
- | not (FilePath.Posix . isValid posixPath)
271
+ | not (PFP . isValid posixPath)
240
272
= 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 )
243
275
244
- | FilePath.Posix . isAbsolute posixPath
276
+ | PFP . isAbsolute posixPath
245
277
= 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 )
248
280
249
- | any (== " .. " ) (FilePath.Posix . splitDirectories posixPath)
281
+ | any (== [ PS. pstr |..|] ) (PFP . splitDirectories posixPath)
250
282
= 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 )
253
285
254
286
| otherwise = Nothing
255
287
256
288
where
257
- posixPath = entryTarPath entry
258
- windowsPath = fromFilePathToWindowsPath posixPath
289
+ posixPath = entryTarPath entry
290
+ ( Just windowsPath) = toWindowsPath posixPath
259
291
260
292
portableFileType ftype = case ftype of
261
293
NormalFile {} -> True
@@ -264,13 +296,13 @@ checkEntryPortability entry
264
296
Directory -> True
265
297
_ -> False
266
298
267
- portableChar c = c <= '\ 127 '
299
+ portableChar c = PS. toChar c <= '\ 127 '
268
300
269
301
-- | Portability problems in a tar archive
270
302
data PortabilityError
271
303
= NonPortableFormat Format
272
304
| NonPortableFileType
273
- | NonPortableEntryNameChar FilePath
305
+ | NonPortableEntryNameChar PosixPath
274
306
| NonPortableFileName PortabilityPlatform FileNameError
275
307
deriving (Typeable )
276
308
0 commit comments