only run tahoe start once
This commit is contained in:
parent
aafef31ecd
commit
215ea66471
1 changed files with 49 additions and 26 deletions
|
@ -25,6 +25,7 @@ module Remote.Tahoe (remote) where
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import Data.Aeson
|
import Data.Aeson
|
||||||
import Data.ByteString.Lazy.UTF8 (fromString)
|
import Data.ByteString.Lazy.UTF8 (fromString)
|
||||||
|
import Control.Concurrent.STM
|
||||||
|
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
import Types.Remote
|
import Types.Remote
|
||||||
|
@ -39,6 +40,9 @@ import Utility.UserInfo
|
||||||
import Utility.Metered
|
import Utility.Metered
|
||||||
import Utility.Env
|
import Utility.Env
|
||||||
|
|
||||||
|
{- The TMVar is left empty until tahoe has been verified to be running. -}
|
||||||
|
data TahoeHandle = TahoeHandle TahoeConfigDir (TMVar ())
|
||||||
|
|
||||||
type TahoeConfigDir = FilePath
|
type TahoeConfigDir = FilePath
|
||||||
type SharedConvergenceSecret = String
|
type SharedConvergenceSecret = String
|
||||||
type IntroducerFurl = String
|
type IntroducerFurl = String
|
||||||
|
@ -55,16 +59,18 @@ remote = RemoteType {
|
||||||
gen :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> Annex (Maybe Remote)
|
gen :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> Annex (Maybe Remote)
|
||||||
gen r u c gc = do
|
gen r u c gc = do
|
||||||
cst <- remoteCost gc expensiveRemoteCost
|
cst <- remoteCost gc expensiveRemoteCost
|
||||||
configdir <- liftIO $ maybe (defaultTahoeConfigDir u) return (remoteAnnexTahoe gc)
|
hdl <- liftIO $ TahoeHandle
|
||||||
|
<$> maybe (defaultTahoeConfigDir u) return (remoteAnnexTahoe gc)
|
||||||
|
<*> newEmptyTMVarIO
|
||||||
return $ Just $ Remote {
|
return $ Just $ Remote {
|
||||||
uuid = u,
|
uuid = u,
|
||||||
cost = cst,
|
cost = cst,
|
||||||
name = Git.repoDescribe r,
|
name = Git.repoDescribe r,
|
||||||
storeKey = store u configdir,
|
storeKey = store u hdl,
|
||||||
retrieveKeyFile = retrieve u configdir,
|
retrieveKeyFile = retrieve u hdl,
|
||||||
retrieveKeyFileCheap = \_ _ -> return False,
|
retrieveKeyFileCheap = \_ _ -> return False,
|
||||||
removeKey = remove,
|
removeKey = remove,
|
||||||
hasKey = checkPresent u configdir,
|
hasKey = checkPresent u hdl,
|
||||||
hasKeyCheap = False,
|
hasKeyCheap = False,
|
||||||
whereisKey = Nothing,
|
whereisKey = Nothing,
|
||||||
remoteFsck = Nothing,
|
remoteFsck = Nothing,
|
||||||
|
@ -98,36 +104,31 @@ tahoeSetup mu c = do
|
||||||
furlk = "introducer-furl"
|
furlk = "introducer-furl"
|
||||||
missingfurl = error "Set TAHOE_FURL to the introducer furl to use."
|
missingfurl = error "Set TAHOE_FURL to the introducer furl to use."
|
||||||
|
|
||||||
store :: UUID -> TahoeConfigDir -> Key -> AssociatedFile -> MeterUpdate -> Annex Bool
|
store :: UUID -> TahoeHandle -> Key -> AssociatedFile -> MeterUpdate -> Annex Bool
|
||||||
store u configdir k _f _p = sendAnnex k noop $ \src -> do
|
store u hdl k _f _p = sendAnnex k noop $ \src ->
|
||||||
liftIO $ startTahoeDaemon configdir
|
parsePut <$> liftIO (readTahoe hdl "put" [File src]) >>= maybe
|
||||||
parsePut <$> liftIO (readTahoe configdir "put" [File src]) >>= maybe
|
|
||||||
(return False)
|
(return False)
|
||||||
(\cap -> storeCapability u k cap >> return True)
|
(\cap -> storeCapability u k cap >> return True)
|
||||||
|
|
||||||
retrieve :: UUID -> TahoeConfigDir -> Key -> AssociatedFile -> FilePath -> MeterUpdate -> Annex Bool
|
retrieve :: UUID -> TahoeHandle -> Key -> AssociatedFile -> FilePath -> MeterUpdate -> Annex Bool
|
||||||
retrieve u configdir k _f d _p = go =<< getCapability u k
|
retrieve u hdl k _f d _p = go =<< getCapability u k
|
||||||
where
|
where
|
||||||
go Nothing = return False
|
go Nothing = return False
|
||||||
go (Just cap) = liftIO $ do
|
go (Just cap) = liftIO $ requestTahoe hdl "get" [Param cap, File d]
|
||||||
startTahoeDaemon configdir
|
|
||||||
boolTahoe configdir "get" [Param cap, File d]
|
|
||||||
|
|
||||||
remove :: Key -> Annex Bool
|
remove :: Key -> Annex Bool
|
||||||
remove _k = do
|
remove _k = do
|
||||||
warning "content cannot be removed from tahoe remote"
|
warning "content cannot be removed from tahoe remote"
|
||||||
return False
|
return False
|
||||||
|
|
||||||
checkPresent :: UUID -> TahoeConfigDir -> Key -> Annex (Either String Bool)
|
checkPresent :: UUID -> TahoeHandle -> Key -> Annex (Either String Bool)
|
||||||
checkPresent u configdir k = go =<< getCapability u k
|
checkPresent u hdl k = go =<< getCapability u k
|
||||||
where
|
where
|
||||||
go Nothing = return (Right False)
|
go Nothing = return (Right False)
|
||||||
go (Just cap) = liftIO $ do
|
go (Just cap) = liftIO $ parseCheck <$> readTahoe hdl "check"
|
||||||
startTahoeDaemon configdir
|
[ Param "--raw"
|
||||||
parseCheck <$> readTahoe configdir "check"
|
, Param cap
|
||||||
[ Param "--raw"
|
]
|
||||||
, Param cap
|
|
||||||
]
|
|
||||||
|
|
||||||
defaultTahoeConfigDir :: UUID -> IO TahoeConfigDir
|
defaultTahoeConfigDir :: UUID -> IO TahoeConfigDir
|
||||||
defaultTahoeConfigDir u = do
|
defaultTahoeConfigDir u = do
|
||||||
|
@ -174,18 +175,40 @@ getSharedConvergenceSecret configdir = go (60 :: Int)
|
||||||
convergenceFile :: TahoeConfigDir -> FilePath
|
convergenceFile :: TahoeConfigDir -> FilePath
|
||||||
convergenceFile configdir = configdir </> "private" </> "convergence"
|
convergenceFile configdir = configdir </> "private" </> "convergence"
|
||||||
|
|
||||||
{- XXX Avoid starting tahoe if it is already running. -}
|
|
||||||
startTahoeDaemon :: TahoeConfigDir -> IO ()
|
startTahoeDaemon :: TahoeConfigDir -> IO ()
|
||||||
startTahoeDaemon configdir = void $ boolTahoe configdir "start" []
|
startTahoeDaemon configdir = void $ boolTahoe configdir "start" []
|
||||||
|
|
||||||
|
{- Ensures that tahoe has been started, before running an action
|
||||||
|
- that uses it. -}
|
||||||
|
withTahoeConfigDir :: TahoeHandle -> (TahoeConfigDir -> IO a) -> IO a
|
||||||
|
withTahoeConfigDir (TahoeHandle configdir v) a = go =<< atomically needsstart
|
||||||
|
where
|
||||||
|
go True = do
|
||||||
|
startTahoeDaemon configdir
|
||||||
|
a configdir
|
||||||
|
go False = a configdir
|
||||||
|
needsstart = ifM (isEmptyTMVar v)
|
||||||
|
( do
|
||||||
|
putTMVar v ()
|
||||||
|
return True
|
||||||
|
, return False
|
||||||
|
)
|
||||||
|
|
||||||
boolTahoe :: TahoeConfigDir -> String -> [CommandParam] -> IO Bool
|
boolTahoe :: TahoeConfigDir -> String -> [CommandParam] -> IO Bool
|
||||||
boolTahoe configdir command params = boolSystem "tahoe" $
|
boolTahoe configdir command params = boolSystem "tahoe" $
|
||||||
tahoeParams configdir command params
|
tahoeParams configdir command params
|
||||||
|
|
||||||
readTahoe :: TahoeConfigDir -> String -> [CommandParam] -> IO String
|
{- Runs a tahoe command that requests the daemon do something. -}
|
||||||
readTahoe configdir command params = catchDefaultIO "" $
|
requestTahoe :: TahoeHandle -> String -> [CommandParam] -> IO Bool
|
||||||
readProcess "tahoe" $ toCommand $
|
requestTahoe hdl command params = withTahoeConfigDir hdl $ \configdir ->
|
||||||
tahoeParams configdir command params
|
boolTahoe configdir command params
|
||||||
|
|
||||||
|
{- Runs a tahoe command that requests the daemon output something. -}
|
||||||
|
readTahoe :: TahoeHandle -> String -> [CommandParam] -> IO String
|
||||||
|
readTahoe hdl command params = withTahoeConfigDir hdl $ \configdir ->
|
||||||
|
catchDefaultIO "" $
|
||||||
|
readProcess "tahoe" $ toCommand $
|
||||||
|
tahoeParams configdir command params
|
||||||
|
|
||||||
tahoeParams :: TahoeConfigDir -> String -> [CommandParam] -> [CommandParam]
|
tahoeParams :: TahoeConfigDir -> String -> [CommandParam] -> [CommandParam]
|
||||||
tahoeParams configdir command params =
|
tahoeParams configdir command params =
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue