Use USER and HOME environment when set, and only fall back to getpwent, which doesn't work with LDAP or NIS.
This commit is contained in:
parent
2018de53a3
commit
7ee0ffaeb9
13 changed files with 49 additions and 20 deletions
|
@ -9,6 +9,7 @@ module Assistant.Ssh where
|
||||||
|
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
import Utility.TempFile
|
import Utility.TempFile
|
||||||
|
import Utility.UserInfo
|
||||||
|
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
|
|
|
@ -31,6 +31,7 @@ import Remote (prettyListUUIDs)
|
||||||
import Annex.UUID
|
import Annex.UUID
|
||||||
import Types.StandardGroups
|
import Types.StandardGroups
|
||||||
import Logs.PreferredContent
|
import Logs.PreferredContent
|
||||||
|
import Utility.UserInfo
|
||||||
|
|
||||||
import Yesod
|
import Yesod
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
|
|
|
@ -26,6 +26,7 @@ import Utility.Verifiable
|
||||||
import Utility.Network
|
import Utility.Network
|
||||||
import Annex.UUID
|
import Annex.UUID
|
||||||
#endif
|
#endif
|
||||||
|
import Utility.UserInfo
|
||||||
|
|
||||||
import Yesod
|
import Yesod
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
|
@ -34,7 +35,6 @@ import qualified Data.Text as T
|
||||||
import qualified Data.Text.Encoding as T
|
import qualified Data.Text.Encoding as T
|
||||||
import qualified Data.ByteString.Lazy as B
|
import qualified Data.ByteString.Lazy as B
|
||||||
import Data.Char
|
import Data.Char
|
||||||
import System.Posix.User
|
|
||||||
import qualified Control.Exception as E
|
import qualified Control.Exception as E
|
||||||
import Control.Concurrent
|
import Control.Concurrent
|
||||||
#endif
|
#endif
|
||||||
|
@ -97,7 +97,7 @@ startPairing stage oncancel alert muuid displaysecret secret = do
|
||||||
keypair <- genSshKeyPair
|
keypair <- genSshKeyPair
|
||||||
pairdata <- PairData
|
pairdata <- PairData
|
||||||
<$> getHostname
|
<$> getHostname
|
||||||
<*> getUserName
|
<*> myUserName
|
||||||
<*> pure reldir
|
<*> pure reldir
|
||||||
<*> pure (sshPubKey keypair)
|
<*> pure (sshPubKey keypair)
|
||||||
<*> (maybe genUUID return muuid)
|
<*> (maybe genUUID return muuid)
|
||||||
|
@ -160,7 +160,7 @@ promptSecret msg cont = pairPage $ do
|
||||||
let (username, hostname) = maybe ("", "")
|
let (username, hostname) = maybe ("", "")
|
||||||
(\(_, v, a) -> (T.pack $ remoteUserName v, T.pack $ fromMaybe (showAddr a) (remoteHostName v)))
|
(\(_, v, a) -> (T.pack $ remoteUserName v, T.pack $ fromMaybe (showAddr a) (remoteHostName v)))
|
||||||
(verifiableVal . fromPairMsg <$> msg)
|
(verifiableVal . fromPairMsg <$> msg)
|
||||||
u <- T.pack <$> liftIO getUserName
|
u <- T.pack <$> liftIO myUserName
|
||||||
let sameusername = username == u
|
let sameusername = username == u
|
||||||
let authtoken = webAppFormAuthToken
|
let authtoken = webAppFormAuthToken
|
||||||
$(widgetFile "configurators/pairing/prompt")
|
$(widgetFile "configurators/pairing/prompt")
|
||||||
|
@ -177,9 +177,6 @@ secretProblem s
|
||||||
toSecret :: Text -> Secret
|
toSecret :: Text -> Secret
|
||||||
toSecret s = B.fromChunks [T.encodeUtf8 $ T.toLower $ T.filter isAlphaNum s]
|
toSecret s = B.fromChunks [T.encodeUtf8 $ T.toLower $ T.filter isAlphaNum s]
|
||||||
|
|
||||||
getUserName :: IO String
|
|
||||||
getUserName = userName <$> (getUserEntryForID =<< getEffectiveUserID)
|
|
||||||
|
|
||||||
pairPage :: Widget -> Handler RepHtml
|
pairPage :: Widget -> Handler RepHtml
|
||||||
pairPage w = bootstrap (Just Config) $ do
|
pairPage w = bootstrap (Just Config) $ do
|
||||||
sideBarDisplay
|
sideBarDisplay
|
||||||
|
|
|
@ -21,13 +21,13 @@ import Logs.Remote
|
||||||
import Remote
|
import Remote
|
||||||
import Logs.PreferredContent
|
import Logs.PreferredContent
|
||||||
import Types.StandardGroups
|
import Types.StandardGroups
|
||||||
|
import Utility.UserInfo
|
||||||
|
|
||||||
import Yesod
|
import Yesod
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import Network.Socket
|
import Network.Socket
|
||||||
import System.Posix.User
|
|
||||||
|
|
||||||
sshConfigurator :: Widget -> Handler RepHtml
|
sshConfigurator :: Widget -> Handler RepHtml
|
||||||
sshConfigurator a = bootstrap (Just Config) $ do
|
sshConfigurator a = bootstrap (Just Config) $ do
|
||||||
|
@ -96,8 +96,7 @@ usable UsableSshInput = True
|
||||||
|
|
||||||
getAddSshR :: Handler RepHtml
|
getAddSshR :: Handler RepHtml
|
||||||
getAddSshR = sshConfigurator $ do
|
getAddSshR = sshConfigurator $ do
|
||||||
u <- liftIO $ T.pack . userName
|
u <- liftIO $ T.pack <$> myUserName
|
||||||
<$> (getUserEntryForID =<< getEffectiveUserID)
|
|
||||||
((result, form), enctype) <- lift $
|
((result, form), enctype) <- lift $
|
||||||
runFormGet $ renderBootstrap $ sshInputAForm $
|
runFormGet $ renderBootstrap $ sshInputAForm $
|
||||||
SshInput Nothing (Just u) Nothing
|
SshInput Nothing (Just u) Nothing
|
||||||
|
|
|
@ -15,6 +15,7 @@ import Common
|
||||||
import Git
|
import Git
|
||||||
import Git.Types
|
import Git.Types
|
||||||
import qualified Git.Construct
|
import qualified Git.Construct
|
||||||
|
import Utility.UserInfo
|
||||||
|
|
||||||
{- Returns a single git config setting, or a default value if not set. -}
|
{- Returns a single git config setting, or a default value if not set. -}
|
||||||
get :: String -> String -> Repo -> String
|
get :: String -> String -> Repo -> String
|
||||||
|
|
|
@ -27,6 +27,7 @@ import Common
|
||||||
import Git.Types
|
import Git.Types
|
||||||
import Git
|
import Git
|
||||||
import qualified Git.Url as Url
|
import qualified Git.Url as Url
|
||||||
|
import Utility.UserInfo
|
||||||
|
|
||||||
{- Finds the git repository used for the cwd, which may be in a parent
|
{- Finds the git repository used for the cwd, which may be in a parent
|
||||||
- directory. -}
|
- directory. -}
|
||||||
|
|
8
Init.hs
8
Init.hs
|
@ -20,20 +20,16 @@ import qualified Annex.Branch
|
||||||
import Logs.UUID
|
import Logs.UUID
|
||||||
import Annex.Version
|
import Annex.Version
|
||||||
import Annex.UUID
|
import Annex.UUID
|
||||||
|
import Utility.UserInfo
|
||||||
import System.Posix.User
|
|
||||||
|
|
||||||
genDescription :: Maybe String -> Annex String
|
genDescription :: Maybe String -> Annex String
|
||||||
genDescription (Just d) = return d
|
genDescription (Just d) = return d
|
||||||
genDescription Nothing = do
|
genDescription Nothing = do
|
||||||
hostname <- maybe "" id <$> liftIO getHostname
|
hostname <- maybe "" id <$> liftIO getHostname
|
||||||
let at = if null hostname then "" else "@"
|
let at = if null hostname then "" else "@"
|
||||||
username <- clicketyclickety
|
username <- liftIO myUserName
|
||||||
reldir <- liftIO . relHome =<< fromRepo Git.repoPath
|
reldir <- liftIO . relHome =<< fromRepo Git.repoPath
|
||||||
return $ concat [username, at, hostname, ":", reldir]
|
return $ concat [username, at, hostname, ":", reldir]
|
||||||
where
|
|
||||||
clicketyclickety = liftIO $ userName <$>
|
|
||||||
(getUserEntryForID =<< getEffectiveUserID)
|
|
||||||
|
|
||||||
initialize :: Maybe String -> Annex ()
|
initialize :: Maybe String -> Annex ()
|
||||||
initialize mdescription = do
|
initialize mdescription = do
|
||||||
|
|
|
@ -26,6 +26,7 @@ import Remote.Helper.Encryptable
|
||||||
import Crypto
|
import Crypto
|
||||||
import Data.ByteString.Lazy.UTF8 (fromString)
|
import Data.ByteString.Lazy.UTF8 (fromString)
|
||||||
import Data.Digest.Pure.SHA
|
import Data.Digest.Pure.SHA
|
||||||
|
import Utility.UserInfo
|
||||||
|
|
||||||
type BupRepo = String
|
type BupRepo = String
|
||||||
|
|
||||||
|
|
|
@ -25,6 +25,7 @@ module Utility.FreeDesktop (
|
||||||
|
|
||||||
import Utility.Exception
|
import Utility.Exception
|
||||||
import Utility.Path
|
import Utility.Path
|
||||||
|
import Utility.UserInfo
|
||||||
import Utility.Process
|
import Utility.Process
|
||||||
import Utility.PartialPrelude
|
import Utility.PartialPrelude
|
||||||
|
|
||||||
|
|
|
@ -14,9 +14,9 @@ import System.Directory
|
||||||
import Data.List
|
import Data.List
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import System.Posix.User
|
|
||||||
|
|
||||||
import Utility.Monad
|
import Utility.Monad
|
||||||
|
import Utility.UserInfo
|
||||||
|
|
||||||
{- Returns the parent directory of a path. Parent of / is "" -}
|
{- Returns the parent directory of a path. Parent of / is "" -}
|
||||||
parentDir :: FilePath -> FilePath
|
parentDir :: FilePath -> FilePath
|
||||||
|
@ -128,10 +128,6 @@ preserveOrder (l:ls) new = found ++ preserveOrder ls rest
|
||||||
runPreserveOrder :: ([FilePath] -> IO [FilePath]) -> [FilePath] -> IO [FilePath]
|
runPreserveOrder :: ([FilePath] -> IO [FilePath]) -> [FilePath] -> IO [FilePath]
|
||||||
runPreserveOrder a files = preserveOrder files <$> a files
|
runPreserveOrder a files = preserveOrder files <$> a files
|
||||||
|
|
||||||
{- Current user's home directory. -}
|
|
||||||
myHomeDir :: IO FilePath
|
|
||||||
myHomeDir = homeDirectory <$> (getUserEntryForID =<< getEffectiveUserID)
|
|
||||||
|
|
||||||
{- Converts paths in the home directory to use ~/ -}
|
{- Converts paths in the home directory to use ~/ -}
|
||||||
relHome :: FilePath -> IO String
|
relHome :: FilePath -> IO String
|
||||||
relHome path = do
|
relHome path = do
|
||||||
|
|
32
Utility/UserInfo.hs
Normal file
32
Utility/UserInfo.hs
Normal file
|
@ -0,0 +1,32 @@
|
||||||
|
{- user info
|
||||||
|
-
|
||||||
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
||||||
|
-
|
||||||
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
|
-}
|
||||||
|
|
||||||
|
module Utility.UserInfo (
|
||||||
|
myHomeDir,
|
||||||
|
myUserName
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Control.Applicative
|
||||||
|
import System.Posix.User
|
||||||
|
import System.Posix.Env
|
||||||
|
|
||||||
|
{- Current user's home directory.
|
||||||
|
-
|
||||||
|
- getpwent will fail on LDAP or NIS, so use HOME if set. -}
|
||||||
|
myHomeDir :: IO FilePath
|
||||||
|
myHomeDir = myVal ["HOME"] homeDirectory
|
||||||
|
|
||||||
|
{- Current user's user name. -}
|
||||||
|
myUserName :: IO String
|
||||||
|
myUserName = myVal ["USER", "LOGNAME"] userName
|
||||||
|
|
||||||
|
myVal :: [String] -> (UserEntry -> String) -> IO String
|
||||||
|
myVal envvars extract = maybe (extract <$> getpwent) return =<< check envvars
|
||||||
|
where
|
||||||
|
check [] = return Nothing
|
||||||
|
check (v:vs) = maybe (check vs) (return . Just) =<< getEnv v
|
||||||
|
getpwent = getUserEntryForID =<< getEffectiveUserID
|
2
debian/changelog
vendored
2
debian/changelog
vendored
|
@ -24,6 +24,8 @@ git-annex (3.20121018) UNRELEASED; urgency=low
|
||||||
* configure: Check that checksum programs produce correct checksums.
|
* configure: Check that checksum programs produce correct checksums.
|
||||||
* Re-enable dbus, using a new version of the library that fixes the memory
|
* Re-enable dbus, using a new version of the library that fixes the memory
|
||||||
leak.
|
leak.
|
||||||
|
* Use USER and HOME environment when set, and only fall back to getpwent,
|
||||||
|
which doesn't work with LDAP or NIS.
|
||||||
|
|
||||||
-- Joey Hess <joeyh@debian.org> Wed, 17 Oct 2012 14:24:10 -0400
|
-- Joey Hess <joeyh@debian.org> Wed, 17 Oct 2012 14:24:10 -0400
|
||||||
|
|
||||||
|
|
|
@ -10,3 +10,4 @@ What version of git-annex are you using? On what operating system?
|
||||||
Please provide any additional information below.
|
Please provide any additional information below.
|
||||||
|
|
||||||
|
|
||||||
|
> [[fixed|done]] --[[Joey]]
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue