At this point the test suite builds, and mostly the assistant is left. Sponsored-by: unqueued
		
			
				
	
	
		
			95 lines
		
	
	
	
		
			2.6 KiB
			
		
	
	
	
		
			Haskell
		
	
	
	
	
	
			
		
		
	
	
			95 lines
		
	
	
	
		
			2.6 KiB
			
		
	
	
	
		
			Haskell
		
	
	
	
	
	
{- git-annex-shell checks
 | 
						|
 -
 | 
						|
 - Copyright 2012-2024 Joey Hess <id@joeyh.name>
 | 
						|
 -
 | 
						|
 - Licensed under the GNU AGPL version 3 or higher.
 | 
						|
 -}
 | 
						|
 | 
						|
module CmdLine.GitAnnexShell.Checks where
 | 
						|
 | 
						|
import Annex.Common
 | 
						|
import Command
 | 
						|
import qualified Annex
 | 
						|
import Annex.Init
 | 
						|
import Utility.UserInfo
 | 
						|
import Utility.Env
 | 
						|
 | 
						|
limitedEnv :: String
 | 
						|
limitedEnv = "GIT_ANNEX_SHELL_LIMITED"
 | 
						|
 | 
						|
checkNotLimited :: IO ()
 | 
						|
checkNotLimited = checkEnv limitedEnv
 | 
						|
 | 
						|
readOnlyEnv :: String
 | 
						|
readOnlyEnv = "GIT_ANNEX_SHELL_READONLY"
 | 
						|
 | 
						|
checkNotReadOnly :: IO ()
 | 
						|
checkNotReadOnly = checkEnv readOnlyEnv
 | 
						|
 | 
						|
appendOnlyEnv :: String
 | 
						|
appendOnlyEnv = "GIT_ANNEX_SHELL_APPENDONLY"
 | 
						|
 | 
						|
checkNotAppendOnly :: IO ()
 | 
						|
checkNotAppendOnly = checkEnv appendOnlyEnv
 | 
						|
 | 
						|
checkEnv :: String -> IO ()
 | 
						|
checkEnv var = checkEnvSet var >>= \case
 | 
						|
	False -> noop
 | 
						|
	True -> giveup $ "Action blocked by " ++ var
 | 
						|
 | 
						|
checkEnvSet :: String -> IO Bool
 | 
						|
checkEnvSet var = getEnv var >>= return . \case
 | 
						|
	Nothing -> False
 | 
						|
	Just "" -> False
 | 
						|
	Just _ -> True
 | 
						|
 | 
						|
checkDirectory :: Maybe FilePath -> IO ()
 | 
						|
checkDirectory mdir = do
 | 
						|
	v <- getEnv "GIT_ANNEX_SHELL_DIRECTORY"
 | 
						|
	case (v, mdir) of
 | 
						|
		(Nothing, _) -> noop
 | 
						|
		(Just d, Nothing) -> req (toOsPath d) Nothing
 | 
						|
		(Just d, Just dir)
 | 
						|
			| toOsPath d `equalFilePath` toOsPath dir -> noop
 | 
						|
			| otherwise -> do
 | 
						|
				home <- myHomeDir
 | 
						|
				d' <- canondir home d
 | 
						|
				dir' <- canondir home dir
 | 
						|
				if d' `equalFilePath` dir'
 | 
						|
					then noop
 | 
						|
					else req d' (Just dir')
 | 
						|
  where
 | 
						|
	req d mdir' = giveup $ unwords 
 | 
						|
		[ "Only allowed to access"
 | 
						|
		, fromOsPath d
 | 
						|
		, maybe "and could not determine directory from command line"
 | 
						|
			(("not " ++) . fromOsPath)
 | 
						|
			mdir'
 | 
						|
		]
 | 
						|
 | 
						|
	{- A directory may start with ~/ or in some cases, even /~/,
 | 
						|
	 - or could just be relative to home, or of course could
 | 
						|
	 - be absolute. -}
 | 
						|
	canondir home d
 | 
						|
		| "~/" `isPrefixOf` d = return $ toOsPath d
 | 
						|
		| "/~/" `isPrefixOf` d = return $ toOsPath $ drop 1 d
 | 
						|
		| otherwise = relHome $ absPathFrom
 | 
						|
			(toOsPath home)
 | 
						|
			(toOsPath d)
 | 
						|
 | 
						|
{- Modifies a Command to check that it is run in either a git-annex
 | 
						|
 - repository, or a repository with a gcrypt-id set. -}
 | 
						|
gitAnnexShellCheck :: Command -> Command
 | 
						|
gitAnnexShellCheck = addCheck GitAnnexShellOk okforshell . dontCheck repoExists
 | 
						|
  where
 | 
						|
	okforshell = unlessM (isInitialized <||> isJust . gcryptId <$> Annex.getGitConfig) $
 | 
						|
		giveup "Not a git-annex or gcrypt repository."
 | 
						|
 | 
						|
{- Used for Commands that don't support proxying. -}
 | 
						|
notProxyable :: Command -> Command
 | 
						|
notProxyable c = addCheck GitAnnexShellNotProxyable checkok c
 | 
						|
  where
 | 
						|
	checkok = Annex.getState Annex.proxyremote >>= \case
 | 
						|
		Nothing -> return ()
 | 
						|
		Just _ -> giveup $ "Cannot proxy " ++ cmdname c ++ " command."
 | 
						|
 |