2012-11-14 23:32:27 +00:00
|
|
|
{- Credentials storage
|
|
|
|
-
|
|
|
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
2013-05-10 21:29:59 +00:00
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
|
2012-11-14 23:32:27 +00:00
|
|
|
module Creds where
|
|
|
|
|
|
|
|
import Common.Annex
|
|
|
|
import Annex.Perms
|
|
|
|
import Utility.FileMode
|
|
|
|
import Crypto
|
|
|
|
import Types.Remote (RemoteConfig, RemoteConfigKey)
|
2012-11-19 21:32:58 +00:00
|
|
|
import Remote.Helper.Encryptable (remoteCipher, embedCreds)
|
2013-09-22 18:13:31 +00:00
|
|
|
import Utility.Env (setEnv, getEnv)
|
2012-11-14 23:32:27 +00:00
|
|
|
|
|
|
|
import qualified Data.ByteString.Lazy.Char8 as L
|
|
|
|
import qualified Data.Map as M
|
|
|
|
import Utility.Base64
|
|
|
|
|
|
|
|
type Creds = String -- can be any data
|
|
|
|
type CredPair = (String, String) -- login, password
|
|
|
|
|
|
|
|
{- A CredPair can be stored in a file, or in the environment, or perhaps
|
|
|
|
- in a remote's configuration. -}
|
|
|
|
data CredPairStorage = CredPairStorage
|
|
|
|
{ credPairFile :: FilePath
|
|
|
|
, credPairEnvironment :: (String, String)
|
|
|
|
, credPairRemoteKey :: Maybe RemoteConfigKey
|
|
|
|
}
|
|
|
|
|
2012-11-19 21:32:58 +00:00
|
|
|
{- Stores creds in a remote's configuration, if the remote allows
|
|
|
|
- that. Otherwise, caches them locally. -}
|
2012-11-14 23:32:27 +00:00
|
|
|
setRemoteCredPair :: RemoteConfig -> CredPairStorage -> Annex RemoteConfig
|
2012-11-28 17:31:49 +00:00
|
|
|
setRemoteCredPair c storage = go =<< getRemoteCredPair c storage
|
2012-11-14 23:32:27 +00:00
|
|
|
where
|
2012-11-19 21:32:58 +00:00
|
|
|
go (Just creds)
|
|
|
|
| embedCreds c = case credPairRemoteKey storage of
|
|
|
|
Nothing -> localcache creds
|
|
|
|
Just key -> storeconfig creds key =<< remoteCipher c
|
|
|
|
| otherwise = localcache creds
|
2012-11-14 23:32:27 +00:00
|
|
|
go Nothing = return c
|
|
|
|
|
2012-11-19 21:32:58 +00:00
|
|
|
localcache creds = do
|
|
|
|
writeCacheCredPair creds storage
|
|
|
|
return c
|
|
|
|
|
|
|
|
storeconfig creds key (Just cipher) = do
|
2013-09-01 18:12:00 +00:00
|
|
|
s <- liftIO $ encrypt [] cipher
|
2012-11-19 21:32:58 +00:00
|
|
|
(feedBytes $ L.pack $ encodeCredPair creds)
|
|
|
|
(readBytes $ return . L.unpack)
|
|
|
|
return $ M.insert key (toB64 s) c
|
|
|
|
storeconfig creds key Nothing =
|
|
|
|
return $ M.insert key (toB64 $ encodeCredPair creds) c
|
|
|
|
|
2012-11-14 23:32:27 +00:00
|
|
|
{- Gets a remote's credpair, from the environment if set, otherwise
|
2012-11-19 21:32:58 +00:00
|
|
|
- from the cache in gitAnnexCredsDir, or failing that, from the
|
2012-11-14 23:32:27 +00:00
|
|
|
- value in RemoteConfig. -}
|
2012-11-28 17:31:49 +00:00
|
|
|
getRemoteCredPairFor :: String -> RemoteConfig -> CredPairStorage -> Annex (Maybe CredPair)
|
|
|
|
getRemoteCredPairFor this c storage = maybe missing (return . Just) =<< getRemoteCredPair c storage
|
2012-11-20 20:43:58 +00:00
|
|
|
where
|
|
|
|
(loginvar, passwordvar) = credPairEnvironment storage
|
|
|
|
missing = do
|
|
|
|
warning $ unwords
|
|
|
|
[ "Set both", loginvar
|
|
|
|
, "and", passwordvar
|
|
|
|
, "to use", this
|
|
|
|
]
|
|
|
|
return Nothing
|
|
|
|
|
2012-11-28 17:31:49 +00:00
|
|
|
getRemoteCredPair :: RemoteConfig -> CredPairStorage -> Annex (Maybe CredPair)
|
|
|
|
getRemoteCredPair c storage = maybe fromcache (return . Just) =<< fromenv
|
2012-11-14 23:32:27 +00:00
|
|
|
where
|
|
|
|
fromenv = liftIO $ getEnvCredPair storage
|
|
|
|
fromcache = maybe fromconfig (return . Just) =<< readCacheCredPair storage
|
|
|
|
fromconfig = case credPairRemoteKey storage of
|
|
|
|
Just key -> do
|
|
|
|
mcipher <- remoteCipher c
|
|
|
|
case (M.lookup key c, mcipher) of
|
2012-11-19 21:32:58 +00:00
|
|
|
(Nothing, _) -> return Nothing
|
2012-11-14 23:32:27 +00:00
|
|
|
(Just enccreds, Just cipher) -> do
|
2012-11-18 19:27:44 +00:00
|
|
|
creds <- liftIO $ decrypt cipher
|
|
|
|
(feedBytes $ L.pack $ fromB64 enccreds)
|
|
|
|
(readBytes $ return . L.unpack)
|
2012-11-19 21:32:58 +00:00
|
|
|
fromcreds creds
|
|
|
|
(Just bcreds, Nothing) ->
|
|
|
|
fromcreds $ fromB64 bcreds
|
2012-11-14 23:32:27 +00:00
|
|
|
Nothing -> return Nothing
|
2012-11-19 21:32:58 +00:00
|
|
|
fromcreds creds = case decodeCredPair creds of
|
|
|
|
Just credpair -> do
|
|
|
|
writeCacheCredPair credpair storage
|
|
|
|
return $ Just credpair
|
2013-04-03 07:52:41 +00:00
|
|
|
_ -> error "bad creds"
|
2012-11-14 23:32:27 +00:00
|
|
|
|
|
|
|
{- Gets a CredPair from the environment. -}
|
|
|
|
getEnvCredPair :: CredPairStorage -> IO (Maybe CredPair)
|
|
|
|
getEnvCredPair storage = liftM2 (,)
|
2013-09-22 18:13:31 +00:00
|
|
|
<$> getEnv uenv
|
|
|
|
<*> getEnv penv
|
2012-11-14 23:32:27 +00:00
|
|
|
where
|
|
|
|
(uenv, penv) = credPairEnvironment storage
|
|
|
|
|
|
|
|
{- Stores a CredPair in the environment. -}
|
|
|
|
setEnvCredPair :: CredPair -> CredPairStorage -> IO ()
|
2013-08-04 17:07:55 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
2012-11-14 23:32:27 +00:00
|
|
|
setEnvCredPair (l, p) storage = do
|
|
|
|
set uenv l
|
|
|
|
set penv p
|
|
|
|
where
|
|
|
|
(uenv, penv) = credPairEnvironment storage
|
2013-05-11 22:23:41 +00:00
|
|
|
set var val = void $ setEnv var val True
|
2013-05-11 20:03:00 +00:00
|
|
|
#else
|
|
|
|
setEnvCredPair _ _ = error "setEnvCredPair TODO"
|
|
|
|
#endif
|
2012-11-14 23:32:27 +00:00
|
|
|
|
|
|
|
writeCacheCredPair :: CredPair -> CredPairStorage -> Annex ()
|
|
|
|
writeCacheCredPair credpair storage =
|
|
|
|
writeCacheCreds (encodeCredPair credpair) (credPairFile storage)
|
|
|
|
|
|
|
|
{- Stores the creds in a file inside gitAnnexCredsDir that only the user
|
|
|
|
- can read. -}
|
|
|
|
writeCacheCreds :: Creds -> FilePath -> Annex ()
|
|
|
|
writeCacheCreds creds file = do
|
|
|
|
d <- fromRepo gitAnnexCredsDir
|
|
|
|
createAnnexDirectory d
|
2013-05-09 17:57:31 +00:00
|
|
|
liftIO $ writeFileProtected (d </> file) creds
|
2012-11-14 23:32:27 +00:00
|
|
|
|
|
|
|
readCacheCredPair :: CredPairStorage -> Annex (Maybe CredPair)
|
|
|
|
readCacheCredPair storage = maybe Nothing decodeCredPair
|
|
|
|
<$> readCacheCreds (credPairFile storage)
|
|
|
|
|
|
|
|
readCacheCreds :: FilePath -> Annex (Maybe Creds)
|
|
|
|
readCacheCreds file = do
|
|
|
|
d <- fromRepo gitAnnexCredsDir
|
|
|
|
let f = d </> file
|
|
|
|
liftIO $ catchMaybeIO $ readFile f
|
|
|
|
|
|
|
|
encodeCredPair :: CredPair -> Creds
|
|
|
|
encodeCredPair (l, p) = unlines [l, p]
|
|
|
|
|
|
|
|
decodeCredPair :: Creds -> Maybe CredPair
|
|
|
|
decodeCredPair creds = case lines creds of
|
|
|
|
l:p:[] -> Just (l, p)
|
|
|
|
_ -> Nothing
|