1+ {-# LANGUAGE CPP #-}
12{-# LANGUAGE ScopedTypeVariables #-}
23{-# LANGUAGE GeneralizedNewtypeDeriving #-}
34{-# LANGUAGE TemplateHaskell #-}
@@ -30,6 +31,8 @@ module Stack.Config
3031 ,getIsGMP4
3132 ,getSnapshots
3233 ,makeConcreteResolver
34+ ,checkOwnership
35+ ,getInContainer
3336 ) where
3437
3538import qualified Codec.Archive.Tar as Tar
@@ -40,6 +43,7 @@ import Control.Arrow ((***))
4043import Control.Exception (assert )
4144import Control.Monad (liftM , unless , when , filterM )
4245import Control.Monad.Catch (MonadThrow , MonadCatch , catchAll , throwM )
46+ import Control.Monad.Extra (firstJustM )
4347import Control.Monad.IO.Class
4448import Control.Monad.Logger hiding (Loc )
4549import Control.Monad.Reader (MonadReader , ask , asks , runReaderT )
@@ -49,6 +53,7 @@ import Data.Aeson.Extended
4953import qualified Data.ByteString as S
5054import qualified Data.ByteString.Base16 as B16
5155import qualified Data.ByteString.Lazy as L
56+ import Data.Foldable (forM_ )
5257import qualified Data.IntMap as IntMap
5358import qualified Data.Map as Map
5459import Data.Maybe
@@ -66,6 +71,7 @@ import Network.HTTP.Download (download, downloadJSON)
6671import Options.Applicative (Parser , strOption , long , help )
6772import Path
6873import Path.Extra (toFilePathNoTrailingSep )
74+ import Path.Find (findInParents )
6975import Path.IO
7076import qualified Paths_stack as Meta
7177import Safe (headMay )
@@ -77,9 +83,10 @@ import qualified Stack.Image as Image
7783import Stack.PackageIndex
7884import Stack.Types
7985import Stack.Types.Internal
80- import qualified System.Directory as D
8186import System.Environment
8287import System.IO
88+ import System.PosixCompat.Files (fileOwner , getFileStatus )
89+ import System.PosixCompat.User (getEffectiveUserID )
8390import System.Process.Read
8491
8592-- | If deprecated path exists, use it and print a warning.
@@ -289,6 +296,11 @@ configFromConfigMonoid configStackRoot configUserConfigPath mresolver mproject c
289296 configAllowNewer = fromMaybe False configMonoidAllowNewer
290297 configDefaultTemplate = configMonoidDefaultTemplate
291298
299+ configAllowDifferentUser <-
300+ case configMonoidAllowDifferentUser of
301+ Just True -> return True
302+ _ -> getInContainer
303+
292304 return Config {.. }
293305
294306-- | Get the default 'GHCVariant'. On older Linux systems with libgmp4, returns 'GHCGMP4'.
@@ -365,7 +377,7 @@ loadConfig :: (MonadLogger m,MonadIO m,MonadCatch m,MonadThrow m,MonadBaseContro
365377 -- ^ Override resolver
366378 -> m (LoadConfig m )
367379loadConfig configArgs mstackYaml mresolver = do
368- stackRoot <- determineStackRoot
380+ ( stackRoot, userOwnsStackRoot) <- determineStackRootAndOwnership
369381 userConfigPath <- getDefaultUserConfigPath stackRoot
370382 extraConfigs0 <- getExtraConfigs userConfigPath >>= mapM loadYaml
371383 let extraConfigs =
@@ -387,10 +399,18 @@ loadConfig configArgs mstackYaml mresolver = do
387399 Just (_, _, projectConfig) -> configArgs : projectConfig : extraConfigs
388400 unless (fromCabalVersion Meta. version `withinRange` configRequireStackVersion config)
389401 (throwM (BadStackVersionException (configRequireStackVersion config)))
402+
403+ let mprojectRoot = fmap (\ (_, fp, _) -> parent fp) mproject
404+ unless (configAllowDifferentUser config) $ do
405+ unless userOwnsStackRoot $
406+ throwM (UserDoesn'tOwnDirectory stackRoot)
407+ forM_ mprojectRoot $ \ dir ->
408+ checkOwnership (dir </> configWorkDir config)
409+
390410 return LoadConfig
391411 { lcConfig = config
392412 , lcLoadBuildConfig = loadBuildConfig mproject config mresolver
393- , lcProjectRoot = fmap ( \ (_, fp, _) -> parent fp) mproject
413+ , lcProjectRoot = mprojectRoot
394414 }
395415
396416-- | Load the build configuration, adds build-specific values to config loaded by @loadConfig@.
@@ -611,15 +631,83 @@ resolvePackageLocation menv projRoot (PLRemote url remotePackageType) = do
611631 throwM $ UnexpectedArchiveContents dirs files
612632 _ -> return dir
613633
614- -- | Get the stack root, e.g. ~/.stack
615- determineStackRoot :: (MonadIO m , MonadThrow m ) => m (Path Abs Dir )
616- determineStackRoot = do
617- env <- liftIO getEnvironment
618- case lookup stackRootEnvVar env of
619- Nothing -> getAppUserDataDir $ (mkRelDir stackProgName)
620- Just x -> do
621- liftIO $ D. createDirectoryIfMissing True x
622- resolveDir' x
634+ -- | Get the stack root, e.g. @~/.stack@, and determine whether the user owns it.
635+ --
636+ -- On Windows, the second value is always 'True'.
637+ determineStackRootAndOwnership
638+ :: (MonadIO m , MonadCatch m )
639+ => m (Path Abs Dir , Bool )
640+ determineStackRootAndOwnership = do
641+ stackRoot <- do
642+ mstackRoot <- liftIO $ lookupEnv stackRootEnvVar
643+ case mstackRoot of
644+ Nothing -> getAppUserDataDir $ (mkRelDir stackProgName)
645+ Just x -> parseAbsDir x
646+
647+ (existingStackRootOrParentDir, userOwnsIt) <- do
648+ mdirAndOwnership <- findInParents getDirAndOwnership stackRoot
649+ case mdirAndOwnership of
650+ Just x -> return x
651+ Nothing -> throwM (BadStackRootEnvVar stackRoot)
652+
653+ when (existingStackRootOrParentDir /= stackRoot) $
654+ if userOwnsIt
655+ then liftIO $ ensureDir stackRoot
656+ else throwM $
657+ Won'tCreateStackRootInDirectoryOwnedByDifferentUser
658+ stackRoot
659+ existingStackRootOrParentDir
660+
661+ stackRoot' <- canonicalizePath stackRoot
662+ return (stackRoot', userOwnsIt)
663+
664+ -- | @'checkOwnership' dir@ throws 'UserDoesn'tOwnDirectory' if @dir@
665+ -- isn't owned by the current user.
666+ --
667+ -- If @dir@ doesn't exist, its parent directory is checked instead.
668+ -- If the parent directory doesn't exist either, @'NoSuchDirectory' ('parent' dir)@
669+ -- is thrown.
670+ checkOwnership :: (MonadIO m , MonadCatch m ) => Path Abs Dir -> m ()
671+ checkOwnership dir = do
672+ mdirAndOwnership <- firstJustM getDirAndOwnership [dir, parent dir]
673+ case mdirAndOwnership of
674+ Just (_, True ) -> return ()
675+ Just (dir', False ) -> throwM (UserDoesn'tOwnDirectory dir')
676+ Nothing ->
677+ (throwM . NoSuchDirectory ) $ (toFilePathNoTrailingSep . parent) dir
678+
679+ -- | @'getDirAndOwnership' dir@ returns @'Just' (dir, 'True')@ when @dir@
680+ -- exists and the current user owns it in the sense of 'isOwnedByUser'.
681+ getDirAndOwnership
682+ :: (MonadIO m , MonadCatch m )
683+ => Path Abs Dir
684+ -> m (Maybe (Path Abs Dir , Bool ))
685+ getDirAndOwnership dir = forgivingAbsence $ do
686+ ownership <- isOwnedByUser dir
687+ return (dir, ownership)
688+
689+ -- | Check whether the current user (determined with 'getEffectiveUserId') is
690+ -- the owner for the given path.
691+ --
692+ -- Will always return 'True' on Windows.
693+ isOwnedByUser :: MonadIO m => Path Abs t -> m Bool
694+ isOwnedByUser path = liftIO $ do
695+ if osIsWindows
696+ then return True
697+ else do
698+ fileStatus <- getFileStatus (toFilePath path)
699+ user <- getEffectiveUserID
700+ return (user == fileOwner fileStatus)
701+ where
702+ #ifdef WINDOWS
703+ osIsWindows = True
704+ #else
705+ osIsWindows = False
706+ #endif
707+
708+ -- | 'True' if we are currently running inside a Docker container.
709+ getInContainer :: (MonadIO m ) => m Bool
710+ getInContainer = liftIO (isJust <$> lookupEnv inContainerEnvVar)
623711
624712-- | Determine the extra config file locations which exist.
625713--
@@ -665,21 +753,16 @@ getProjectConfig Nothing = do
665753 liftM Just $ resolveFile' fp
666754 Nothing -> do
667755 currDir <- getCurrentDir
668- search currDir
756+ findInParents getStackDotYaml currDir
669757 where
670- search dir = do
758+ getStackDotYaml dir = do
671759 let fp = dir </> stackDotYaml
672760 fp' = toFilePath fp
673761 $ logDebug $ " Checking for project config at: " <> T. pack fp'
674762 exists <- doesFileExist fp
675763 if exists
676764 then return $ Just fp
677- else do
678- let dir' = parent dir
679- if dir == dir'
680- -- fully traversed, give up
681- then return Nothing
682- else search dir'
765+ else return Nothing
683766
684767-- | Find the project config file location, respecting environment variables
685768-- and otherwise traversing parents. If no config is found, we supply a default
0 commit comments