module Darcs.UI.Commands.TransferMode ( transferMode ) where
import Darcs.Prelude
import Control.Exception ( catch )
import System.IO ( stdout, hFlush )
import Darcs.Util.File ( withCurrentDirectory )
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, odesc, ocheck, defaultFlags )
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 = "Internal command for efficient ssh transfers."
transferModeHelp :: Doc
transferModeHelp = text $
 "When pulling from or pushing to a remote repository over ssh, if both\n" ++
 "the local and remote ends have Darcs 2, the `transfer-mode' command\n" ++
 "will be invoked on the remote end.  This allows Darcs to intelligently\n" ++
 "transfer information over a single ssh connection.\n" ++
 "\n" ++
 "If either end runs Darcs 1, a separate ssh connection will be created\n" ++
 "for each transfer.  As well as being less efficient, this means users\n" ++
 "who do not run ssh-agent will be prompted for the ssh password tens or\n" ++
 "hundreds of times!\n"
transferMode :: DarcsCommand
transferMode = DarcsCommand
    { commandProgramName = "darcs"
    , commandName = "transfer-mode"
    , commandHelp = transferModeHelp
    , commandDescription = transferModeDescription
    , commandExtraArgs = 0
    , commandExtraArgHelp = []
    , commandCompleteArgs = noArgs
    , commandCommand = transferModeCmd
    , commandPrereq = amInRepository
    , commandArgdefaults = nodefaults
    , commandAdvancedOptions = []
    , commandBasicOptions = odesc transferModeBasicOpts
    , commandDefaults = defaultFlags transferModeOpts
    , commandCheckOptions = ocheck transferModeOpts
    }
  where
    transferModeBasicOpts = O.repoDir
    transferModeOpts = transferModeBasicOpts `withStdOpts` oid
transferModeCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
transferModeCmd _ _ _ = do setProgressMode False
                           putStrLn transferModeHeader
                           hFlush stdout
                           withCurrentDirectory darcsdir transfer
transfer :: IO ()
transfer = do 'g':'e':'t':' ':fn <- getLine
              x <- readfile fn
              case x of
                Right c -> do putStrLn $ "got " ++ fn
                              print $ B.length c
                              B.hPut stdout c
                              hFlush stdout
                Left e -> do putStrLn $ "error " ++ fn
                             print e
                             hFlush stdout
              transfer
readfile :: String -> IO (Either String B.ByteString)
readfile fn = (Right `fmap` B.readFile fn) `catch` (return . Left  . prettyException)