Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Session
- data Channel
- data KnownHosts
- data Sftp
- data SftpHandle
- data SftpAttributes
- type SftpList = [(ByteString, SftpAttributes)]
- data SftpFileTransferFlags
- withSSH2 :: FilePath -> FilePath -> FilePath -> String -> String -> String -> Int -> (Session -> IO a) -> IO a
- withSSH2User :: FilePath -> String -> String -> String -> Int -> (Session -> IO a) -> IO a
- withSSH2Agent :: String -> String -> String -> Int -> (Session -> IO a) -> IO a
- withSession :: String -> Int -> (Session -> IO a) -> IO a
- withChannel :: Session -> (Channel -> IO a) -> IO (Int, a)
- withChannelBy :: IO a -> (a -> Channel) -> (a -> IO b) -> IO (Int, b)
- checkHost :: Session -> String -> Int -> FilePath -> [KnownHostType] -> IO KnownHostResult
- readAllChannel :: Channel -> IO ByteString
- writeAllChannel :: Channel -> ByteString -> IO ()
- scpSendFile :: Session -> Int -> FilePath -> FilePath -> IO Integer
- scpReceiveFile :: Session -> FilePath -> FilePath -> IO Integer
- runShellCommands :: Session -> [String] -> IO (Int, [ByteString])
- execCommands :: Session -> [String] -> IO (Int, [ByteString])
- directTcpIpEx :: Session -> String -> Int -> String -> Int -> IO Channel
- withSFTP :: FilePath -> FilePath -> FilePath -> String -> String -> String -> Int -> (Sftp -> IO a) -> IO a
- withSFTPUser :: FilePath -> String -> String -> String -> Int -> (Sftp -> IO a) -> IO a
- withSftpSession :: Session -> (Sftp -> IO a) -> IO a
- sftpListDir :: Sftp -> FilePath -> IO SftpList
- sftpRenameFile :: Sftp -> FilePath -> FilePath -> IO ()
- sftpSendFile :: Sftp -> FilePath -> FilePath -> Int -> IO Integer
- sftpSendFromHandle :: Sftp -> Handle -> FilePath -> Int -> IO Integer
- sftpSendBytes :: Sftp -> ByteString -> FilePath -> Int -> IO Integer
- sftpReceiveFile :: Sftp -> FilePath -> FilePath -> IO Integer
- sftpReadFileToHandler :: SftpHandle -> Handle -> Int -> IO Int
- sftpFstat :: SftpHandle -> IO SftpAttributes
- sftpDeleteFile :: Sftp -> FilePath -> IO ()
- socketConnect :: String -> Int -> IO Socket
- sessionInit :: String -> Int -> IO Session
- sessionClose :: Session -> IO ()
Types
Instances
Data Session Source # | |
Defined in Network.SSH.Client.LibSSH2.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Session -> c Session # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Session # toConstr :: Session -> Constr # dataTypeOf :: Session -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Session) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Session) # gmapT :: (forall b. Data b => b -> b) -> Session -> Session # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Session -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Session -> r # gmapQ :: (forall d. Data d => d -> u) -> Session -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Session -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Session -> m Session # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Session -> m Session # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Session -> m Session # | |
Show Session Source # | |
Eq Session Source # | |
ToPointer Session Source # | |
Instances
Data Channel Source # | |
Defined in Network.SSH.Client.LibSSH2.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Channel -> c Channel # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Channel # toConstr :: Channel -> Constr # dataTypeOf :: Channel -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Channel) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Channel) # gmapT :: (forall b. Data b => b -> b) -> Channel -> Channel # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Channel -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Channel -> r # gmapQ :: (forall d. Data d => d -> u) -> Channel -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Channel -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Channel -> m Channel # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Channel -> m Channel # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Channel -> m Channel # | |
Show Channel Source # | |
Eq Channel Source # | |
ToPointer Channel Source # | |
data KnownHosts Source #
Instances
Data KnownHosts Source # | |
Defined in Network.SSH.Client.LibSSH2.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> KnownHosts -> c KnownHosts # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c KnownHosts # toConstr :: KnownHosts -> Constr # dataTypeOf :: KnownHosts -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c KnownHosts) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KnownHosts) # gmapT :: (forall b. Data b => b -> b) -> KnownHosts -> KnownHosts # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KnownHosts -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KnownHosts -> r # gmapQ :: (forall d. Data d => d -> u) -> KnownHosts -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> KnownHosts -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> KnownHosts -> m KnownHosts # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KnownHosts -> m KnownHosts # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KnownHosts -> m KnownHosts # | |
Show KnownHosts Source # | |
Defined in Network.SSH.Client.LibSSH2.Types showsPrec :: Int -> KnownHosts -> ShowS # show :: KnownHosts -> String # showList :: [KnownHosts] -> ShowS # | |
Eq KnownHosts Source # | |
Defined in Network.SSH.Client.LibSSH2.Types (==) :: KnownHosts -> KnownHosts -> Bool # (/=) :: KnownHosts -> KnownHosts -> Bool # | |
ToPointer KnownHosts Source # | |
Defined in Network.SSH.Client.LibSSH2.Types toPointer :: KnownHosts -> Ptr () Source # |
data SftpHandle Source #
Instances
Show SftpHandle Source # | |
Defined in Network.SSH.Client.LibSSH2.Types showsPrec :: Int -> SftpHandle -> ShowS # show :: SftpHandle -> String # showList :: [SftpHandle] -> ShowS # | |
ToPointer SftpHandle Source # | |
Defined in Network.SSH.Client.LibSSH2.Types toPointer :: SftpHandle -> Ptr () Source # |
data SftpAttributes Source #
Instances
Show SftpAttributes Source # | |
Defined in Network.SSH.Client.LibSSH2.Foreign showsPrec :: Int -> SftpAttributes -> ShowS # show :: SftpAttributes -> String # showList :: [SftpAttributes] -> ShowS # | |
Eq SftpAttributes Source # | |
Defined in Network.SSH.Client.LibSSH2.Foreign (==) :: SftpAttributes -> SftpAttributes -> Bool # (/=) :: SftpAttributes -> SftpAttributes -> Bool # |
type SftpList = [(ByteString, SftpAttributes)] Source #
data SftpFileTransferFlags Source #
Sftp support
Instances
Show SftpFileTransferFlags Source # | |
Defined in Network.SSH.Client.LibSSH2.Foreign showsPrec :: Int -> SftpFileTransferFlags -> ShowS # show :: SftpFileTransferFlags -> String # showList :: [SftpFileTransferFlags] -> ShowS # | |
Eq SftpFileTransferFlags Source # | |
Defined in Network.SSH.Client.LibSSH2.Foreign (==) :: SftpFileTransferFlags -> SftpFileTransferFlags -> Bool # (/=) :: SftpFileTransferFlags -> SftpFileTransferFlags -> Bool # |
Functions
:: FilePath | Path to known_hosts file |
-> FilePath | Path to public key file |
-> FilePath | Path to private key file |
-> String | Passphrase |
-> String | Remote user name |
-> String | Remote host name |
-> Int | Remote port number (usually 22) |
-> (Session -> IO a) | Actions to perform on session |
-> IO a |
Execute some actions within SSH2 connection. Uses public key authentication.
:: FilePath | Path to known_hosts file |
-> String | Remote user name |
-> String | Remote password |
-> String | Remote host name |
-> Int | Remote port number (usually 22) |
-> (Session -> IO a) | Actions to perform on session |
-> IO a |
Execute some actions within SSH2 connection. Uses username/password authentication.
:: String | Path to known_hosts file |
-> String | Remote user name |
-> String | Remote host name |
-> Int | Remote port number (usually 22) |
-> (Session -> IO a) | Actions to perform on session |
-> IO a |
Execute some actions within SSH2 connection. Uses agent based public key authentication.
:: String | Remote host name |
-> Int | Remote port number (usually 22) |
-> (Session -> IO a) | Actions to perform on handle and session |
-> IO a |
Execute some actions within SSH2 session
withChannel :: Session -> (Channel -> IO a) -> IO (Int, a) Source #
Execute some actions withing SSH2 channel
:: IO a | Create a channel (and possibly other stuff) |
-> (a -> Channel) | Extract the channel from "other stuff" |
-> (a -> IO b) | Actions to execute on the channel |
-> IO (Int, b) | Channel exit status and return value |
Generalization of withChannel
:: Session | |
-> String | Remote host name |
-> Int | Remote port number (usually 22) |
-> FilePath | Path to known_hosts file |
-> [KnownHostType] | Flags specifying what format the host name is, what format the key is and what key type it is |
-> IO KnownHostResult |
readAllChannel :: Channel -> IO ByteString Source #
Read all data from the channel
Although this function returns a lazy bytestring, the data is not read lazily.
writeAllChannel :: Channel -> ByteString -> IO () Source #
Write a lazy bytestring to the channel
:: Session | |
-> Int | File creation mode (0o777, for example) |
-> FilePath | Path to local file |
-> FilePath | Remote file path |
-> IO Integer |
Send a file to remote host via SCP. Returns size of sent data.
Receive file from remote host via SCP. Returns size of received data.
runShellCommands :: Session -> [String] -> IO (Int, [ByteString]) Source #
execCommands :: Session -> [String] -> IO (Int, [ByteString]) Source #
Sftp Functions
:: FilePath | Path to known_hosts file |
-> FilePath | Path to public key file |
-> FilePath | Path to private key file |
-> String | Passphrase |
-> String | Remote user name |
-> String | Remote host name |
-> Int | Remote port number (usually 22) |
-> (Sftp -> IO a) | Actions to perform on sftp session |
-> IO a |
Execute some actions within SFTP connection. Uses public key authentication.
:: FilePath | Path to known_hosts file |
-> String | Remote user name |
-> String | Remote password |
-> String | Remote host name |
-> Int | Remote port number (usually 22) |
-> (Sftp -> IO a) | Actions to perform on sftp session |
-> IO a |
Execute some actions within SFTP connection. Uses username/password authentication.
Execute some actions within SFTP session
Reads directory information Returns the list of files with attributes, directory . and .. are not excluded
Rename a file on the sftp server
:: Sftp | Opened sftp session |
-> FilePath | Path to local file |
-> FilePath | Remote file path |
-> Int | File creation mode (0o777, for example) |
-> IO Integer |
Send a file to remote host via SFTP Returns size of sent data.
:: Sftp | Opened sftp session |
-> Handle | Handle to read from |
-> FilePath | Remote file path |
-> Int | File creation mode (0o777, for example) |
-> IO Integer |
Send a file to remote host via SFTP Returns size of sent data.
:: Sftp | Opened sftp session |
-> ByteString | Bytes to write |
-> FilePath | Remote file path |
-> Int | File creation mode (0o777, for example) |
-> IO Integer |
Send bytes to a remote host via SFTP Returns the size of sent data.
Received a file from remote host via SFTP Returns size of received data.
sftpReadFileToHandler :: SftpHandle -> Handle -> Int -> IO Int Source #
Download file from the sftp server
sftpFstat :: SftpHandle -> IO SftpAttributes Source #
Get sftp attributes from the sftp handler
Delete file from SFTP server
Utilities
socketConnect :: String -> Int -> IO Socket Source #
Similar to Network.connectTo, but does not socketToHandle.
sessionClose :: Session -> IO () Source #