| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Network.Hawk.Client
Description
Functions for making Hawk-authenticated request headers and verifying responses from the server.
The easiest way to make authenticated requests is to use withHawk
 with functions from the Network.HTTP.Simple module (from the
 http-conduit package).
- withHawk :: (MonadIO m, MonadCatch m) => Credentials -> Maybe ExtData -> Maybe PayloadInfo -> ServerAuthorizationCheck -> (Request -> m (Response body)) -> Request -> m (Response body)
 - data ServerAuthorizationCheck
 - data HawkException = HawkServerAuthorizationException String
 - data Credentials = Credentials {}
 - sign :: MonadIO m => Credentials -> Maybe ExtData -> Maybe PayloadInfo -> NominalDiffTime -> Request -> m (HeaderArtifacts, Request)
 - authenticate :: Response body -> Credentials -> HeaderArtifacts -> Maybe ByteString -> ServerAuthorizationCheck -> IO (Either String (Maybe ServerAuthorizationHeader))
 - header :: Text -> Method -> Credentials -> Maybe PayloadInfo -> NominalDiffTime -> Maybe ExtData -> IO Header
 - headerOz :: Text -> Method -> Credentials -> Maybe PayloadInfo -> NominalDiffTime -> Maybe ExtData -> Text -> Maybe Text -> IO Header
 - getBewit :: Credentials -> NominalDiffTime -> Maybe ExtData -> NominalDiffTime -> ByteString -> IO (Maybe ByteString)
 - message :: Credentials -> ByteString -> Maybe Int -> ByteString -> NominalDiffTime -> IO MessageAuth
 - data Header = Header {}
 - type Authorization = ByteString
 - module Network.Hawk.Types
 
Higher-level API
Arguments
| :: (MonadIO m, MonadCatch m) | |
| => Credentials | Credentials for signing the request.  | 
| -> Maybe ExtData | Optional application-specific data.  | 
| -> Maybe PayloadInfo | Optional payload to sign.  | 
| -> ServerAuthorizationCheck | Whether to verify the server's response.  | 
| -> (Request -> m (Response body)) | The action to run with the request.  | 
| -> Request | The request to sign.  | 
| -> m (Response body) | The result of the action.  | 
Signs and executes a request, then checks the server's response. Handles retrying of requests if the server and client clocks are out of sync.
A HawkException will be thrown if the server's response fails to
 authenticate.
Types
data ServerAuthorizationCheck Source #
Whether the client wants to check the received
 Server-Authorization header depends on the application.
Instances
data HawkException Source #
Client exceptions specific to Hawk.
Constructors
| HawkServerAuthorizationException String | The returned   | 
Instances
data Credentials Source #
ID and key used for encrypting Hawk Authorization header.
Constructors
| Credentials | |
Instances
Protocol functions
Arguments
| :: MonadIO m | |
| => Credentials | Credentials for signing  | 
| -> Maybe ExtData | Optional application-specific data.  | 
| -> Maybe PayloadInfo | Optional payload to hash  | 
| -> NominalDiffTime | Time offset to sync with server time  | 
| -> Request | The request to sign  | 
| -> m (HeaderArtifacts, Request) | 
Modifies a Request to include the Authorization header
 necessary for Hawk.
Arguments
| :: Response body | Response from server.  | 
| -> Credentials | Credentials used for signing the request.  | 
| -> HeaderArtifacts | The result of   | 
| -> Maybe ByteString | Optional payload body from response.  | 
| -> ServerAuthorizationCheck | Whether a valid   | 
| -> IO (Either String (Maybe ServerAuthorizationHeader)) | Error message if authentication failed.  | 
Validates the server response from a signed request. If the payload body is provided, its hash will be checked.
Arguments
| :: Text | The request URL  | 
| -> Method | The request method  | 
| -> Credentials | Credentials used to generate the header  | 
| -> Maybe PayloadInfo | Optional request payload  | 
| -> NominalDiffTime | Time offset to sync with server time  | 
| -> Maybe ExtData | Application-specific   | 
| -> IO Header | 
Generates the Hawk authentication header for a request.
Arguments
| :: Text | The request URL  | 
| -> Method | The request method  | 
| -> Credentials | Credentials used to generate the header  | 
| -> Maybe PayloadInfo | Optional request payload  | 
| -> NominalDiffTime | Time offset to sync with server time  | 
| -> Maybe ExtData | Application-specific   | 
| -> Text | Oz application identifier  | 
| -> Maybe Text | Oz delegated application  | 
| -> IO Header | 
Generates the Hawk authentication header for an Oz request. Oz requires another attribute -- the application id. It also has an optional delegated-by attribute, which is the application id of the application the credentials were directly issued to.
Arguments
| :: Credentials | Credentials used to generate the bewit.  | 
| -> NominalDiffTime | Time-to-live (TTL) value.  | 
| -> Maybe ExtData | Optional application-specific data.  | 
| -> NominalDiffTime | Time offset to sync with server time.  | 
| -> ByteString | URI.  | 
| -> IO (Maybe ByteString) | Base-64 encoded bewit value. fixme: javascript version supports deconstructed parsed uri objects fixme: not much point having two time interval arguments? Maybe just have a single expiry time argument.  | 
Generate a bewit value for a given URI. If the URI can't be
 parsed, Nothing will be returned.
See Network.Hawk.URI for more information about bewits.
Arguments
| :: Credentials | Credentials for encryption.  | 
| -> ByteString | Destination host.  | 
| -> Maybe Int | Destination port.  | 
| -> ByteString | The message.  | 
| -> NominalDiffTime | Time offset to sync with server time.  | 
| -> IO MessageAuth | 
Generates an authorization object for a Hawk signed message.
Types
The result of Hawk header generation.
Constructors
| Header | |
Fields 
  | |
type Authorization = ByteString Source #
The value of an Authorization header.
module Network.Hawk.Types