module Network.SSH.Client.SimpleSSH
(
SimpleSSHError(..)
, SimpleSSH
, Session
, Result(..)
, ResultExit(..)
, runSimpleSSH
, withSessionPassword
, withSessionKey
, execCommand
, sendFile
, openSession
, authenticateWithPassword
, authenticateWithKey
, closeSession
) where
import Control.Applicative
import Control.Monad.Error
import qualified Data.ByteString.Char8 as BS
import Foreign.C.String
import Foreign.Marshal.Alloc
import Foreign.Ptr
import Network.SSH.Client.SimpleSSH.Foreign
import Network.SSH.Client.SimpleSSH.Types
getValue :: CEither -> (Ptr () -> IO b) -> IO b
getValue eitherC builder = builder =<< getValueC eitherC
getError :: CEither -> IO SimpleSSHError
getError eitherC = readError <$> getErrorC eitherC
getOut :: CResult -> IO BS.ByteString
getOut ptr = BS.packCString =<< getOutC ptr
getErr :: CResult -> IO BS.ByteString
getErr ptr = BS.packCString =<< getErrC ptr
getExitCode :: CResult -> IO Integer
getExitCode ptr = toInteger <$> getExitCodeC ptr
getExitSignal :: CResult -> IO BS.ByteString
getExitSignal ptr = do
signalPtr <- getExitSignalC ptr
if signalPtr == nullPtr
then return ""
else BS.packCString signalPtr
readResult :: CResult -> IO Result
readResult resultC = Result
<$> getOut resultC
<*> getErr resultC
<*> readResultExit resultC
readResultExit :: CResult -> IO ResultExit
readResultExit resultC = do
exitCode <- getExitCode resultC
exitSignal <- getExitSignal resultC
return $ case (exitCode, exitSignal) of
(0, _) -> ExitSuccess
(_, "") -> ExitFailure exitCode
_ -> ExitSignal exitSignal
readCount :: CCount -> IO Integer
readCount countC = toInteger <$> getCountC countC
liftIOEither :: IO (Either SimpleSSHError a) -> SimpleSSH a
liftIOEither ioAction = do
eRes <- liftIO ioAction
case eRes of
Left err -> throwError err
Right res -> return res
liftEitherCFree :: (CEither -> IO ())
-> (Ptr () -> IO a)
-> IO CEither
-> IO (Either SimpleSSHError a)
liftEitherCFree customFree builder action = do
eitherC <- action
checkLeft <- isLeftC eitherC
res <- if checkLeft == 0
then Right <$> getValue eitherC builder
else Left <$> getError eitherC
customFree eitherC
return res
liftEitherC :: (Ptr () -> IO a) -> IO CEither -> IO (Either SimpleSSHError a)
liftEitherC = liftEitherCFree free
openSession :: String
-> Integer
-> String
-> SimpleSSH Session
openSession hostname port knownhostsPath = liftIOEither $ do
hostnameC <- newCString hostname
knownhostsPathC <- newCString knownhostsPath
let portC = fromInteger port
res <- liftEitherC (return . Session) $ openSessionC hostnameC portC knownhostsPathC
free hostnameC
free knownhostsPathC
return res
authenticateWithPassword :: Session
-> String
-> String
-> SimpleSSH Session
authenticateWithPassword session username password = liftIOEither $ do
usernameC <- newCString username
passwordC <- newCString password
res <- liftEitherC (return . Session) $ authenticatePasswordC session usernameC passwordC
free usernameC
free passwordC
return res
authenticateWithKey :: Session
-> String
-> FilePath
-> FilePath
-> String
-> SimpleSSH Session
authenticateWithKey session username publicKeyPath privateKeyPath passphrase = liftIOEither $ do
(usernameC, publicKeyPathC, privateKeyPathC, passphraseC) <-
(,,,) <$> newCString username
<*> newCString publicKeyPath
<*> newCString privateKeyPath
<*> newCString passphrase
res <- liftEitherC (return . Session) $ authenticateKeyC session usernameC publicKeyPathC privateKeyPathC passphraseC
mapM_ free [usernameC, publicKeyPathC, privateKeyPathC, passphraseC]
return res
execCommand :: Session
-> String
-> SimpleSSH Result
execCommand session command = do
liftIOEither $ do
commandC <- newCString command
res <- liftEitherCFree freeEitherResultC readResult $ execCommandC session commandC
free commandC
return res
sendFile :: Session
-> Integer
-> String
-> String
-> SimpleSSH Integer
sendFile session mode source target = do
liftIOEither $ do
sourceC <- newCString source
targetC <- newCString target
let modeC = fromInteger mode
res <- liftEitherCFree freeEitherCountC readCount $ sendFileC session modeC sourceC targetC
free sourceC
free targetC
return res
closeSession :: Session -> SimpleSSH ()
closeSession = lift . closeSessionC
withSessionPassword :: String
-> Integer
-> String
-> String
-> String
-> (Session -> SimpleSSH a)
-> SimpleSSH a
withSessionPassword hostname port knownhostsPath username password action = do
session <- openSession hostname port knownhostsPath
authenticatedSession <- authenticateWithPassword session username password
res <- action authenticatedSession
closeSession authenticatedSession
return res
withSessionKey :: String
-> Integer
-> String
-> String
-> String
-> String
-> String
-> (Session -> SimpleSSH a)
-> SimpleSSH a
withSessionKey hostname port knownhostsPath username publicKeyPath privateKeyPath passphrase action = do
session <- openSession hostname port knownhostsPath
authenticatedSession <- authenticateWithKey session username publicKeyPath privateKeyPath passphrase
res <- action authenticatedSession
closeSession authenticatedSession
return res