git-annex/Utility/MagicWormhole.hs

178 lines
4.8 KiB
Haskell
Raw Normal View History

{- Magic Wormhole integration
-
- Copyright 2016 Joey Hess <id@joeyh.name>
-
- License: BSD-2-clause
-}
module Utility.MagicWormhole (
2016-12-17 22:25:33 +00:00
Code,
mkCode,
toCode,
fromCode,
2016-12-17 22:25:33 +00:00
validCode,
CodeObserver,
CodeProducer,
mkCodeObserver,
mkCodeProducer,
waitCode,
sendCode,
WormHoleParams,
appId,
2016-12-17 22:25:33 +00:00
sendFile,
receiveFile,
2016-12-18 21:01:15 +00:00
isInstalled,
2016-12-17 22:25:33 +00:00
) where
import Utility.Process
import Utility.SafeCommand
import Utility.Monad
import Utility.Misc
import Utility.Env
2016-12-18 21:01:15 +00:00
import Utility.Path
import Utility.Exception
import System.IO
import System.Exit
import Control.Concurrent
import Control.Concurrent.Async
import Data.Char
import Data.List
2016-12-30 15:10:20 +00:00
import Control.Applicative
import Prelude
-- | A Magic Wormhole code.
2016-12-17 22:25:33 +00:00
newtype Code = Code String
deriving (Eq, Show)
2016-12-17 22:25:33 +00:00
-- | Smart constructor for Code
mkCode :: String -> Maybe Code
mkCode s
| validCode s = Just (Code s)
| otherwise = Nothing
-- | Tries to fix up some common mistakes in a homan-entered code.
toCode :: String -> Maybe Code
toCode s = mkCode $ intercalate "-" $ words s
fromCode :: Code -> String
fromCode (Code s) = s
-- | Codes have the form number-word-word and may contain 2 or more words.
validCode :: String -> Bool
validCode s =
let (n, r) = separate (== '-') s
(w1, w2) = separate (== '-') r
in and
[ not (null n)
, all isDigit n
, not (null w1)
, not (null w2)
, not $ any isSpace s
]
2016-12-17 22:25:33 +00:00
newtype CodeObserver = CodeObserver (MVar Code)
2016-12-17 22:25:33 +00:00
newtype CodeProducer = CodeProducer (MVar Code)
mkCodeObserver :: IO CodeObserver
2016-12-17 22:25:33 +00:00
mkCodeObserver = CodeObserver <$> newEmptyMVar
mkCodeProducer :: IO CodeProducer
mkCodeProducer = CodeProducer <$> newEmptyMVar
waitCode :: CodeObserver -> IO Code
waitCode (CodeObserver o) = readMVar o
2016-12-17 22:25:33 +00:00
sendCode :: CodeProducer -> Code -> IO ()
sendCode (CodeProducer p) = putMVar p
type WormHoleParams = [CommandParam]
-- | An appid should be provided when using wormhole in an app, to avoid
-- using the same channel space as ad-hoc wormhole users.
appId :: String -> WormHoleParams
appId s = [Param "--appid", Param s]
2016-12-17 22:25:33 +00:00
-- | Sends a file. Once the send is underway, and the Code has been
-- generated, it will be sent to the CodeObserver. (This may not happen,
-- eg if there's a network problem).
--
-- Currently this has to parse the output of wormhole to find the code.
-- To make this as robust as possible, avoids looking for any particular
-- output strings, and only looks for the form of a wormhole code
2016-12-17 21:36:55 +00:00
-- (number-word-word).
--
-- Note that, if the filename looks like "foo 1-wormhole-code bar", when
-- that is output by wormhole, it will look like it's output a wormhole code.
--
-- A request to make the code available in machine-parsable form is here:
-- https://github.com/warner/magic-wormhole/issues/104
sendFile :: FilePath -> CodeObserver -> WormHoleParams -> IO Bool
2016-12-17 22:25:33 +00:00
sendFile f (CodeObserver observer) ps = do
-- Work around stupid stdout buffering behavior of python.
-- See https://github.com/warner/magic-wormhole/issues/108
environ <- addEntry "PYTHONUNBUFFERED" "1" <$> getEnvironment
runWormHoleProcess p { env = Just environ} $ \_hin hout herr ph -> do
(inout, inerr) <- concurrently
(findcode ph hout)
(findcode ph herr)
return (inout || inerr)
where
p = wormHoleProcess (ps ++ [Param "send", File f])
findcode ph h = hGetLineUntilExitOrEOF ph h >>= \case
Nothing -> return False
Just l -> ifM (findcode' (words l))
( drain ph h >> return True
, findcode ph h
)
findcode' [] = return False
findcode' (w:ws) = case mkCode w of
2016-12-17 22:25:33 +00:00
Just code -> do
_ <- tryPutMVar observer code
return True
Nothing -> findcode' ws
drain ph h = hGetLineUntilExitOrEOF ph h >>= \case
Just _ -> drain ph h
Nothing -> return ()
-- | Receives a file. Once the receive is under way, the Code will be
2016-12-17 22:25:33 +00:00
-- read from the CodeProducer, and fed to wormhole on stdin.
receiveFile :: FilePath -> CodeProducer -> WormHoleParams -> IO Bool
receiveFile f (CodeProducer producer) ps = runWormHoleProcess p $ \hin _hout _herr _ph -> do
Code c <- readMVar producer
2016-12-17 22:25:33 +00:00
hPutStrLn hin c
hFlush hin
return True
where
p = wormHoleProcess $ ps ++
[ Param "receive"
, Param "--accept-file"
, Param "--output-file"
, File f
]
wormHoleProcess :: WormHoleParams -> CreateProcess
wormHoleProcess = proc "wormhole" . toCommand
runWormHoleProcess :: CreateProcess -> (Handle -> Handle -> Handle -> ProcessHandle -> IO Bool) -> IO Bool
runWormHoleProcess p consumer =
withCreateProcess p' go `catchNonAsync` const (return False)
where
p' = p
{ std_in = CreatePipe
, std_out = CreatePipe
, std_err = CreatePipe
}
go (Just hin) (Just hout) (Just herr) pid =
consumer hin hout herr pid <&&> waitbool pid
go _ _ _ _ = error "internal"
waitbool pid = do
r <- waitForProcess pid
return $ case r of
ExitSuccess -> True
ExitFailure _ -> False
2016-12-18 21:01:15 +00:00
isInstalled :: IO Bool
isInstalled = inSearchPath "wormhole"