| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Data.Radius.Implements
Synopsis
- signPacket :: (a -> ByteString -> Put) -> ByteString -> Bin128 -> (Word16 -> Bin128 -> Header) -> (Bin128 -> [Attribute' a]) -> (Word16, Bin128, Bin128)
- signedPacket :: (a -> ByteString -> Put) -> ByteString -> Bin128 -> (Word16 -> Bin128 -> Header) -> (Bin128 -> [Attribute' a]) -> Packet [Attribute' a]
- data AuthenticatorError v
- checkSignedRequest :: (TypedNumberSets a, Ord a) => (a -> ByteString -> Put) -> ByteString -> Packet [Attribute' a] -> Either (AuthenticatorError a) (Attributes a)
- checkSignedResponse :: (TypedNumberSets a, Ord a) => (a -> ByteString -> Put) -> ByteString -> Bin128 -> Packet [Attribute' a] -> Either (AuthenticatorError a) (Attributes a)
Documentation
Arguments
| :: (a -> ByteString -> Put) | Printer for vendor specific attribute |
| -> ByteString | Radius secret key |
| -> Bin128 | Request authenticator |
| -> (Word16 -> Bin128 -> Header) | Function to make header |
| -> (Bin128 -> [Attribute' a]) | Function to make attributes from message authenticator |
| -> (Word16, Bin128, Bin128) | Packet length, message authenticator and response authenticator |
Make signatures for response packet. When you don't want to use message authenticator attribute, pass a function to make attributes which doesn't use message authenticator argument.
Arguments
| :: (a -> ByteString -> Put) | Printer for vendor specific attribute |
| -> ByteString | Radius secret key |
| -> Bin128 | Request authenticator |
| -> (Word16 -> Bin128 -> Header) | Function to make header |
| -> (Bin128 -> [Attribute' a]) | Function to make attributes from message authenticator |
| -> Packet [Attribute' a] | Signed packet |
data AuthenticatorError v Source #
Constructors
| NoMessageAuthenticator (Attributes v) | No Message-Authenticator attribute |
| BadMessageAuthenticator | Message-Authenticator attribute is not matched |
| MoreThanOneMessageAuthenticator | More than one Message-Authenticator attribute pairs found |
| BadAuthenticator | Radius packet authenticator is not matched |
| AttributesDecodeError String | Fail to decode attributes, attribute type error etc. |
| NotRequestPacket Code | Not request packet is passed to function to check request packet |
| NotResponsePacket Code | Not response packet is passed to function to check response packet |
Instances
| Show (AuthenticatorError v) Source # | |
Defined in Data.Radius.Implements Methods showsPrec :: Int -> AuthenticatorError v -> ShowS # show :: AuthenticatorError v -> String # showList :: [AuthenticatorError v] -> ShowS # | |
Arguments
| :: (TypedNumberSets a, Ord a) | |
| => (a -> ByteString -> Put) | Printer for vendor specific attribute |
| -> ByteString | |
| -> Packet [Attribute' a] | |
| -> Either (AuthenticatorError a) (Attributes a) |
Arguments
| :: (TypedNumberSets a, Ord a) | |
| => (a -> ByteString -> Put) | Printer for vendor specific attribute |
| -> ByteString | |
| -> Bin128 | |
| -> Packet [Attribute' a] | |
| -> Either (AuthenticatorError a) (Attributes a) |