| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Signet
Synopsis
- verifyWebhookText :: (MonadIO m, MonadThrow m) => Text -> Text -> Text -> Text -> Text -> m Signature
- verifyWebhookByteString :: (MonadIO m, MonadThrow m) => ByteString -> ByteString -> ByteString -> ByteString -> ByteString -> m Signature
- verifyWebhook :: (MonadIO m, MonadThrow m) => Verifier -> Message -> Signatures -> m Signature
- verifyWebhookWith :: Tolerance -> UTCTime -> Verifier -> Message -> Signatures -> Either SignetException Signature
- signWebhook :: Signer -> Message -> Signature
- hWebhookId :: HeaderName
- hWebhookTimestamp :: HeaderName
- hWebhookSignature :: HeaderName
- newtype AsymmetricSignature = MkAsymmetricSignature Signature
- newtype Id = MkId ByteString
- parseId :: ByteString -> Either InvalidId Id
- data Message = MkMessage {}
- parseMessage :: ByteString -> Either InvalidMessage Message
- newtype Payload = MkPayload ByteString
- newtype PublicKey = MkPublicKey PublicKey
- newtype Secret = MkSecret ScrubbedBytes
- newtype SecretKey = MkSecretKey SecretKey
- data Signature where
- pattern AsymmetricSignature :: AsymmetricSignature -> Signature
- pattern SymmetricSignature :: SymmetricSignature -> Signature
- newtype Signatures = MkSignatures [Signature]
- parseSignatures :: ByteString -> Either InvalidSignature ([UnknownSignature], Signatures)
- data Signer where
- pattern AsymmetricSigner :: SecretKey -> Signer
- pattern SymmetricSigner :: Secret -> Signer
- parseSigner :: ByteString -> Either InvalidSigner Signer
- newtype SymmetricSignature = MkSymmetricSignature (Digest SHA256)
- newtype Timestamp = MkTimestamp UTCTime
- parseTimestamp :: ByteString -> Either InvalidTimestamp Timestamp
- newtype Tolerance = MkTolerance NominalDiffTime
- typicalTolerance :: Tolerance
- data Verifier where
- pattern AsymmetricVerifier :: PublicKey -> Verifier
- pattern SymmetricVerifier :: Secret -> Verifier
- parseVerifier :: ByteString -> Either InvalidVerifier Verifier
- newtype InvalidAsymmetricSignature = MkInvalidAsymmetricSignature ByteString
- newtype InvalidId = MkInvalidId ByteString
- data InvalidMessage
- newtype InvalidPublicKey = MkInvalidPublicKey ByteString
- newtype InvalidSecret = MkInvalidSecret ByteString
- newtype InvalidSecretKey = MkInvalidSecretKey ByteString
- data InvalidSignature
- newtype InvalidSigner = MkInvalidSigner ByteString
- newtype InvalidSymmetricSignature = MkInvalidSymmetricSignature ByteString
- newtype InvalidTimestamp = MkInvalidTimestamp ByteString
- newtype InvalidVerifier = MkInvalidVerifier ByteString
- data SignetException
- newtype ToleranceException = MkToleranceException Timestamp
- newtype UnknownSignature = MkUnknownSignature ByteString
- newtype VerificationException = MkVerificationException Id
Verification
Arguments
| :: (MonadIO m, MonadThrow m) | |
| => Text | A |
| -> Text | The webhook's unique |
| -> Text | The webhook's |
| -> Text | The webhook's raw |
| -> Text | The webhook's |
| -> m Signature |
Verifies a webhook with Text values. This is a wrapper around
verifyWebhookByteString that assumes all values are encoded as UTF-8.
verifyWebhookByteString Source #
Arguments
| :: (MonadIO m, MonadThrow m) | |
| => ByteString | |
| -> ByteString | |
| -> ByteString | |
| -> ByteString | |
| -> ByteString | |
| -> m Signature |
Verifies a webhook with ByteString values. This is a
wrapper around verifyWebhook. See verifyWebhookText for a description of
the arguments.
verifyWebhook :: (MonadIO m, MonadThrow m) => Verifier -> Message -> Signatures -> m Signature Source #
Verifies a webhook. This is a wrapper around verifyWebhookWith that uses
typicalTolerance and the current time.
Throws an exception if the webhook is invalid.
Arguments
| :: Tolerance | Often |
| -> UTCTime | Usually |
| -> Verifier | See |
| -> Message | See |
| -> Signatures | See |
| -> Either SignetException Signature |
Verifies a webhook. This is the lowest-level function that gives you the
most control. If you're looking for something that's easier to use and
assumes some reasonable defaults, consider verifyWebhook.
Signing
Headers
Types
newtype AsymmetricSignature Source #
Constructors
| MkAsymmetricSignature Signature |
Instances
| Show AsymmetricSignature Source # | |
Defined in Signet.Unstable.Type.AsymmetricSignature Methods showsPrec :: Int -> AsymmetricSignature -> ShowS # show :: AsymmetricSignature -> String # showList :: [AsymmetricSignature] -> ShowS # | |
| Eq AsymmetricSignature Source # | |
Defined in Signet.Unstable.Type.AsymmetricSignature Methods (==) :: AsymmetricSignature -> AsymmetricSignature -> Bool # (/=) :: AsymmetricSignature -> AsymmetricSignature -> Bool # | |
Constructors
| MkId ByteString |
parseMessage :: ByteString -> Either InvalidMessage Message Source #
Alias for parse.
Constructors
| MkSecret ScrubbedBytes |
Instances
Bundled Patterns
| pattern AsymmetricSignature :: AsymmetricSignature -> Signature | Alias for |
| pattern SymmetricSignature :: SymmetricSignature -> Signature | Alias for |
newtype Signatures Source #
Constructors
| MkSignatures [Signature] |
Instances
| Show Signatures Source # | |
Defined in Signet.Unstable.Type.Signatures Methods showsPrec :: Int -> Signatures -> ShowS # show :: Signatures -> String # showList :: [Signatures] -> ShowS # | |
| Eq Signatures Source # | |
Defined in Signet.Unstable.Type.Signatures | |
parseSignatures :: ByteString -> Either InvalidSignature ([UnknownSignature], Signatures) Source #
Alias for parse.
Bundled Patterns
| pattern AsymmetricSigner :: SecretKey -> Signer | Alias for |
| pattern SymmetricSigner :: Secret -> Signer | Alias for |
Instances
parseSigner :: ByteString -> Either InvalidSigner Signer Source #
Alias for parse.
newtype SymmetricSignature Source #
Constructors
| MkSymmetricSignature (Digest SHA256) |
Instances
| Show SymmetricSignature Source # | |
Defined in Signet.Unstable.Type.SymmetricSignature Methods showsPrec :: Int -> SymmetricSignature -> ShowS # show :: SymmetricSignature -> String # showList :: [SymmetricSignature] -> ShowS # | |
| Eq SymmetricSignature Source # | |
Defined in Signet.Unstable.Type.SymmetricSignature Methods (==) :: SymmetricSignature -> SymmetricSignature -> Bool # (/=) :: SymmetricSignature -> SymmetricSignature -> Bool # | |
parseTimestamp :: ByteString -> Either InvalidTimestamp Timestamp Source #
Alias for parse.
Constructors
| MkTolerance NominalDiffTime |
typicalTolerance :: Tolerance Source #
Alias for typical.
Bundled Patterns
| pattern AsymmetricVerifier :: PublicKey -> Verifier | Alias for |
| pattern SymmetricVerifier :: Secret -> Verifier | Alias for |
parseVerifier :: ByteString -> Either InvalidVerifier Verifier Source #
Alias for parse.
Exceptions
newtype InvalidAsymmetricSignature Source #
Constructors
| MkInvalidAsymmetricSignature ByteString |
Instances
Constructors
| MkInvalidId ByteString |
Instances
| Exception InvalidId Source # | |
Defined in Signet.Unstable.Exception.InvalidId Methods toException :: InvalidId -> SomeException # fromException :: SomeException -> Maybe InvalidId # displayException :: InvalidId -> String # backtraceDesired :: InvalidId -> Bool # | |
| Show InvalidId Source # | |
| Eq InvalidId Source # | |
data InvalidMessage Source #
Constructors
| InvalidId InvalidId | |
| InvalidTimestamp InvalidTimestamp |
Instances
| Exception InvalidMessage Source # | |
Defined in Signet.Unstable.Exception.InvalidMessage Methods toException :: InvalidMessage -> SomeException # fromException :: SomeException -> Maybe InvalidMessage # displayException :: InvalidMessage -> String # backtraceDesired :: InvalidMessage -> Bool # | |
| Show InvalidMessage Source # | |
Defined in Signet.Unstable.Exception.InvalidMessage Methods showsPrec :: Int -> InvalidMessage -> ShowS # show :: InvalidMessage -> String # showList :: [InvalidMessage] -> ShowS # | |
| Eq InvalidMessage Source # | |
Defined in Signet.Unstable.Exception.InvalidMessage Methods (==) :: InvalidMessage -> InvalidMessage -> Bool # (/=) :: InvalidMessage -> InvalidMessage -> Bool # | |
newtype InvalidPublicKey Source #
Constructors
| MkInvalidPublicKey ByteString |
Instances
| Exception InvalidPublicKey Source # | |
Defined in Signet.Unstable.Exception.InvalidPublicKey Methods toException :: InvalidPublicKey -> SomeException # fromException :: SomeException -> Maybe InvalidPublicKey # | |
| Show InvalidPublicKey Source # | |
Defined in Signet.Unstable.Exception.InvalidPublicKey Methods showsPrec :: Int -> InvalidPublicKey -> ShowS # show :: InvalidPublicKey -> String # showList :: [InvalidPublicKey] -> ShowS # | |
| Eq InvalidPublicKey Source # | |
Defined in Signet.Unstable.Exception.InvalidPublicKey Methods (==) :: InvalidPublicKey -> InvalidPublicKey -> Bool # (/=) :: InvalidPublicKey -> InvalidPublicKey -> Bool # | |
newtype InvalidSecret Source #
Constructors
| MkInvalidSecret ByteString |
Instances
| Exception InvalidSecret Source # | |
Defined in Signet.Unstable.Exception.InvalidSecret Methods toException :: InvalidSecret -> SomeException # fromException :: SomeException -> Maybe InvalidSecret # displayException :: InvalidSecret -> String # backtraceDesired :: InvalidSecret -> Bool # | |
| Show InvalidSecret Source # | |
Defined in Signet.Unstable.Exception.InvalidSecret Methods showsPrec :: Int -> InvalidSecret -> ShowS # show :: InvalidSecret -> String # showList :: [InvalidSecret] -> ShowS # | |
| Eq InvalidSecret Source # | |
Defined in Signet.Unstable.Exception.InvalidSecret Methods (==) :: InvalidSecret -> InvalidSecret -> Bool # (/=) :: InvalidSecret -> InvalidSecret -> Bool # | |
newtype InvalidSecretKey Source #
Constructors
| MkInvalidSecretKey ByteString |
Instances
| Exception InvalidSecretKey Source # | |
Defined in Signet.Unstable.Exception.InvalidSecretKey Methods toException :: InvalidSecretKey -> SomeException # fromException :: SomeException -> Maybe InvalidSecretKey # | |
| Show InvalidSecretKey Source # | |
Defined in Signet.Unstable.Exception.InvalidSecretKey Methods showsPrec :: Int -> InvalidSecretKey -> ShowS # show :: InvalidSecretKey -> String # showList :: [InvalidSecretKey] -> ShowS # | |
| Eq InvalidSecretKey Source # | |
Defined in Signet.Unstable.Exception.InvalidSecretKey Methods (==) :: InvalidSecretKey -> InvalidSecretKey -> Bool # (/=) :: InvalidSecretKey -> InvalidSecretKey -> Bool # | |
data InvalidSignature Source #
Constructors
| InvalidAsymmetricSignature InvalidAsymmetricSignature | |
| InvalidSymmetricSignature InvalidSymmetricSignature |
Instances
| Exception InvalidSignature Source # | |
Defined in Signet.Unstable.Exception.InvalidSignature Methods toException :: InvalidSignature -> SomeException # fromException :: SomeException -> Maybe InvalidSignature # | |
| Show InvalidSignature Source # | |
Defined in Signet.Unstable.Exception.InvalidSignature Methods showsPrec :: Int -> InvalidSignature -> ShowS # show :: InvalidSignature -> String # showList :: [InvalidSignature] -> ShowS # | |
| Eq InvalidSignature Source # | |
Defined in Signet.Unstable.Exception.InvalidSignature Methods (==) :: InvalidSignature -> InvalidSignature -> Bool # (/=) :: InvalidSignature -> InvalidSignature -> Bool # | |
newtype InvalidSigner Source #
Constructors
| MkInvalidSigner ByteString |
Instances
| Exception InvalidSigner Source # | |
Defined in Signet.Unstable.Exception.InvalidSigner Methods toException :: InvalidSigner -> SomeException # fromException :: SomeException -> Maybe InvalidSigner # displayException :: InvalidSigner -> String # backtraceDesired :: InvalidSigner -> Bool # | |
| Show InvalidSigner Source # | |
Defined in Signet.Unstable.Exception.InvalidSigner Methods showsPrec :: Int -> InvalidSigner -> ShowS # show :: InvalidSigner -> String # showList :: [InvalidSigner] -> ShowS # | |
| Eq InvalidSigner Source # | |
Defined in Signet.Unstable.Exception.InvalidSigner Methods (==) :: InvalidSigner -> InvalidSigner -> Bool # (/=) :: InvalidSigner -> InvalidSigner -> Bool # | |
newtype InvalidSymmetricSignature Source #
Constructors
| MkInvalidSymmetricSignature ByteString |
Instances
newtype InvalidTimestamp Source #
Constructors
| MkInvalidTimestamp ByteString |
Instances
| Exception InvalidTimestamp Source # | |
Defined in Signet.Unstable.Exception.InvalidTimestamp Methods toException :: InvalidTimestamp -> SomeException # fromException :: SomeException -> Maybe InvalidTimestamp # | |
| Show InvalidTimestamp Source # | |
Defined in Signet.Unstable.Exception.InvalidTimestamp Methods showsPrec :: Int -> InvalidTimestamp -> ShowS # show :: InvalidTimestamp -> String # showList :: [InvalidTimestamp] -> ShowS # | |
| Eq InvalidTimestamp Source # | |
Defined in Signet.Unstable.Exception.InvalidTimestamp Methods (==) :: InvalidTimestamp -> InvalidTimestamp -> Bool # (/=) :: InvalidTimestamp -> InvalidTimestamp -> Bool # | |
newtype InvalidVerifier Source #
Constructors
| MkInvalidVerifier ByteString |
Instances
| Exception InvalidVerifier Source # | |
Defined in Signet.Unstable.Exception.InvalidVerifier Methods toException :: InvalidVerifier -> SomeException # fromException :: SomeException -> Maybe InvalidVerifier # displayException :: InvalidVerifier -> String # backtraceDesired :: InvalidVerifier -> Bool # | |
| Show InvalidVerifier Source # | |
Defined in Signet.Unstable.Exception.InvalidVerifier Methods showsPrec :: Int -> InvalidVerifier -> ShowS # show :: InvalidVerifier -> String # showList :: [InvalidVerifier] -> ShowS # | |
| Eq InvalidVerifier Source # | |
Defined in Signet.Unstable.Exception.InvalidVerifier Methods (==) :: InvalidVerifier -> InvalidVerifier -> Bool # (/=) :: InvalidVerifier -> InvalidVerifier -> Bool # | |
data SignetException Source #
Instances
| Exception SignetException Source # | |
Defined in Signet.Unstable.Exception.SignetException Methods toException :: SignetException -> SomeException # fromException :: SomeException -> Maybe SignetException # displayException :: SignetException -> String # backtraceDesired :: SignetException -> Bool # | |
| Show SignetException Source # | |
Defined in Signet.Unstable.Exception.SignetException Methods showsPrec :: Int -> SignetException -> ShowS # show :: SignetException -> String # showList :: [SignetException] -> ShowS # | |
| Eq SignetException Source # | |
Defined in Signet.Unstable.Exception.SignetException Methods (==) :: SignetException -> SignetException -> Bool # (/=) :: SignetException -> SignetException -> Bool # | |
newtype ToleranceException Source #
Constructors
| MkToleranceException Timestamp |
Instances
| Exception ToleranceException Source # | |
Defined in Signet.Unstable.Exception.ToleranceException Methods toException :: ToleranceException -> SomeException # fromException :: SomeException -> Maybe ToleranceException # | |
| Show ToleranceException Source # | |
Defined in Signet.Unstable.Exception.ToleranceException Methods showsPrec :: Int -> ToleranceException -> ShowS # show :: ToleranceException -> String # showList :: [ToleranceException] -> ShowS # | |
| Eq ToleranceException Source # | |
Defined in Signet.Unstable.Exception.ToleranceException Methods (==) :: ToleranceException -> ToleranceException -> Bool # (/=) :: ToleranceException -> ToleranceException -> Bool # | |
newtype UnknownSignature Source #
Constructors
| MkUnknownSignature ByteString |
Instances
| Exception UnknownSignature Source # | |
Defined in Signet.Unstable.Exception.UnknownSignature Methods toException :: UnknownSignature -> SomeException # fromException :: SomeException -> Maybe UnknownSignature # | |
| Show UnknownSignature Source # | |
Defined in Signet.Unstable.Exception.UnknownSignature Methods showsPrec :: Int -> UnknownSignature -> ShowS # show :: UnknownSignature -> String # showList :: [UnknownSignature] -> ShowS # | |
| Eq UnknownSignature Source # | |
Defined in Signet.Unstable.Exception.UnknownSignature Methods (==) :: UnknownSignature -> UnknownSignature -> Bool # (/=) :: UnknownSignature -> UnknownSignature -> Bool # | |
newtype VerificationException Source #
Constructors
| MkVerificationException Id |
Instances
| Exception VerificationException Source # | |
| Show VerificationException Source # | |
Defined in Signet.Unstable.Exception.VerificationException Methods showsPrec :: Int -> VerificationException -> ShowS # show :: VerificationException -> String # showList :: [VerificationException] -> ShowS # | |
| Eq VerificationException Source # | |
Defined in Signet.Unstable.Exception.VerificationException Methods (==) :: VerificationException -> VerificationException -> Bool # (/=) :: VerificationException -> VerificationException -> Bool # | |