-- Copyright (C) 2006 Tommy Pettersson -- -- This program is free software; you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation; either version 2, or (at your option) -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program; see the file COPYING. If not, write to -- the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, -- Boston, MA 02110-1301, USA. {-# OPTIONS_GHC -cpp #-} {-# LANGUAGE CPP #-} #include "gadts.h" module Darcs.CommandsAux ( check_paths, malicious_patches, has_malicious_path, ) where import Darcs.Flags ( DarcsFlag( RestrictPaths, DontRestrictPaths ) ) import Darcs.Patch ( Patchy, list_touched_files ) import Darcs.Ordered ( FL, mapFL ) import Darcs.Sealed ( Sealed2(..), unseal2 ) import Darcs.Global ( darcsdir ) import Data.List ( intersect ) import System.FilePath ( splitDirectories ) -- * File paths {- Darcs will operate on files and directories with the invoking user's privileges. The paths for these files and directories are stored in patches, which darcs receives in various ways. Even though darcs will not create patches with "unexpected" file paths, there are no such guarantees for received patches. A spoofed patch could inflict changes on any file or directory which the invoking user is privileged to modify. There is no one single "apply" function that can check paths, so each command is responsible for not applying patches without first checking them with one of these function when appropriate. -} {- | A convenience function to call from all darcs command functions before applying any patches. It checks for malicious paths in patches, and prints an error message and fails if it finds one. -} check_paths :: Patchy p => [DarcsFlag] -> FL p C(x y) -> IO () check_paths opts patches = if check_is_on && or (mapFL has_malicious_path patches) then fail "Malicious path" -- TODO: print patch(es) and path(s) -- NOTE: should use safe Doc printer, this can be evil chars else return () where check_is_on = DontRestrictPaths `notElem` opts || RestrictPaths `elem` opts -- | Filter out patches that contains some malicious file path malicious_patches :: Patchy p => [Sealed2 p] -> [Sealed2 p] malicious_patches to_check = filter (unseal2 has_malicious_path) to_check has_malicious_path :: Patchy p => p C(x y) -> Bool has_malicious_path patch = let paths = list_touched_files patch in any is_malicious_path paths {-| What is a malicious path? A spoofed path is a malicious path. 1. Darcs only creates explicitly relative paths (beginning with @\".\/\"@), so any not explicitly relative path is surely spoofed. 2. Darcs normalizes paths so they never contain @\"\/..\/\"@, so paths with @\"\/..\/\"@ are surely spoofed. A path to a darcs repository's meta data can modify \"trusted\" patches or change safety defaults in that repository, so we check for paths containing @\"\/_darcs\/\"@ which is the entry to darcs meta data. To do? * How about get repositories? * Would it be worth adding a --semi-safe-paths option for allowing changes to certain preference files (_darcs\/prefs\/) in sub repositories'? -} is_malicious_path :: String -> Bool is_malicious_path fp = not (is_explicitly_relative fp) || splitDirectories fp `contains_any` [ "..", darcsdir ] where contains_any a b = not . null $ intersect a b is_explicitly_relative :: String -> Bool is_explicitly_relative ('.':'/':_) = True -- begins with "./" is_explicitly_relative _ = False