gsasl-0.3.7: Bindings for GNU libgsasl

Safe HaskellNone
LanguageHaskell2010

Network.Protocol.SASL.GNU

Contents

Synopsis

Library Information

headerVersion :: (Integer, Integer, Integer) Source #

Which version of gsasl.h this module was compiled against

libraryVersion :: IO (Integer, Integer, Integer) Source #

Which version of libgsasl.so is loaded

checkVersion :: IO Bool Source #

Whether the header and library versions are compatible

SASL Contexts

data SASL a Source #

Instances
Monad SASL Source # 
Instance details

Defined in Network.Protocol.SASL.GNU

Methods

(>>=) :: SASL a -> (a -> SASL b) -> SASL b

(>>) :: SASL a -> SASL b -> SASL b

return :: a -> SASL a

fail :: String -> SASL a

Functor SASL Source # 
Instance details

Defined in Network.Protocol.SASL.GNU

Methods

fmap :: (a -> b) -> SASL a -> SASL b

(<$) :: a -> SASL b -> SASL a

Applicative SASL Source # 
Instance details

Defined in Network.Protocol.SASL.GNU

Methods

pure :: a -> SASL a

(<*>) :: SASL (a -> b) -> SASL a -> SASL b

liftA2 :: (a -> b -> c) -> SASL a -> SASL b -> SASL c

(*>) :: SASL a -> SASL b -> SASL b

(<*) :: SASL a -> SASL b -> SASL a

MonadIO SASL Source # 
Instance details

Defined in Network.Protocol.SASL.GNU

Methods

liftIO :: IO a -> SASL a

runSASL :: SASL a -> IO a Source #

setCallback :: (Property -> Session Progress) -> SASL () Source #

Set the current SASL callback. The callback will be used by mechanisms to discover various parameters, such as usernames and passwords.

runCallback :: Property -> Session Progress Source #

Run the current callback; the property indicates what action the callback is expected to perform.

Mechanisms

newtype Mechanism Source #

Constructors

Mechanism ByteString 
Instances
Eq Mechanism Source # 
Instance details

Defined in Network.Protocol.SASL.GNU

Methods

(==) :: Mechanism -> Mechanism -> Bool

(/=) :: Mechanism -> Mechanism -> Bool

Show Mechanism Source # 
Instance details

Defined in Network.Protocol.SASL.GNU

Methods

showsPrec :: Int -> Mechanism -> ShowS

show :: Mechanism -> String

showList :: [Mechanism] -> ShowS

IsString Mechanism Source # 
Instance details

Defined in Network.Protocol.SASL.GNU

Methods

fromString :: String -> Mechanism

clientMechanisms :: SASL [Mechanism] Source #

A list of Mechanisms supported by the libgsasl client.

clientSupports :: Mechanism -> SASL Bool Source #

Whether there is client-side support for a specified Mechanism.

clientSuggestMechanism :: [Mechanism] -> SASL (Maybe Mechanism) Source #

Given a list of Mechanisms, suggest which to use (or Nothing if no supported Mechanism is found).

serverMechanisms :: SASL [Mechanism] Source #

A list of Mechanisms supported by the libgsasl server.

serverSupports :: Mechanism -> SASL Bool Source #

Whether there is server-side support for a specified Mechanism.

SASL Sessions

data Session a Source #

Instances
Monad Session Source # 
Instance details

Defined in Network.Protocol.SASL.GNU

Methods

(>>=) :: Session a -> (a -> Session b) -> Session b

(>>) :: Session a -> Session b -> Session b

return :: a -> Session a

fail :: String -> Session a

Functor Session Source # 
Instance details

Defined in Network.Protocol.SASL.GNU

Methods

fmap :: (a -> b) -> Session a -> Session b

(<$) :: a -> Session b -> Session a

Applicative Session Source # 
Instance details

Defined in Network.Protocol.SASL.GNU

Methods

pure :: a -> Session a

(<*>) :: Session (a -> b) -> Session a -> Session b

liftA2 :: (a -> b -> c) -> Session a -> Session b -> Session c

(*>) :: Session a -> Session b -> Session b

(<*) :: Session a -> Session b -> Session a

MonadIO Session Source # 
Instance details

Defined in Network.Protocol.SASL.GNU

Methods

liftIO :: IO a -> Session a

runClient :: Mechanism -> Session a -> SASL (Either Error a) Source #

Run a session using the libgsasl client.

runServer :: Mechanism -> Session a -> SASL (Either Error a) Source #

Run a session using the libgsasl server.

mechanismName :: Session Mechanism Source #

The name of the session's SASL mechanism.

Session Properties

setProperty :: Property -> ByteString -> Session () Source #

Store some data in the session for the given property. The data must be NULL-terminated.

getProperty :: Property -> Session (Maybe ByteString) Source #

Retrieve the data stored in the session for the given property, possibly invoking the current callback to get the value.

getPropertyFast :: Property -> Session (Maybe ByteString) Source #

Retrieve the data stored in the session for the given property, without invoking the current callback.

Session IO

data Progress Source #

Constructors

Complete 
NeedsMore 
Instances
Eq Progress Source # 
Instance details

Defined in Network.Protocol.SASL.GNU

Methods

(==) :: Progress -> Progress -> Bool

(/=) :: Progress -> Progress -> Bool

Show Progress Source # 
Instance details

Defined in Network.Protocol.SASL.GNU

Methods

showsPrec :: Int -> Progress -> ShowS

show :: Progress -> String

showList :: [Progress] -> ShowS

step :: ByteString -> Session (ByteString, Progress) Source #

Perform one step of SASL authentication. This reads data from the other end, processes it (potentially running the callback), and returns data to be sent back.

Also returns NeedsMore if authentication is not yet complete.

step64 :: ByteString -> Session (ByteString, Progress) Source #

A simple wrapper around step which uses base64 to decode the input and encode the output.

encode :: ByteString -> Session ByteString Source #

Encode data according to the negotiated SASL mechanism. This might mean the data is integrity or privacy protected.

decode :: ByteString -> Session ByteString Source #

Decode data according to the negotiated SASL mechanism. This might mean the data is integrity or privacy protected.

Error handling

catch :: Session a -> (Error -> Session a) -> Session a Source #

handle :: (Error -> Session a) -> Session a -> Session a Source #

try :: Session a -> Session (Either Error a) Source #

Bundled codecs

toBase64 :: ByteString -> ByteString Source #

fromBase64 :: ByteString -> ByteString Source #

md5 :: ByteString -> ByteString Source #

sha1 :: ByteString -> ByteString Source #

hmacMD5 Source #

Arguments

:: ByteString

Key

-> ByteString

Input data

-> ByteString 

hmacSHA1 Source #

Arguments

:: ByteString

Key

-> ByteString

Input data

-> ByteString 

nonce :: Integer -> IO ByteString Source #

Returns unpredictable data of a given size

random :: Integer -> IO ByteString Source #

Returns cryptographically strong random data of a given size