Skip to content

Commit

Permalink
Implement Unicode support by utilizing PosixString and friends
Browse files Browse the repository at this point in the history
  • Loading branch information
hasufell committed Dec 11, 2023
1 parent 6dd1a8d commit 6dd8c9c
Show file tree
Hide file tree
Showing 13 changed files with 523 additions and 360 deletions.
27 changes: 15 additions & 12 deletions Codec/Archive/Tar.hs
Original file line number Diff line number Diff line change
Expand Up @@ -165,9 +165,12 @@ import Codec.Archive.Tar.Check

import Control.Exception (Exception, throw, catch)
import qualified Data.ByteString.Lazy as BS
import System.IO (withFile, IOMode(..))
import System.IO (IOMode(..))
import Prelude hiding (read)

import System.OsPath (OsPath)
import qualified System.File.OsPath as OSP

-- | Create a new @\".tar\"@ file from a directory of files.
--
-- It is equivalent to calling the standard @tar@ program like so:
Expand Down Expand Up @@ -199,11 +202,11 @@ import Prelude hiding (read)
--
-- * @rwxr-xr-x@ for directories
--
create :: FilePath -- ^ Path of the \".tar\" file to write.
-> FilePath -- ^ Base directory
-> [FilePath] -- ^ Files and directories to archive, relative to base dir
create :: OsPath -- ^ Path of the \".tar\" file to write.
-> OsPath -- ^ Base directory
-> [OsPath] -- ^ Files and directories to archive, relative to base dir
-> IO ()
create tar base paths = BS.writeFile tar . write =<< pack base paths
create tar base paths = OSP.writeFile tar . write =<< pack base paths

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

-- | Append new entries to a @\".tar\"@ file from a directory of files.
--
-- This is much like 'create', except that all the entries are added to the
-- end of an existing tar file. Or if the file does not already exists then
-- it behaves the same as 'create'.
--
append :: FilePath -- ^ Path of the \".tar\" file to write.
-> FilePath -- ^ Base directory
-> [FilePath] -- ^ Files and directories to archive, relative to base dir
append :: OsPath -- ^ Path of the \".tar\" file to write.
-> OsPath -- ^ Base directory
-> [OsPath] -- ^ Files and directories to archive, relative to base dir
-> IO ()
append tar base paths =
withFile tar ReadWriteMode $ \hnd -> do
OSP.withFile tar ReadWriteMode $ \hnd -> do
_ <- hSeekEndEntryOffset hnd Nothing
BS.hPut hnd . write =<< pack base paths
114 changes: 70 additions & 44 deletions Codec/Archive/Tar/Check/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE QuasiQuotes #-}
{-# OPTIONS_GHC -Wno-orphans #-}
-----------------------------------------------------------------------------
-- |
Expand Down Expand Up @@ -50,6 +51,17 @@ import qualified System.FilePath as FilePath.Native
import qualified System.FilePath.Windows as FilePath.Windows
import qualified System.FilePath.Posix as FilePath.Posix

import System.OsPath (OsPath)
import System.OsPath.Posix (PosixPath)
import qualified System.OsPath as OSP
import qualified System.OsPath.Posix as PFP
import qualified System.OsPath.Windows as WFP

import System.OsString.Posix (pstr)
import System.OsString (osstr)
import qualified System.OsString.Posix as PS
import qualified System.OsString.Windows as WS


--------------------------
-- Security
Expand All @@ -72,57 +84,71 @@ import qualified System.FilePath.Posix as FilePath.Posix
--
checkSecurity
:: Entries e
-> GenEntries FilePath FilePath (Either (Either e DecodeLongNamesError) FileNameError)
-> GenEntries PosixPath PosixPath (Either (Either e DecodeLongNamesError) FileNameError)
checkSecurity = checkEntries checkEntrySecurity . decodeLongNames

-- | Worker of 'checkSecurity'.
--
-- @since 0.6.0.0
checkEntrySecurity :: GenEntry FilePath FilePath -> Maybe FileNameError
checkEntrySecurity :: GenEntry PosixPath PosixPath -> Maybe FileNameError
checkEntrySecurity e =
check (entryTarPath e) <|>
case entryContent e of
HardLink link ->
check link
SymbolicLink link ->
check (FilePath.Posix.takeDirectory (entryTarPath e) FilePath.Posix.</> link)
check (PFP.takeDirectory (entryTarPath e) PFP.</> link)
_ -> Nothing
where
checkPosix :: PosixPath -> Maybe FileNameError
checkPosix name
| FilePath.Posix.isAbsolute name
| PFP.isAbsolute name
= Just $ AbsoluteFileName name
| not (FilePath.Posix.isValid name)
| not (PFP.isValid name)
= Just $ InvalidFileName name
| not (isInsideBaseDir (FilePath.Posix.splitDirectories name))
| not (isInsideBaseDir (PFP.splitDirectories name))
= Just $ UnsafeLinkTarget name
| otherwise = Nothing

checkNative (fromFilePathToNative -> name)
| FilePath.Native.isAbsolute name || FilePath.Native.hasDrive name
= Just $ AbsoluteFileName name
| not (FilePath.Native.isValid name)
= Just $ InvalidFileName name
| not (isInsideBaseDir (FilePath.Native.splitDirectories name))
= Just $ UnsafeLinkTarget name
checkNative :: PosixPath -> Maybe FileNameError
checkNative name'
| OSP.isAbsolute name || OSP.hasDrive name
= Just $ AbsoluteFileName name'
| not (OSP.isValid name)
= Just $ InvalidFileName name'
| not (isInsideBaseDir' (OSP.splitDirectories name))
= Just $ UnsafeLinkTarget name'
| otherwise = Nothing
where
(Just name) = fromPosixPath name'

check name = checkPosix name <|> checkNative (fromFilePathToNative name)
check name = checkPosix name <|> checkNative name

isInsideBaseDir :: [FilePath] -> Bool
isInsideBaseDir :: [PosixPath] -> Bool
isInsideBaseDir = go 0
where
go :: Word -> [FilePath] -> Bool
go :: Word -> [PosixPath] -> Bool
go !_ [] = True
go 0 ([pstr|..|] : _) = False
go lvl ([pstr|..|] : xs) = go (lvl - 1) xs
go lvl ([pstr|.|] : xs) = go lvl xs
go lvl (_ : xs) = go (lvl + 1) xs

isInsideBaseDir' :: [OsPath] -> Bool
isInsideBaseDir' = go 0
where
go :: Word -> [OsPath] -> Bool
go !_ [] = True
go 0 (".." : _) = False
go lvl (".." : xs) = go (lvl - 1) xs
go lvl ("." : xs) = go lvl xs
go 0 ([osstr|..|] : _) = False
go lvl ([osstr|..|] : xs) = go (lvl - 1) xs
go lvl ([osstr|.|] : xs) = go lvl xs
go lvl (_ : xs) = go (lvl + 1) xs

-- | Errors arising from tar file names being in some way invalid or dangerous
data FileNameError
= InvalidFileName FilePath
| AbsoluteFileName FilePath
| UnsafeLinkTarget FilePath
= InvalidFileName PosixPath
| AbsoluteFileName PosixPath
| UnsafeLinkTarget PosixPath
-- ^ @since 0.6.0.0
deriving (Typeable)

Expand Down Expand Up @@ -155,17 +181,17 @@ showFileNameError mb_plat err = case err of
-- (or 'checkPortability').
--
checkTarbomb
:: FilePath
:: PosixPath
-> Entries e
-> GenEntries FilePath FilePath (Either (Either e DecodeLongNamesError) TarBombError)
-> GenEntries PosixPath PosixPath (Either (Either e DecodeLongNamesError) TarBombError)
checkTarbomb expectedTopDir
= checkEntries (checkEntryTarbomb expectedTopDir)
. decodeLongNames

-- | Worker of 'checkTarbomb'.
--
-- @since 0.6.0.0
checkEntryTarbomb :: FilePath -> GenEntry FilePath linkTarget -> Maybe TarBombError
checkEntryTarbomb :: PosixPath -> GenEntry PosixPath linkTarget -> Maybe TarBombError
checkEntryTarbomb expectedTopDir entry = do
case entryContent entry of
-- Global extended header aka XGLTYPE aka pax_global_header
Expand All @@ -174,18 +200,18 @@ checkEntryTarbomb expectedTopDir entry = do
-- Extended header referring to the next file in the archive aka XHDTYPE
OtherEntryType 'x' _ _ -> Nothing
_ ->
case FilePath.Posix.splitDirectories (entryTarPath entry) of
case PFP.splitDirectories (entryTarPath entry) of
(topDir:_) | topDir == expectedTopDir -> Nothing
_ -> Just $ TarBombError expectedTopDir (entryTarPath entry)

-- | An error that occurs if a tar file is a \"tar bomb\" that would extract
-- files outside of the intended directory.
data TarBombError
= TarBombError
FilePath -- ^ Path inside archive.
PosixPath -- ^ Path inside archive.
--
-- @since 0.6.0.0
FilePath -- ^ Expected top directory.
PosixPath -- ^ Expected top directory.
deriving (Typeable)

instance Exception TarBombError
Expand Down Expand Up @@ -219,43 +245,43 @@ instance Show TarBombError where
--
checkPortability
:: Entries e
-> GenEntries FilePath FilePath (Either (Either e DecodeLongNamesError) PortabilityError)
-> GenEntries PosixPath PosixPath (Either (Either e DecodeLongNamesError) PortabilityError)
checkPortability = checkEntries checkEntryPortability . decodeLongNames

-- | Worker of 'checkPortability'.
--
-- @since 0.6.0.0
checkEntryPortability :: GenEntry FilePath linkTarget -> Maybe PortabilityError
checkEntryPortability :: GenEntry PosixPath linkTarget -> Maybe PortabilityError
checkEntryPortability entry
| entryFormat entry `elem` [V7Format, GnuFormat]
= Just $ NonPortableFormat (entryFormat entry)

| not (portableFileType (entryContent entry))
= Just NonPortableFileType

| not (all portableChar posixPath)
| not (PS.all portableChar posixPath)
= Just $ NonPortableEntryNameChar posixPath

| not (FilePath.Posix.isValid posixPath)
| not (PFP.isValid posixPath)
= Just $ NonPortableFileName "unix" (InvalidFileName posixPath)
| not (FilePath.Windows.isValid windowsPath)
= Just $ NonPortableFileName "windows" (InvalidFileName windowsPath)
| not (WFP.isValid windowsPath)
= Just $ NonPortableFileName "windows" (InvalidFileName posixPath)

| FilePath.Posix.isAbsolute posixPath
| PFP.isAbsolute posixPath
= Just $ NonPortableFileName "unix" (AbsoluteFileName posixPath)
| FilePath.Windows.isAbsolute windowsPath
= Just $ NonPortableFileName "windows" (AbsoluteFileName windowsPath)
| WFP.isAbsolute windowsPath
= Just $ NonPortableFileName "windows" (AbsoluteFileName posixPath)

| any (=="..") (FilePath.Posix.splitDirectories posixPath)
| any (== [PS.pstr|..|]) (PFP.splitDirectories posixPath)
= Just $ NonPortableFileName "unix" (InvalidFileName posixPath)
| any (=="..") (FilePath.Windows.splitDirectories windowsPath)
= Just $ NonPortableFileName "windows" (InvalidFileName windowsPath)
| any (== [WS.pstr|..|]) (WFP.splitDirectories windowsPath)
= Just $ NonPortableFileName "windows" (InvalidFileName posixPath)

| otherwise = Nothing

where
posixPath = entryTarPath entry
windowsPath = fromFilePathToWindowsPath posixPath
posixPath = entryTarPath entry
(Just windowsPath) = toWindowsPath posixPath

portableFileType ftype = case ftype of
NormalFile {} -> True
Expand All @@ -264,13 +290,13 @@ checkEntryPortability entry
Directory -> True
_ -> False

portableChar c = c <= '\127'
portableChar c = PS.toChar c <= '\127'

-- | Portability problems in a tar archive
data PortabilityError
= NonPortableFormat Format
| NonPortableFileType
| NonPortableEntryNameChar FilePath
| NonPortableEntryNameChar PosixPath
| NonPortableFileName PortabilityPlatform FileNameError
deriving (Typeable)

Expand Down
Loading

0 comments on commit 6dd8c9c

Please sign in to comment.