@@ -60,16 +60,18 @@ import Control.Monad.Trans (MonadIO(liftIO))
6060import qualified Data.ByteString.Lazy.Char8 as L
6161import qualified Data.ByteString.Char8 as S
6262import Data.Data (Data , Typeable )
63- import Data.List (sort )
63+ import Data.Foldable (toList )
64+ import Data.List (sort , isPrefixOf )
6465import Data.Maybe (fromMaybe )
6566import Data.Map (Map )
6667import qualified Data.Map as Map
67- import Filesystem.Path.CurrentOS (commonPrefix , encodeString , decodeString , collapse , append )
68+ import Data.Sequence (Seq ((:|>) , (:<|) ), (|>) , (<|) )
69+ import qualified Data.Sequence as Seq
6870import Happstack.Server.Monads (ServerMonad (askRq ), FilterMonad , WebMonad )
6971import Happstack.Server.Response (ToMessage (toResponse ), ifModifiedSince , forbidden , ok , seeOther )
7072import Happstack.Server.Types (Length (ContentLength ), Request (rqPaths , rqUri ), Response (SendFile ), RsFlags (rsfLength ), nullRsFlags , result , resultBS , setHeader )
71- import System.Directory (doesDirectoryExist , doesFileExist , getDirectoryContents , getModificationTime )
72- import System.FilePath ((</>) , addTrailingPathSeparator , hasDrive , isPathSeparator , joinPath , takeExtension , isValid )
73+ import System.Directory (doesDirectoryExist , doesFileExist , getDirectoryContents , getModificationTime , makeAbsolute )
74+ import System.FilePath ((</>) , addTrailingPathSeparator , hasDrive , isPathSeparator , joinPath , takeExtension , isValid , normalise , splitDirectories , isAbsolute )
7375import System.IO (IOMode (ReadMode ), hFileSize , hClose , openBinaryFile , withBinaryFile )
7476import System.Log.Logger (Priority (DEBUG ), logM )
7577import Text.Blaze.Html ((!) )
@@ -319,7 +321,7 @@ serveFileFrom :: (ServerMonad m, FilterMonad Response m, MonadIO m, MonadPlus m)
319321 -> FilePath -- ^ path to the file to serve
320322 -> m Response
321323serveFileFrom root mimeFn fp =
322- maybe no yes $ combineSafe root fp
324+ combineSafe root fp >>= maybe no yes
323325 where
324326 no = forbidden $ toResponse " Directory traversal forbidden"
325327 yes = serveFile mimeFn
@@ -383,15 +385,44 @@ fileServe' serveFn mimeFn indexFn localPath = do
383385-- Nothing
384386-- >>> combineSafe "/var/uploads/" "../uploads/home/../etc/passwd"
385387-- Just "/var/uploads/etc/passwd"
386- combineSafe :: FilePath -> FilePath -> Maybe FilePath
387- combineSafe root path =
388- if commonPrefix [root', joined] == root'
389- then Just $ encodeString joined
390- else Nothing
388+ combineSafe :: MonadIO m => FilePath -> FilePath -> m (Maybe FilePath )
389+ combineSafe root path = do
390+ root' <- liftIO $ makeAbsolute root
391+ let path' = normalise path
392+ pure $
393+ case combineReduce root' path' of
394+ Just combined | root' `isPrefixOf` combined ->
395+ Just combined
396+ _ ->
397+ Nothing
391398 where
392- root' = decodeString root
393- path' = decodeString path
394- joined = collapse $ append root' path'
399+ -- Combine an absolute path with another path, reducing any @..@ elements
400+ combineReduce :: FilePath -> FilePath -> Maybe FilePath
401+ combineReduce r p
402+ | isAbsolute r = Just $
403+ let splitP = splitDirectories p
404+ splitR = splitDirectories r
405+ -- Split off the head and re-add it after processing the tail with @go@
406+ headP :<| tailP = Seq. fromList splitP
407+ headR :<| tailR = Seq. fromList splitR
408+ in joinPath $ toList $
409+ -- If @p@ is absolute, then process it against the root path, dropping @r@ completely
410+ if isAbsolute p
411+ then headP <| go Seq. Empty (toList tailP)
412+ else headR <| go tailR splitP
413+ -- If the root is not absolute, it is unclear how to handle arbitrary @..@ elements in a safe way
414+ | otherwise = Nothing
415+
416+ -- | Build up a 'Seq' representation of @path@, reducing any @..@ elements
417+ -- This function assumes the 'Seq' is a split absolute path, with the beginning part removed.
418+ --
419+ -- Note that this functionality has been removed from the filepath package
420+ -- See: <https://neilmitchell.blogspot.com/2015/10/filepaths-are-subtle-symlinks-are-hard.html>
421+ go :: Seq FilePath -> [FilePath ] -> Seq FilePath
422+ go p [] = p
423+ go Seq. Empty (" .." : _ ) = Seq. Empty -- Going up beyond the top level does nothing
424+ go (s :|> _) (" .." : ps) = go s ps -- Going up a level pops an element off the right side of the Seq
425+ go s (p : ps) = go (s |> p) ps -- Just add an element to the right side of the Seq
395426
396427isSafePath :: [FilePath ] -> Bool
397428isSafePath [] = True
0 commit comments