add CredPair cache
Note that this does not yet use SecureMem. It would probably make sense for the Password part of a CredPair to use SecureMem, and making that change is better than passing in a String and having it converted to SecureMem in this code.
This commit is contained in:
parent
89bd493e33
commit
ac98853f05
4 changed files with 77 additions and 1 deletions
53
Assistant/CredPairCache.hs
Normal file
53
Assistant/CredPairCache.hs
Normal file
|
@ -0,0 +1,53 @@
|
||||||
|
{- git-annex assistant CredPair cache.
|
||||||
|
-
|
||||||
|
- Copyright 2014 Joey Hess <joey@kitenet.net>
|
||||||
|
-
|
||||||
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
|
-}
|
||||||
|
|
||||||
|
{-# LANGUAGE BangPatterns #-}
|
||||||
|
|
||||||
|
module Assistant.CredPairCache (
|
||||||
|
cacheCred,
|
||||||
|
getCachedCred,
|
||||||
|
expireCachedCred,
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Assistant.Types.CredPairCache
|
||||||
|
import Types.Creds
|
||||||
|
import Assistant.Common
|
||||||
|
import Utility.ThreadScheduler
|
||||||
|
|
||||||
|
import qualified Data.Map as M
|
||||||
|
import Control.Concurrent
|
||||||
|
|
||||||
|
{- Caches a CredPair, but only for a limited time, after which it
|
||||||
|
- will expire.
|
||||||
|
-
|
||||||
|
- Note that repeatedly caching the same CredPair
|
||||||
|
- does not reset its expiry time.
|
||||||
|
-}
|
||||||
|
cacheCred :: CredPair -> Seconds -> Assistant ()
|
||||||
|
cacheCred (login, password) expireafter = do
|
||||||
|
cache <- getAssistant credPairCache
|
||||||
|
liftIO $ do
|
||||||
|
changeStrict cache $ M.insert login password
|
||||||
|
void $ forkIO $ do
|
||||||
|
threadDelaySeconds expireafter
|
||||||
|
changeStrict cache $ M.delete login
|
||||||
|
|
||||||
|
getCachedCred :: Login -> Assistant (Maybe Password)
|
||||||
|
getCachedCred login = do
|
||||||
|
cache <- getAssistant credPairCache
|
||||||
|
liftIO $ M.lookup login <$> readMVar cache
|
||||||
|
|
||||||
|
expireCachedCred :: Login -> Assistant ()
|
||||||
|
expireCachedCred login = do
|
||||||
|
cache <- getAssistant credPairCache
|
||||||
|
liftIO $ changeStrict cache $ M.delete login
|
||||||
|
|
||||||
|
{- Update map strictly to avoid keeping references to old creds in memory. -}
|
||||||
|
changeStrict :: CredPairCache -> (M.Map Login Password -> M.Map Login Password) -> IO ()
|
||||||
|
changeStrict cache a = modifyMVar_ cache $ \m -> do
|
||||||
|
let !m' = a m
|
||||||
|
return m'
|
|
@ -44,6 +44,7 @@ import Assistant.Types.Buddies
|
||||||
import Assistant.Types.NetMessager
|
import Assistant.Types.NetMessager
|
||||||
import Assistant.Types.ThreadName
|
import Assistant.Types.ThreadName
|
||||||
import Assistant.Types.RemoteControl
|
import Assistant.Types.RemoteControl
|
||||||
|
import Assistant.Types.CredPairCache
|
||||||
|
|
||||||
newtype Assistant a = Assistant { mkAssistant :: ReaderT AssistantData IO a }
|
newtype Assistant a = Assistant { mkAssistant :: ReaderT AssistantData IO a }
|
||||||
deriving (
|
deriving (
|
||||||
|
@ -70,6 +71,7 @@ data AssistantData = AssistantData
|
||||||
, buddyList :: BuddyList
|
, buddyList :: BuddyList
|
||||||
, netMessager :: NetMessager
|
, netMessager :: NetMessager
|
||||||
, remoteControl :: RemoteControl
|
, remoteControl :: RemoteControl
|
||||||
|
, credPairCache :: CredPairCache
|
||||||
}
|
}
|
||||||
|
|
||||||
newAssistantData :: ThreadState -> DaemonStatusHandle -> IO AssistantData
|
newAssistantData :: ThreadState -> DaemonStatusHandle -> IO AssistantData
|
||||||
|
@ -89,6 +91,7 @@ newAssistantData st dstatus = AssistantData
|
||||||
<*> newBuddyList
|
<*> newBuddyList
|
||||||
<*> newNetMessager
|
<*> newNetMessager
|
||||||
<*> newRemoteControl
|
<*> newRemoteControl
|
||||||
|
<*> newCredPairCache
|
||||||
|
|
||||||
runAssistant :: AssistantData -> Assistant a -> IO a
|
runAssistant :: AssistantData -> Assistant a -> IO a
|
||||||
runAssistant d a = runReaderT (mkAssistant a) d
|
runAssistant d a = runReaderT (mkAssistant a) d
|
||||||
|
|
18
Assistant/Types/CredPairCache.hs
Normal file
18
Assistant/Types/CredPairCache.hs
Normal file
|
@ -0,0 +1,18 @@
|
||||||
|
{- git-annex assistant CredPair cache.
|
||||||
|
-
|
||||||
|
- Copyright 2014 Joey Hess <joey@kitenet.net>
|
||||||
|
-
|
||||||
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
|
-}
|
||||||
|
|
||||||
|
module Assistant.Types.CredPairCache where
|
||||||
|
|
||||||
|
import Types.Creds
|
||||||
|
|
||||||
|
import Control.Concurrent
|
||||||
|
import qualified Data.Map as M
|
||||||
|
|
||||||
|
type CredPairCache = MVar (M.Map Login Password)
|
||||||
|
|
||||||
|
newCredPairCache :: IO CredPairCache
|
||||||
|
newCredPairCache = newMVar M.empty
|
|
@ -9,4 +9,6 @@ module Types.Creds where
|
||||||
|
|
||||||
type Creds = String -- can be any data that contains credentials
|
type Creds = String -- can be any data that contains credentials
|
||||||
|
|
||||||
type CredPair = (String, String) -- login, password
|
type CredPair = (Login, Password)
|
||||||
|
type Login = String
|
||||||
|
type Password = String -- todo: use securemem
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue