summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Assistant/Ssh.hs1
-rw-r--r--Git/Config.hs1
-rw-r--r--Git/Construct.hs1
-rw-r--r--Init.hs8
-rw-r--r--Remote/Bup.hs1
-rw-r--r--Utility/FreeDesktop.hs1
-rw-r--r--Utility/Path.hs6
-rw-r--r--Utility/UserInfo.hs32
-rw-r--r--debian/changelog2
-rw-r--r--doc/bugs/git-annex:_getUserEntryForID:_failed___40__Success__41__.mdwn1
10 files changed, 43 insertions, 11 deletions
diff --git a/Assistant/Ssh.hs b/Assistant/Ssh.hs
index 0d3ebcfac..de7665dad 100644
--- a/Assistant/Ssh.hs
+++ b/Assistant/Ssh.hs
@@ -9,6 +9,7 @@ module Assistant.Ssh where
import Common.Annex
import Utility.TempFile
+import Utility.UserInfo
import Data.Text (Text)
import qualified Data.Text as T
diff --git a/Git/Config.hs b/Git/Config.hs
index cc9b27b69..0d6d67fc0 100644
--- a/Git/Config.hs
+++ b/Git/Config.hs
@@ -15,6 +15,7 @@ import Common
import Git
import Git.Types
import qualified Git.Construct
+import Utility.UserInfo
{- Returns a single git config setting, or a default value if not set. -}
get :: String -> String -> Repo -> String
diff --git a/Git/Construct.hs b/Git/Construct.hs
index 3d39b0801..663303c15 100644
--- a/Git/Construct.hs
+++ b/Git/Construct.hs
@@ -27,6 +27,7 @@ import Common
import Git.Types
import Git
import qualified Git.Url as Url
+import Utility.UserInfo
{- Finds the git repository used for the cwd, which may be in a parent
- directory. -}
diff --git a/Init.hs b/Init.hs
index aae10160d..0b3605e41 100644
--- a/Init.hs
+++ b/Init.hs
@@ -20,20 +20,16 @@ import qualified Annex.Branch
import Logs.UUID
import Annex.Version
import Annex.UUID
-
-import System.Posix.User
+import Utility.UserInfo
genDescription :: Maybe String -> Annex String
genDescription (Just d) = return d
genDescription Nothing = do
hostname <- maybe "" id <$> liftIO getHostname
let at = if null hostname then "" else "@"
- username <- clicketyclickety
+ username <- liftIO myUserName
reldir <- liftIO . relHome =<< fromRepo Git.repoPath
return $ concat [username, at, hostname, ":", reldir]
- where
- clicketyclickety = liftIO $ userName <$>
- (getUserEntryForID =<< getEffectiveUserID)
initialize :: Maybe String -> Annex ()
initialize mdescription = do
diff --git a/Remote/Bup.hs b/Remote/Bup.hs
index 916095cc9..375c5c352 100644
--- a/Remote/Bup.hs
+++ b/Remote/Bup.hs
@@ -26,6 +26,7 @@ import Remote.Helper.Encryptable
import Crypto
import Data.ByteString.Lazy.UTF8 (fromString)
import Data.Digest.Pure.SHA
+import Utility.UserInfo
type BupRepo = String
diff --git a/Utility/FreeDesktop.hs b/Utility/FreeDesktop.hs
index 0845f3329..7aba1f272 100644
--- a/Utility/FreeDesktop.hs
+++ b/Utility/FreeDesktop.hs
@@ -25,6 +25,7 @@ module Utility.FreeDesktop (
import Utility.Exception
import Utility.Path
+import Utility.UserInfo
import Utility.Process
import Utility.PartialPrelude
diff --git a/Utility/Path.hs b/Utility/Path.hs
index 209ff1b0f..f4c2843fc 100644
--- a/Utility/Path.hs
+++ b/Utility/Path.hs
@@ -14,9 +14,9 @@ import System.Directory
import Data.List
import Data.Maybe
import Control.Applicative
-import System.Posix.User
import Utility.Monad
+import Utility.UserInfo
{- Returns the parent directory of a path. Parent of / is "" -}
parentDir :: FilePath -> FilePath
@@ -128,10 +128,6 @@ preserveOrder (l:ls) new = found ++ preserveOrder ls rest
runPreserveOrder :: ([FilePath] -> IO [FilePath]) -> [FilePath] -> IO [FilePath]
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 ~/ -}
relHome :: FilePath -> IO String
relHome path = do
diff --git a/Utility/UserInfo.hs b/Utility/UserInfo.hs
new file mode 100644
index 000000000..6e757548a
--- /dev/null
+++ b/Utility/UserInfo.hs
@@ -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
diff --git a/debian/changelog b/debian/changelog
index 2278195c2..aa3eb9db5 100644
--- a/debian/changelog
+++ b/debian/changelog
@@ -24,6 +24,8 @@ git-annex (3.20121018) UNRELEASED; urgency=low
* configure: Check that checksum programs produce correct checksums.
* Re-enable dbus, using a new version of the library that fixes the memory
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
diff --git a/doc/bugs/git-annex:_getUserEntryForID:_failed___40__Success__41__.mdwn b/doc/bugs/git-annex:_getUserEntryForID:_failed___40__Success__41__.mdwn
index a929048f6..976109c79 100644
--- a/doc/bugs/git-annex:_getUserEntryForID:_failed___40__Success__41__.mdwn
+++ b/doc/bugs/git-annex:_getUserEntryForID:_failed___40__Success__41__.mdwn
@@ -10,3 +10,4 @@ What version of git-annex are you using? On what operating system?
Please provide any additional information below.
+> [[fixed|done]] --[[Joey]]