-- GENERATED by C->Haskell Compiler, version 0.28.3 Switcheroo, 25 November 2017 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 "src/Network/SSH/Client/LibSSH2/Errors.chs" #-}
{-# LANGUAGE ForeignFunctionInterface, DeriveDataTypeable, FlexibleInstances #-}






{-# LINE 12 "src/Network/SSH/Client/LibSSH2/Errors.chs" #-}


module Network.SSH.Client.LibSSH2.Errors
  (-- * Types
   ErrorCode (..),
   SftpErrorCode (..),
   NULL_POINTER,

   -- * Utilities
   IntResult (..),

   -- * Functions
   getLastError,
   getLastSftpError,
   handleInt,
   handleBool,
   handleNullPtr,
   int2error, error2int,
   int2sftperror, sftperror2int,
   blockedDirections,
   threadWaitSession
  ) where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp



import Control.Exception
import Data.Generics
import Foreign
import Foreign.C.Types

import Network.SSH.Client.LibSSH2.Types
import Network.SSH.Client.LibSSH2.WaitSocket

-- | Error codes returned by libssh2.
data ErrorCode =
    NONE
  | SOCKET_NONE
  | 
  | 
  | INVALID_MAC
  | KEX_FALIURE
  | ALLOC
  | SOCKET_SEND
  | KEY_EXCHANGE_FAILURE
  | TIMEOUT
  | HOSTKEY_INIT
  | HOSTKEY_SIGN
  | DECRYPT
  | SOCKET_DISCONNECT
  | PROTO
  | PASSWORD_EXPIRED
  | FILE
  | METHOD_NONE
  | AUTHENTICATION_FAILED
  | PUBLICKEY_UNVERIFIED
  | CHANNEL_OUTOFORDER
  | CHANNEL_FAILURE
  | CHANNEL_REQUEST_DENIED
  | CHANNEL_UNKNOWN
  | CHANNEL_WINDOW_EXCEEDED
  | CHANNEL_PACKET_EXCEEDED
  | CHANNEL_CLOSED
  | CHANNEL_EOF_SENT
  | SCP_PROTOCOL
  | ZLIB
  | SOCKET_TIMEOUT
  | SFTP_PROTOCOL
  | REQUEST_DENIED
  | METHOD_NOT_SUPPORTED
  | INVAL
  | INVALID_POLL_TYPE
  | PUBLICKEY_PROTOCOL
  | EAGAIN
  | BUFFER_TOO_SMALL
  | BAD_USE
  | COMPRESS
  | OUT_OF_BOUNDARY
  | AGENT_PROTOCOL
  | SOCKET_RECV
  | ENCRYPT
  | BAD_SOCKET
  | ERROR_KNOWN_HOSTS
  deriving (ErrorCode -> ErrorCode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ErrorCode -> ErrorCode -> Bool
$c/= :: ErrorCode -> ErrorCode -> Bool
== :: ErrorCode -> ErrorCode -> Bool
$c== :: ErrorCode -> ErrorCode -> Bool
Eq, Int -> ErrorCode -> ShowS
[ErrorCode] -> ShowS
ErrorCode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ErrorCode] -> ShowS
$cshowList :: [ErrorCode] -> ShowS
show :: ErrorCode -> String
$cshow :: ErrorCode -> String
showsPrec :: Int -> ErrorCode -> ShowS
$cshowsPrec :: Int -> ErrorCode -> ShowS
Show, Eq ErrorCode
ErrorCode -> ErrorCode -> Bool
ErrorCode -> ErrorCode -> Ordering
ErrorCode -> ErrorCode -> ErrorCode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ErrorCode -> ErrorCode -> ErrorCode
$cmin :: ErrorCode -> ErrorCode -> ErrorCode
max :: ErrorCode -> ErrorCode -> ErrorCode
$cmax :: ErrorCode -> ErrorCode -> ErrorCode
>= :: ErrorCode -> ErrorCode -> Bool
$c>= :: ErrorCode -> ErrorCode -> Bool
> :: ErrorCode -> ErrorCode -> Bool
$c> :: ErrorCode -> ErrorCode -> Bool
<= :: ErrorCode -> ErrorCode -> Bool
$c<= :: ErrorCode -> ErrorCode -> Bool
< :: ErrorCode -> ErrorCode -> Bool
$c< :: ErrorCode -> ErrorCode -> Bool
compare :: ErrorCode -> ErrorCode -> Ordering
$ccompare :: ErrorCode -> ErrorCode -> Ordering
Ord, Int -> ErrorCode
ErrorCode -> Int
ErrorCode -> [ErrorCode]
ErrorCode -> ErrorCode
ErrorCode -> ErrorCode -> [ErrorCode]
ErrorCode -> ErrorCode -> ErrorCode -> [ErrorCode]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ErrorCode -> ErrorCode -> ErrorCode -> [ErrorCode]
$cenumFromThenTo :: ErrorCode -> ErrorCode -> ErrorCode -> [ErrorCode]
enumFromTo :: ErrorCode -> ErrorCode -> [ErrorCode]
$cenumFromTo :: ErrorCode -> ErrorCode -> [ErrorCode]
enumFromThen :: ErrorCode -> ErrorCode -> [ErrorCode]
$cenumFromThen :: ErrorCode -> ErrorCode -> [ErrorCode]
enumFrom :: ErrorCode -> [ErrorCode]
$cenumFrom :: ErrorCode -> [ErrorCode]
fromEnum :: ErrorCode -> Int
$cfromEnum :: ErrorCode -> Int
toEnum :: Int -> ErrorCode
$ctoEnum :: Int -> ErrorCode
pred :: ErrorCode -> ErrorCode
$cpred :: ErrorCode -> ErrorCode
succ :: ErrorCode -> ErrorCode
$csucc :: ErrorCode -> ErrorCode
Enum, Typeable ErrorCode
ErrorCode -> DataType
ErrorCode -> Constr
(forall b. Data b => b -> b) -> ErrorCode -> ErrorCode
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ErrorCode -> u
forall u. (forall d. Data d => d -> u) -> ErrorCode -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorCode -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorCode -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ErrorCode -> m ErrorCode
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ErrorCode -> m ErrorCode
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ErrorCode
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ErrorCode -> c ErrorCode
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ErrorCode)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ErrorCode)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ErrorCode -> m ErrorCode
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ErrorCode -> m ErrorCode
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ErrorCode -> m ErrorCode
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ErrorCode -> m ErrorCode
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ErrorCode -> m ErrorCode
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ErrorCode -> m ErrorCode
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ErrorCode -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ErrorCode -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ErrorCode -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ErrorCode -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorCode -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorCode -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorCode -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorCode -> r
gmapT :: (forall b. Data b => b -> b) -> ErrorCode -> ErrorCode
$cgmapT :: (forall b. Data b => b -> b) -> ErrorCode -> ErrorCode
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ErrorCode)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ErrorCode)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ErrorCode)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ErrorCode)
dataTypeOf :: ErrorCode -> DataType
$cdataTypeOf :: ErrorCode -> DataType
toConstr :: ErrorCode -> Constr
$ctoConstr :: ErrorCode -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ErrorCode
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ErrorCode
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ErrorCode -> c ErrorCode
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ErrorCode -> c ErrorCode
Data, Typeable)

instance Exception ErrorCode

error2int :: (Num i) => ErrorCode -> i
error2int :: forall i. Num i => ErrorCode -> i
error2int = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => a -> a
negate forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => a -> Int
fromEnum

int2error :: (Integral i) => i -> ErrorCode
int2error :: forall i. Integral i => i -> ErrorCode
int2error = forall a. Enum a => Int -> a
toEnum forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => a -> a
negate forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Exception to throw when null pointer received
-- from libssh2.
data NULL_POINTER = NULL_POINTER
  deriving (NULL_POINTER -> NULL_POINTER -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NULL_POINTER -> NULL_POINTER -> Bool
$c/= :: NULL_POINTER -> NULL_POINTER -> Bool
== :: NULL_POINTER -> NULL_POINTER -> Bool
$c== :: NULL_POINTER -> NULL_POINTER -> Bool
Eq, Int -> NULL_POINTER -> ShowS
[NULL_POINTER] -> ShowS
NULL_POINTER -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NULL_POINTER] -> ShowS
$cshowList :: [NULL_POINTER] -> ShowS
show :: NULL_POINTER -> String
$cshow :: NULL_POINTER -> String
showsPrec :: Int -> NULL_POINTER -> ShowS
$cshowsPrec :: Int -> NULL_POINTER -> ShowS
Show, Typeable NULL_POINTER
NULL_POINTER -> DataType
NULL_POINTER -> Constr
(forall b. Data b => b -> b) -> NULL_POINTER -> NULL_POINTER
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> NULL_POINTER -> u
forall u. (forall d. Data d => d -> u) -> NULL_POINTER -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NULL_POINTER -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NULL_POINTER -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NULL_POINTER -> m NULL_POINTER
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NULL_POINTER -> m NULL_POINTER
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NULL_POINTER
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NULL_POINTER -> c NULL_POINTER
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NULL_POINTER)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NULL_POINTER)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NULL_POINTER -> m NULL_POINTER
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NULL_POINTER -> m NULL_POINTER
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NULL_POINTER -> m NULL_POINTER
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NULL_POINTER -> m NULL_POINTER
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NULL_POINTER -> m NULL_POINTER
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NULL_POINTER -> m NULL_POINTER
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NULL_POINTER -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NULL_POINTER -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> NULL_POINTER -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NULL_POINTER -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NULL_POINTER -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NULL_POINTER -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NULL_POINTER -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NULL_POINTER -> r
gmapT :: (forall b. Data b => b -> b) -> NULL_POINTER -> NULL_POINTER
$cgmapT :: (forall b. Data b => b -> b) -> NULL_POINTER -> NULL_POINTER
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NULL_POINTER)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NULL_POINTER)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NULL_POINTER)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NULL_POINTER)
dataTypeOf :: NULL_POINTER -> DataType
$cdataTypeOf :: NULL_POINTER -> DataType
toConstr :: NULL_POINTER -> Constr
$ctoConstr :: NULL_POINTER -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NULL_POINTER
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NULL_POINTER
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NULL_POINTER -> c NULL_POINTER
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NULL_POINTER -> c NULL_POINTER
Data, Typeable)

instance Exception NULL_POINTER

class IntResult a where
  intResult :: a -> Int

instance IntResult Int where
  intResult :: Int -> Int
intResult = forall a. a -> a
id

instance IntResult (Int, a) where
  intResult :: (Int, a) -> Int
intResult = forall a b. (a, b) -> a
fst

instance IntResult (Int, a, b) where
  intResult :: (Int, a, b) -> Int
intResult = \(Int
i, a
_, b
_) -> Int
i

instance IntResult (Int, a, b, c) where
  intResult :: (Int, a, b, c) -> Int
intResult = \(Int
i, a
_, b
_, c
_) -> Int
i

instance IntResult CInt where
  intResult :: CInt -> Int
intResult = forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance IntResult CLong where
  intResult :: CLong -> Int
intResult = forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance IntResult CLLong where
  intResult :: CLLong -> Int
intResult = forall a b. (Integral a, Num b) => a -> b
fromIntegral

getLastError_ :: (Session) -> (Ptr Int) -> (Int) -> IO ((Int), (String))
getLastError_ :: Session -> Ptr Int -> Int -> IO (Int, String)
getLastError_ Session
a1 Ptr Int
a3 Int
a4 =
  let {a1' :: Ptr ()
a1' = forall p. ToPointer p => p -> Ptr ()
toPointer Session
a1} in 
  forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr (Ptr CChar)
a2' -> 
  let {a3' :: Ptr b
a3' = forall a b. Ptr a -> Ptr b
castPtr Ptr Int
a3} in 
  let {a4' :: CInt
a4' = forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
a4} in 
  Ptr () -> Ptr (Ptr CChar) -> Ptr CInt -> CInt -> IO CInt
getLastError_'_ Ptr ()
a1' Ptr (Ptr CChar)
a2' forall a. Ptr a
a3' CInt
a4' forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CInt
res ->
  let {res' :: Int
res' = forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
res} in
  Ptr (Ptr CChar) -> IO String
peekCStringPtr  Ptr (Ptr CChar)
a2'forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \String
a2'' -> 
  forall (m :: * -> *) a. Monad m => a -> m a
return (Int
res', a2'')

{-# LINE 137 "src/Network/SSH/Client/LibSSH2/Errors.chs" #-}


-- | Get last error information.
getLastError :: Session -> IO (Int, String)
getLastError s = getLastError_ s nullPtr 0

-- | Throw an exception if negative value passed,
-- or return unchanged value.
handleInt :: (IntResult a, SshCtx ctx) => Maybe ctx -> IO a -> IO a
handleInt s io = do
  x <- io
  let r = intResult x
  if r < 0
    then case int2error r of
           EAGAIN -> threadWaitSession s >> handleInt s io
           err    ->
             case s of
               Nothing  -> throw err
               Just ctx -> throwCtxSpecificError ctx err
    else return x

handleBool :: CInt -> IO Bool
handleBool :: CInt -> IO Bool
handleBool CInt
x
  | CInt
x forall a. Eq a => a -> a -> Bool
== CInt
0 = forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
  | CInt
x forall a. Ord a => a -> a -> Bool
> CInt
0  = forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
  | Bool
otherwise = forall a e. Exception e => e -> a
throw (forall i. Integral i => i -> ErrorCode
int2error CInt
x)

-- | Throw an exception if null pointer passed,
-- or return it casted to right type.
handleNullPtr :: (SshCtx c) => Maybe c -> (Ptr () -> IO a) -> IO (Ptr ()) -> IO a
handleNullPtr :: forall c a.
SshCtx c =>
Maybe c -> (Ptr () -> IO a) -> IO (Ptr ()) -> IO a
handleNullPtr Maybe c
m_ctx Ptr () -> IO a
fromPointer IO (Ptr ())
io = do
  Ptr ()
ptr <- IO (Ptr ())
io
  if Ptr ()
ptr forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
    then case Maybe c
m_ctx of
      Maybe c
Nothing  -> forall a e. Exception e => e -> a
throw NULL_POINTER
NULL_POINTER
      Just c
ctx -> do
        let session :: Session
session = forall a. SshCtx a => a -> Session
getSession c
ctx
        (Int
r, String
_) <- Session -> IO (Int, String)
getLastError Session
session
        case forall i. Integral i => i -> ErrorCode
int2error Int
r of
          ErrorCode
EAGAIN -> forall ctx. SshCtx ctx => Maybe ctx -> IO ()
threadWaitSession (forall a. a -> Maybe a
Just Session
session) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall c a.
SshCtx c =>
Maybe c -> (Ptr () -> IO a) -> IO (Ptr ()) -> IO a
handleNullPtr Maybe c
m_ctx Ptr () -> IO a
fromPointer IO (Ptr ())
io
          ErrorCode
err    -> forall a b. SshCtx a => a -> ErrorCode -> IO b
throwCtxSpecificError c
ctx ErrorCode
err
    else Ptr () -> IO a
fromPointer Ptr ()
ptr

-- | Get currently blocked directions
blockedDirections :: (Session) -> IO (([Direction]))
blockedDirections :: Session -> IO [Direction]
blockedDirections Session
a1 =
  let {a1' :: Ptr ()
a1' = forall p. ToPointer p => p -> Ptr ()
toPointer Session
a1} in 
  Ptr () -> IO CInt
blockedDirections'_ Ptr ()
a1' forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CInt
res ->
  let {res' :: [Direction]
res' = int2dir res} in
  return (res')

{-# LINE 182 "src/Network/SSH/Client/LibSSH2/Errors.chs" #-}


threadWaitSession :: (SshCtx ctx) => Maybe ctx -> IO ()
threadWaitSession Nothing = error "EAGAIN thrown without session present"
threadWaitSession (Just ctx) = do
  let s = getSession ctx
  mSocket <- sessionGetSocket s
  case mSocket of
    Nothing -> error "EAGAIN thrown on session without socket"
    Just socket -> do
      dirs <- blockedDirections s
      case dirs of
        [] -> pure ()
        _ ->
          if (OUTBOUND `elem` dirs)
            then threadWaitWrite socket
            else threadWaitRead socket

-- | Sftp

getLastSftpError_ :: (Sftp) -> IO ((Int))
getLastSftpError_ :: Sftp -> IO Int
getLastSftpError_ Sftp
a1 =
  let {a1' :: Ptr ()
a1' = forall p. ToPointer p => p -> Ptr ()
toPointer Sftp
a1} in 
  Ptr () -> IO CULong
getLastSftpError_'_ Ptr ()
a1' forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CULong
res ->
  let {res' :: Int
res' = forall a b. (Integral a, Num b) => a -> b
fromIntegral CULong
res} in
  return (res')

{-# LINE 203 "src/Network/SSH/Client/LibSSH2/Errors.chs" #-}


-- | Get last sftp related error.
getLastSftpError :: Sftp -> IO Int
getLastSftpError sftp = getLastSftpError_ sftp

sftperror2int :: (Num i) => SftpErrorCode -> i
sftperror2int :: forall i. Num i => SftpErrorCode -> i
sftperror2int = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => a -> Int
fromEnum

int2sftperror :: (Integral i) => i -> SftpErrorCode
int2sftperror :: forall i. Integral i => i -> SftpErrorCode
int2sftperror = forall a. Enum a => Int -> a
toEnum forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Sftp error code returning from libssh2
data SftpErrorCode =
    FX_OK
  | FX_EOF
  | FX_NO_SUCH_FILE
  | FX_PERMISSION_DENIED
  | FX_FAILURE
  | FX_BAD_MESSAGE
  | FX_NO_CONNECTION
  | FX_CONNECTION_LOST
  | FX_OP_UNSUPPORTED
  | FX_INVALID_HANDLE
  | FX_NO_SUCH_PATH
  | FX_FILE_ALREADY_EXISTS
  | FX_WRITE_PROTECT
  | FX_NO_MEDIA
  | FX_NO_SPACE_ON_FILESYSTEM
  | FX_QUOTA_EXCEEDED
  | FX_UNKNOWN_PRINCIPAL
  | FX_LOCK_CONFLICT
  | FX_DIR_NOT_EMPTY
  | FX_NOT_A_DIRECTORY
  | FX_INVALID_FILENAME
  | FX_LINK_LOOP
  deriving (SftpErrorCode -> SftpErrorCode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SftpErrorCode -> SftpErrorCode -> Bool
$c/= :: SftpErrorCode -> SftpErrorCode -> Bool
== :: SftpErrorCode -> SftpErrorCode -> Bool
$c== :: SftpErrorCode -> SftpErrorCode -> Bool
Eq, Int -> SftpErrorCode -> ShowS
[SftpErrorCode] -> ShowS
SftpErrorCode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SftpErrorCode] -> ShowS
$cshowList :: [SftpErrorCode] -> ShowS
show :: SftpErrorCode -> String
$cshow :: SftpErrorCode -> String
showsPrec :: Int -> SftpErrorCode -> ShowS
$cshowsPrec :: Int -> SftpErrorCode -> ShowS
Show, Eq SftpErrorCode
SftpErrorCode -> SftpErrorCode -> Bool
SftpErrorCode -> SftpErrorCode -> Ordering
SftpErrorCode -> SftpErrorCode -> SftpErrorCode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SftpErrorCode -> SftpErrorCode -> SftpErrorCode
$cmin :: SftpErrorCode -> SftpErrorCode -> SftpErrorCode
max :: SftpErrorCode -> SftpErrorCode -> SftpErrorCode
$cmax :: SftpErrorCode -> SftpErrorCode -> SftpErrorCode
>= :: SftpErrorCode -> SftpErrorCode -> Bool
$c>= :: SftpErrorCode -> SftpErrorCode -> Bool
> :: SftpErrorCode -> SftpErrorCode -> Bool
$c> :: SftpErrorCode -> SftpErrorCode -> Bool
<= :: SftpErrorCode -> SftpErrorCode -> Bool
$c<= :: SftpErrorCode -> SftpErrorCode -> Bool
< :: SftpErrorCode -> SftpErrorCode -> Bool
$c< :: SftpErrorCode -> SftpErrorCode -> Bool
compare :: SftpErrorCode -> SftpErrorCode -> Ordering
$ccompare :: SftpErrorCode -> SftpErrorCode -> Ordering
Ord, Int -> SftpErrorCode
SftpErrorCode -> Int
SftpErrorCode -> [SftpErrorCode]
SftpErrorCode -> SftpErrorCode
SftpErrorCode -> SftpErrorCode -> [SftpErrorCode]
SftpErrorCode -> SftpErrorCode -> SftpErrorCode -> [SftpErrorCode]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: SftpErrorCode -> SftpErrorCode -> SftpErrorCode -> [SftpErrorCode]
$cenumFromThenTo :: SftpErrorCode -> SftpErrorCode -> SftpErrorCode -> [SftpErrorCode]
enumFromTo :: SftpErrorCode -> SftpErrorCode -> [SftpErrorCode]
$cenumFromTo :: SftpErrorCode -> SftpErrorCode -> [SftpErrorCode]
enumFromThen :: SftpErrorCode -> SftpErrorCode -> [SftpErrorCode]
$cenumFromThen :: SftpErrorCode -> SftpErrorCode -> [SftpErrorCode]
enumFrom :: SftpErrorCode -> [SftpErrorCode]
$cenumFrom :: SftpErrorCode -> [SftpErrorCode]
fromEnum :: SftpErrorCode -> Int
$cfromEnum :: SftpErrorCode -> Int
toEnum :: Int -> SftpErrorCode
$ctoEnum :: Int -> SftpErrorCode
pred :: SftpErrorCode -> SftpErrorCode
$cpred :: SftpErrorCode -> SftpErrorCode
succ :: SftpErrorCode -> SftpErrorCode
$csucc :: SftpErrorCode -> SftpErrorCode
Enum, Typeable SftpErrorCode
SftpErrorCode -> DataType
SftpErrorCode -> Constr
(forall b. Data b => b -> b) -> SftpErrorCode -> SftpErrorCode
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> SftpErrorCode -> u
forall u. (forall d. Data d => d -> u) -> SftpErrorCode -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SftpErrorCode -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SftpErrorCode -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SftpErrorCode -> m SftpErrorCode
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SftpErrorCode -> m SftpErrorCode
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SftpErrorCode
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SftpErrorCode -> c SftpErrorCode
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SftpErrorCode)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SftpErrorCode)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SftpErrorCode -> m SftpErrorCode
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SftpErrorCode -> m SftpErrorCode
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SftpErrorCode -> m SftpErrorCode
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SftpErrorCode -> m SftpErrorCode
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SftpErrorCode -> m SftpErrorCode
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SftpErrorCode -> m SftpErrorCode
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SftpErrorCode -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SftpErrorCode -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> SftpErrorCode -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SftpErrorCode -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SftpErrorCode -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SftpErrorCode -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SftpErrorCode -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SftpErrorCode -> r
gmapT :: (forall b. Data b => b -> b) -> SftpErrorCode -> SftpErrorCode
$cgmapT :: (forall b. Data b => b -> b) -> SftpErrorCode -> SftpErrorCode
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SftpErrorCode)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SftpErrorCode)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SftpErrorCode)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SftpErrorCode)
dataTypeOf :: SftpErrorCode -> DataType
$cdataTypeOf :: SftpErrorCode -> DataType
toConstr :: SftpErrorCode -> Constr
$ctoConstr :: SftpErrorCode -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SftpErrorCode
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SftpErrorCode
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SftpErrorCode -> c SftpErrorCode
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SftpErrorCode -> c SftpErrorCode
Data, Typeable)

instance Exception SftpErrorCode


class SshCtx a where
  getSession :: a -> Session
  throwCtxSpecificError :: a -> ErrorCode -> IO b

instance SshCtx Session where
  getSession :: Session -> Session
getSession = forall a. a -> a
id
  throwCtxSpecificError :: forall b. Session -> ErrorCode -> IO b
throwCtxSpecificError Session
_ ErrorCode
er = forall a e. Exception e => e -> a
throw ErrorCode
er

instance SshCtx Sftp where
  getSession :: Sftp -> Session
getSession = Sftp -> Session
sftpSession

  throwCtxSpecificError :: forall b. Sftp -> ErrorCode -> IO b
throwCtxSpecificError Sftp
ctx ErrorCode
SFTP_PROTOCOL = do
    Int
er <- Sftp -> IO Int
getLastSftpError Sftp
ctx
    forall a e. Exception e => e -> a
throw (forall i. Integral i => i -> SftpErrorCode
int2sftperror Int
er)
  throwCtxSpecificError Sftp
_ ErrorCode
er = forall a e. Exception e => e -> a
throw ErrorCode
er

instance SshCtx SftpHandle where
  getSession :: SftpHandle -> Session
getSession = forall a. SshCtx a => a -> Session
getSession forall b c a. (b -> c) -> (a -> b) -> a -> c
. SftpHandle -> Sftp
sftpHandleSession

  throwCtxSpecificError :: forall b. SftpHandle -> ErrorCode -> IO b
throwCtxSpecificError SftpHandle
ctx =
    forall a b. SshCtx a => a -> ErrorCode -> IO b
throwCtxSpecificError (SftpHandle -> Sftp
sftpHandleSession SftpHandle
ctx)

instance SshCtx Agent where
  getSession :: Agent -> Session
getSession = forall a. SshCtx a => a -> Session
getSession forall b c a. (b -> c) -> (a -> b) -> a -> c
. Agent -> Session
agentSession
  throwCtxSpecificError :: forall b. Agent -> ErrorCode -> IO b
throwCtxSpecificError Agent
_ ErrorCode
er = forall a e. Exception e => e -> a
throw ErrorCode
er
foreign import ccall safe "Network/SSH/Client/LibSSH2/Errors.chs.h libssh2_session_last_error"
  getLastError_'_ :: ((C2HSImp.Ptr ()) -> ((C2HSImp.Ptr (C2HSImp.Ptr C2HSImp.CChar)) -> ((C2HSImp.Ptr C2HSImp.CInt) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))

foreign import ccall safe "Network/SSH/Client/LibSSH2/Errors.chs.h libssh2_session_block_directions"
  blockedDirections'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))

foreign import ccall safe "Network/SSH/Client/LibSSH2/Errors.chs.h libssh2_sftp_last_error"
  getLastSftpError_'_ :: ((C2HSImp.Ptr ()) -> (IO C2HSImp.CULong))