--  Copyright (C) 2008 David Roundy
--
--  This program is free software; you can redistribute it and/or modify
--  it under the terms of the GNU General Public License as published by
--  the Free Software Foundation; either version 2, or (at your option)
--  any later version.
--
--  This program is distributed in the hope that it will be useful,
--  but WITHOUT ANY WARRANTY; without even the implied warranty of
--  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
--  GNU General Public License for more details.
--
--  You should have received a copy of the GNU General Public License
--  along with this program; see the file COPYING.  If not, write to
--  the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor,
--  Boston, MA 02110-1301, USA.

-- The pragma above is only for pattern guards.
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 :: 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 :: String
-> String
-> Doc
-> String
-> Int
-> [String]
-> ((AbsolutePath, AbsolutePath)
    -> [DarcsFlag] -> [String] -> IO ())
-> ([DarcsFlag] -> IO (Either String ()))
-> ((AbsolutePath, AbsolutePath)
    -> [DarcsFlag] -> [String] -> IO [String])
-> ([DarcsFlag] -> AbsolutePath -> [String] -> IO [String])
-> [DarcsOptDescr DarcsFlag]
-> [DarcsOptDescr DarcsFlag]
-> [DarcsFlag]
-> ([DarcsFlag] -> [String])
-> DarcsCommand
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
    , commandAdvancedOptions :: [DarcsOptDescr DarcsFlag]
commandAdvancedOptions = []
    , commandBasicOptions :: [DarcsOptDescr DarcsFlag]
commandBasicOptions = OptSpec DarcsOptDescr DarcsFlag Any (Maybe String -> Any)
-> [DarcsOptDescr DarcsFlag]
forall (d :: * -> *) f a b. OptSpec d f a b -> [d f]
odesc OptSpec DarcsOptDescr DarcsFlag Any (Maybe String -> Any)
forall a. PrimOptSpec DarcsOptDescr DarcsFlag a (Maybe String)
transferModeBasicOpts
    , commandDefaults :: [DarcsFlag]
commandDefaults = OptSpec
  DarcsOptDescr
  DarcsFlag
  [DarcsFlag]
  (Maybe String
   -> Maybe StdCmdAction
   -> Verbosity
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> [DarcsFlag])
-> [DarcsFlag]
forall (d :: * -> *) f b. OptSpec d f [f] b -> [f]
defaultFlags OptSpec
  DarcsOptDescr
  DarcsFlag
  [DarcsFlag]
  (Maybe String
   -> Maybe StdCmdAction
   -> Verbosity
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> [DarcsFlag])
forall a.
DarcsOption
  a
  (Maybe String
   -> Maybe StdCmdAction
   -> Verbosity
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
transferModeOpts
    , commandCheckOptions :: [DarcsFlag] -> [String]
commandCheckOptions = OptSpec
  DarcsOptDescr
  DarcsFlag
  Any
  (Maybe String
   -> Maybe StdCmdAction
   -> Verbosity
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> Any)
-> [DarcsFlag] -> [String]
forall (d :: * -> *) f a b. OptSpec d f a b -> [f] -> [String]
ocheck OptSpec
  DarcsOptDescr
  DarcsFlag
  Any
  (Maybe String
   -> Maybe StdCmdAction
   -> Verbosity
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> Any)
forall a.
DarcsOption
  a
  (Maybe String
   -> Maybe StdCmdAction
   -> Verbosity
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
transferModeOpts
    }
  where
    transferModeBasicOpts :: PrimOptSpec DarcsOptDescr DarcsFlag a (Maybe String)
transferModeBasicOpts = PrimOptSpec DarcsOptDescr DarcsFlag a (Maybe String)
forall a. PrimOptSpec DarcsOptDescr DarcsFlag a (Maybe String)
O.repoDir
    transferModeOpts :: DarcsOption
  a
  (Maybe String
   -> Maybe StdCmdAction
   -> Verbosity
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
transferModeOpts = PrimOptSpec
  DarcsOptDescr
  DarcsFlag
  (Maybe StdCmdAction
   -> Verbosity
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
  (Maybe String)
forall a. PrimOptSpec DarcsOptDescr DarcsFlag a (Maybe String)
transferModeBasicOpts PrimOptSpec
  DarcsOptDescr
  DarcsFlag
  (Maybe StdCmdAction
   -> Verbosity
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
  (Maybe String)
-> DarcsOption
     (UseCache -> HooksConfig -> Bool -> Bool -> Bool -> a)
     (UseCache -> HooksConfig -> Bool -> Bool -> Bool -> a)
-> DarcsOption
     a
     (Maybe String
      -> Maybe StdCmdAction
      -> Verbosity
      -> UseCache
      -> HooksConfig
      -> Bool
      -> Bool
      -> Bool
      -> a)
forall b c a.
DarcsOption (Maybe StdCmdAction -> Verbosity -> b) c
-> DarcsOption
     (UseCache -> HooksConfig -> Bool -> Bool -> Bool -> a) b
-> DarcsOption a c
`withStdOpts` DarcsOption
  (UseCache -> HooksConfig -> Bool -> Bool -> Bool -> a)
  (UseCache -> HooksConfig -> Bool -> Bool -> Bool -> a)
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 p a. FilePathLike p => p -> 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 (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 (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)