| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
SAML2.XML.Signature
Description
XML Signature Syntax and Processing
http://www.w3.org/TR/2008/REC-xmldsig-core-20080610/ (selected portions)
Documentation
module SAML2.XML.Signature.Types
data SigningKey Source #
Constructors
| SigningKeyDSA KeyPair | |
| SigningKeyRSA KeyPair |
Instances
| Eq SigningKey Source # | |
Defined in SAML2.XML.Signature | |
| Show SigningKey Source # | |
Defined in SAML2.XML.Signature Methods showsPrec :: Int -> SigningKey -> ShowS # show :: SigningKey -> String # showList :: [SigningKey] -> ShowS # | |
data PublicKeys Source #
Constructors
| PublicKeys | |
Fields | |
Instances
| Eq PublicKeys Source # | |
Defined in SAML2.XML.Signature | |
| Show PublicKeys Source # | |
Defined in SAML2.XML.Signature Methods showsPrec :: Int -> PublicKeys -> ShowS # show :: PublicKeys -> String # showList :: [PublicKeys] -> ShowS # | |
| Semigroup PublicKeys Source # | |
Defined in SAML2.XML.Signature Methods (<>) :: PublicKeys -> PublicKeys -> PublicKeys # sconcat :: NonEmpty PublicKeys -> PublicKeys # stimes :: Integral b => b -> PublicKeys -> PublicKeys # | |
| Monoid PublicKeys Source # | |
Defined in SAML2.XML.Signature Methods mempty :: PublicKeys # mappend :: PublicKeys -> PublicKeys -> PublicKeys # mconcat :: [PublicKeys] -> PublicKeys # | |
signBase64 :: SigningKey -> ByteString -> IO ByteString Source #
verifyBase64 :: PublicKeys -> IdentifiedURI SignatureAlgorithm -> ByteString -> ByteString -> Maybe Bool Source #
generateSignature :: SigningKey -> SignedInfo -> IO Signature Source #
verifySignature :: PublicKeys -> String -> XmlTree -> IO (Maybe Bool) Source #