module Darcs.UI.Commands.TransferMode ( transferMode ) where
import Darcs.Prelude
import System.Directory ( withCurrentDirectory )
import Control.Exception ( catch )
import System.IO ( stdout, hFlush )
import Darcs.Util.Exception ( prettyException )
import Darcs.UI.Commands ( DarcsCommand(..), withStdOpts, nodefaults, amInRepository )
import Darcs.UI.Completion ( noArgs )
import Darcs.UI.Flags ( DarcsFlag )
import Darcs.UI.Options ( oid )
import qualified Darcs.UI.Options.All as O
import Darcs.Util.Printer ( Doc, text )
import Darcs.Util.Progress ( setProgressMode )
import Darcs.Util.Global ( darcsdir )
import Darcs.Util.Path ( AbsolutePath )
import Darcs.Util.Ssh ( transferModeHeader )
import qualified Data.ByteString as B (hPut, readFile, length, ByteString)
transferModeDescription :: String
transferModeDescription :: String
transferModeDescription = String
"Internal command for efficient ssh transfers."
transferModeHelp :: Doc
transferModeHelp :: Doc
transferModeHelp = String -> Doc
text (String -> Doc) -> String -> Doc
forall a b. (a -> b) -> a -> b
$
String
"When pulling from or pushing to a remote repository over ssh, if both\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"the local and remote ends have Darcs 2, the `transfer-mode' command\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"will be invoked on the remote end. This allows Darcs to intelligently\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"transfer information over a single ssh connection.\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"If either end runs Darcs 1, a separate ssh connection will be created\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"for each transfer. As well as being less efficient, this means users\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"who do not run ssh-agent will be prompted for the ssh password tens or\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"hundreds of times!\n"
transferMode :: DarcsCommand
transferMode :: DarcsCommand
transferMode = DarcsCommand
{ commandProgramName :: String
commandProgramName = String
"darcs"
, commandName :: String
commandName = String
"transfer-mode"
, commandHelp :: Doc
commandHelp = Doc
transferModeHelp
, commandDescription :: String
commandDescription = String
transferModeDescription
, commandExtraArgs :: Int
commandExtraArgs = Int
0
, commandExtraArgHelp :: [String]
commandExtraArgHelp = []
, commandCompleteArgs :: (AbsolutePath, AbsolutePath)
-> [DarcsFlag] -> [String] -> IO [String]
commandCompleteArgs = (AbsolutePath, AbsolutePath)
-> [DarcsFlag] -> [String] -> IO [String]
noArgs
, commandCommand :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
commandCommand = (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
transferModeCmd
, commandPrereq :: [DarcsFlag] -> IO (Either String ())
commandPrereq = [DarcsFlag] -> IO (Either String ())
amInRepository
, commandArgdefaults :: [DarcsFlag] -> AbsolutePath -> [String] -> IO [String]
commandArgdefaults = [DarcsFlag] -> AbsolutePath -> [String] -> IO [String]
nodefaults
, commandOptions :: CommandOptions
commandOptions = CommandOptions
transferModeOpts
}
where
transferModeBasicOpts :: PrimOptSpec DarcsOptDescr DarcsFlag a (Maybe String)
transferModeBasicOpts = PrimOptSpec DarcsOptDescr DarcsFlag a (Maybe String)
PrimDarcsOption (Maybe String)
O.repoDir
transferModeOpts :: CommandOptions
transferModeOpts = PrimOptSpec
DarcsOptDescr
DarcsFlag
(Maybe StdCmdAction
-> Verbosity
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
(Maybe String)
PrimDarcsOption (Maybe String)
transferModeBasicOpts PrimOptSpec
DarcsOptDescr
DarcsFlag
(Maybe StdCmdAction
-> Verbosity
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
(Maybe String)
-> DarcsOption
(UseCache
-> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
(UseCache
-> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
-> CommandOptions
forall b c.
DarcsOption (Maybe StdCmdAction -> Verbosity -> b) c
-> DarcsOption
(UseCache
-> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
b
-> CommandOptions
`withStdOpts` DarcsOption
(UseCache
-> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
(UseCache
-> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
forall (d :: * -> *) f a. OptSpec d f a a
oid
transferModeCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
transferModeCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
transferModeCmd (AbsolutePath, AbsolutePath)
_ [DarcsFlag]
_ [String]
_ = do Bool -> IO ()
setProgressMode Bool
False
String -> IO ()
putStrLn String
transferModeHeader
Handle -> IO ()
hFlush Handle
stdout
String -> IO () -> IO ()
forall a. String -> IO a -> IO a
withCurrentDirectory String
darcsdir IO ()
transfer
transfer :: IO ()
transfer :: IO ()
transfer = do Char
'g':Char
'e':Char
't':Char
' ':String
fn <- IO String
getLine
Either String ByteString
x <- String -> IO (Either String ByteString)
readfile String
fn
case Either String ByteString
x of
Right ByteString
c -> do String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"got " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fn
Int -> IO ()
forall a. Show a => a -> IO ()
print (Int -> IO ()) -> Int -> IO ()
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
c
Handle -> ByteString -> IO ()
B.hPut Handle
stdout ByteString
c
Handle -> IO ()
hFlush Handle
stdout
Left String
e -> do String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"error " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fn
String -> IO ()
forall a. Show a => a -> IO ()
print String
e
Handle -> IO ()
hFlush Handle
stdout
IO ()
transfer
readfile :: String -> IO (Either String B.ByteString)
readfile :: String -> IO (Either String ByteString)
readfile String
fn = (ByteString -> Either String ByteString
forall a b. b -> Either a b
Right (ByteString -> Either String ByteString)
-> IO ByteString -> IO (Either String ByteString)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` String -> IO ByteString
B.readFile String
fn) IO (Either String ByteString)
-> (SomeException -> IO (Either String ByteString))
-> IO (Either String ByteString)
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch` (Either String ByteString -> IO (Either String ByteString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String ByteString -> IO (Either String ByteString))
-> (SomeException -> Either String ByteString)
-> SomeException
-> IO (Either String ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Either String ByteString
forall a b. a -> Either a b
Left (String -> Either String ByteString)
-> (SomeException -> String)
-> SomeException
-> Either String ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> String
prettyException)