Safe Haskell | None |
---|---|
Language | Haskell2010 |
Note that this is essentially the "kitchen sink" export module, including many functions intended only to be used internally by this package. No API stability is guaranteed for this module. If you see functions here which you believe should be promoted to a stable API, please contact the author.
- 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
- headerBase :: Text -> Method -> Credentials -> Maybe PayloadInfo -> NominalDiffTime -> Maybe ExtData -> Maybe Text -> Maybe Text -> IO Header
- headerBase' :: Text -> Method -> Credentials -> Maybe PayloadInfo -> NominalDiffTime -> Maybe ExtData -> Maybe Text -> Maybe Text -> POSIXTime -> ByteString -> Header
- message :: Credentials -> ByteString -> Maybe Int -> ByteString -> NominalDiffTime -> IO MessageAuth
- message' :: Credentials -> ByteString -> Maybe Int -> ByteString -> NominalDiffTime -> POSIXTime -> ByteString -> MessageAuth
- artsMsg :: Credentials -> HeaderArtifacts -> MessageAuth
- header' :: HawkType -> Text -> Method -> Credentials -> Maybe PayloadInfo -> NominalDiffTime -> Maybe ExtData -> Maybe Text -> Maybe Text -> POSIXTime -> ByteString -> HeaderArtifacts
- headerArtifacts :: POSIXTime -> ByteString -> Method -> ByteString -> Maybe ByteString -> Maybe ByteString -> Maybe Text -> Maybe Text -> ClientId -> ByteString -> HeaderArtifacts
- clientHawkAuth :: HeaderArtifacts -> ByteString
- clientMac :: Credentials -> HawkType -> HeaderArtifacts -> ByteString
- hawkHeaderItems :: [(ByteString, Maybe ByteString)] -> [(ByteString, ByteString)]
- splitUrl :: ByteString -> Maybe SplitURL
- genNonce :: IO ByteString
- data ServerAuthorizationCheck
- authenticate :: Response body -> Credentials -> HeaderArtifacts -> Maybe ByteString -> ServerAuthorizationCheck -> IO (Either String (Maybe ServerAuthorizationHeader))
- authenticate' :: Response body -> Credentials -> HeaderArtifacts -> Maybe ByteString -> ServerAuthorizationCheck -> POSIXTime -> Either String (Maybe ServerAuthorizationHeader)
- responseHeader :: HeaderName -> Response body -> Maybe ByteString
- checkWwwAuthenticateHeader :: Credentials -> ByteString -> Either String (Maybe POSIXTime)
- checkServerAuthorizationHeader :: Credentials -> HeaderArtifacts -> ServerAuthorizationCheck -> POSIXTime -> Maybe ByteString -> Either String (Maybe ServerAuthorizationHeader)
- responseArtifacts :: ServerAuthorizationHeader -> HeaderArtifacts -> HeaderArtifacts
- getBewit :: Credentials -> NominalDiffTime -> Maybe ExtData -> NominalDiffTime -> ByteString -> IO (Maybe ByteString)
- bewitArtifacts :: ByteString -> POSIXTime -> Maybe ExtData -> Maybe HeaderArtifacts
- encodeBewit :: Credentials -> HeaderArtifacts -> ByteString
- bewitString :: ClientId -> POSIXTime -> ByteString -> Maybe ExtData -> ByteString
- sign :: MonadIO m => Credentials -> Maybe ExtData -> Maybe PayloadInfo -> NominalDiffTime -> Request -> m (HeaderArtifacts, Request)
- addAuth :: Header -> Request -> Request
- data HawkException = HawkServerAuthorizationException String
- withHawk :: (MonadIO m, MonadCatch m) => Credentials -> Maybe ExtData -> Maybe PayloadInfo -> ServerAuthorizationCheck -> (Request -> m (Response body)) -> Request -> m (Response body)
- withHawkPayload :: (MonadIO m, MonadCatch m) => Credentials -> Maybe ExtData -> PayloadInfo -> ServerAuthorizationCheck -> (Request -> m (Response body)) -> Request -> m (Response body)
- withHawkBase :: (MonadIO m, MonadThrow m, MonadCatch m) => Credentials -> Maybe ExtData -> Maybe PayloadInfo -> ServerAuthorizationCheck -> (Request -> m (Response body)) -> Request -> m (Response body)
- makeExpiryHandler :: MonadCatch m => Credentials -> Request -> m a -> m (Either NominalDiffTime a)
- doSignedRequest :: (MonadIO m, MonadThrow m) => NominalDiffTime -> Credentials -> Maybe ExtData -> Maybe PayloadInfo -> ServerAuthorizationCheck -> (Request -> m (Response body)) -> Request -> m (Response body)
- authResponse :: MonadIO m => Credentials -> HeaderArtifacts -> ServerAuthorizationCheck -> Response body -> m (Either String (Maybe ServerAuthorizationHeader))
- wasStale :: Request -> Response () -> Credentials -> Maybe NominalDiffTime
- hawkTs :: Credentials -> ResponseHeaders -> Maybe POSIXTime
Documentation
:: 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.
:: 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.
headerBase :: Text -> Method -> Credentials -> Maybe PayloadInfo -> NominalDiffTime -> Maybe ExtData -> Maybe Text -> Maybe Text -> IO Header Source #
headerBase' :: Text -> Method -> Credentials -> Maybe PayloadInfo -> NominalDiffTime -> Maybe ExtData -> Maybe Text -> Maybe Text -> POSIXTime -> ByteString -> Header Source #
:: 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.
:: Credentials | Credentials for encryption. |
-> ByteString | Destination host. |
-> Maybe Int | Destination port. |
-> ByteString | The message. |
-> NominalDiffTime | Time offset to sync with server time. |
-> POSIXTime | Message timestamp. |
-> ByteString | Random nonce string. |
-> MessageAuth |
Generates an authorization object for a Hawk signed message. This variation allows the user to provide the message timestamp and nonce string.
artsMsg :: Credentials -> HeaderArtifacts -> MessageAuth Source #
Signs a message stored in the given artifacts bundle.
header' :: HawkType -> Text -> Method -> Credentials -> Maybe PayloadInfo -> NominalDiffTime -> Maybe ExtData -> Maybe Text -> Maybe Text -> POSIXTime -> ByteString -> HeaderArtifacts Source #
headerArtifacts :: POSIXTime -> ByteString -> Method -> ByteString -> Maybe ByteString -> Maybe ByteString -> Maybe Text -> Maybe Text -> ClientId -> ByteString -> HeaderArtifacts Source #
Constructs artifacts bundle from header params.
clientMac :: Credentials -> HawkType -> HeaderArtifacts -> ByteString Source #
hawkHeaderItems :: [(ByteString, Maybe ByteString)] -> [(ByteString, ByteString)] Source #
genNonce :: IO ByteString Source #
data ServerAuthorizationCheck Source #
Whether the client wants to check the received
Server-Authorization
header depends on the application.
:: 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.
authenticate' :: Response body -> Credentials -> HeaderArtifacts -> Maybe ByteString -> ServerAuthorizationCheck -> POSIXTime -> Either String (Maybe ServerAuthorizationHeader) Source #
responseHeader :: HeaderName -> Response body -> Maybe ByteString Source #
checkWwwAuthenticateHeader :: Credentials -> ByteString -> Either String (Maybe POSIXTime) Source #
The protocol relies on a clock sync between the client and server. To accomplish this, the server informs the client of its current time when an invalid timestamp is received.
If an attacker is able to manipulate this information and cause the client to use an incorrect time, it would be able to cause the client to generate authenticated requests using time in the future. Such requests will fail when sent by the client, and will not likely leave a trace on the server (given the common implementation of nonce, if at all enforced). The attacker will then be able to replay the request at the correct time without detection.
The client must only use the time information provided by the server if:
- it was delivered over a TLS connection and the server identity has been verified, or
- the
tsm
MAC digest calculated using the same client credentials over the timestamp has been verified.
checkServerAuthorizationHeader :: Credentials -> HeaderArtifacts -> ServerAuthorizationCheck -> POSIXTime -> Maybe ByteString -> Either String (Maybe ServerAuthorizationHeader) Source #
responseArtifacts :: ServerAuthorizationHeader -> HeaderArtifacts -> HeaderArtifacts Source #
Updates the artifacts which were used for client authentication with values from there server's response.
:: 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.
bewitArtifacts :: ByteString -> POSIXTime -> Maybe ExtData -> Maybe HeaderArtifacts Source #
encodeBewit :: Credentials -> HeaderArtifacts -> ByteString Source #
bewitString :: ClientId -> POSIXTime -> ByteString -> Maybe ExtData -> ByteString Source #
Constructs a bewit: idexpmacext
:: 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.
data HawkException Source #
Client exceptions specific to Hawk.
HawkServerAuthorizationException String | The returned |
:: (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.
withHawkPayload :: (MonadIO m, MonadCatch m) => Credentials -> Maybe ExtData -> PayloadInfo -> ServerAuthorizationCheck -> (Request -> m (Response body)) -> Request -> m (Response body) Source #
withHawkBase :: (MonadIO m, MonadThrow m, MonadCatch m) => Credentials -> Maybe ExtData -> Maybe PayloadInfo -> ServerAuthorizationCheck -> (Request -> m (Response body)) -> Request -> m (Response body) Source #
Makes a Hawk signed request. If the server responds saying "Stale timestamp", then retry using an adjusted timestamp.
makeExpiryHandler :: MonadCatch m => Credentials -> Request -> m a -> m (Either NominalDiffTime a) Source #
doSignedRequest :: (MonadIO m, MonadThrow m) => NominalDiffTime -> Credentials -> Maybe ExtData -> Maybe PayloadInfo -> ServerAuthorizationCheck -> (Request -> m (Response body)) -> Request -> m (Response body) Source #
Signs a request, runs it, then authenticates the response.
authResponse :: MonadIO m => Credentials -> HeaderArtifacts -> ServerAuthorizationCheck -> Response body -> m (Either String (Maybe ServerAuthorizationHeader)) Source #
Authenticates the server's response if required.
wasStale :: Request -> Response () -> Credentials -> Maybe NominalDiffTime Source #
hawkTs :: Credentials -> ResponseHeaders -> Maybe POSIXTime Source #
Gets the WWW-Authenticate header value and returns the server timestamp, if the response contains an authenticated timestamp.