module SAML2.XML.ASN1 where import Control.Arrow (left) import Data.ASN1.Types (ASN1, ASN1Object(..)) import Data.ASN1.BinaryEncoding (BER(BER), DER(DER)) import Data.ASN1.Encoding (decodeASN1', encodeASN1') import qualified Data.X509 as X509 import qualified Text.XML.HXT.Arrow.Pickle.Xml.Invertible as XP import qualified SAML2.XML.Schema as XS xpASN1 :: XP.PU [ASN1] xpASN1 :: PU [ASN1] xpASN1 = (ByteString -> Either String [ASN1], [ASN1] -> ByteString) -> PU ByteString -> PU [ASN1] forall a b. (a -> Either String b, b -> a) -> PU a -> PU b XP.xpWrapEither ( (ASN1Error -> String) -> Either ASN1Error [ASN1] -> Either String [ASN1] forall b c d. (b -> c) -> Either b d -> Either c d forall (a :: * -> * -> *) b c d. ArrowChoice a => a b c -> a (Either b d) (Either c d) left ASN1Error -> String forall a. Show a => a -> String show (Either ASN1Error [ASN1] -> Either String [ASN1]) -> (ByteString -> Either ASN1Error [ASN1]) -> ByteString -> Either String [ASN1] forall b c a. (b -> c) -> (a -> b) -> a -> c . BER -> ByteString -> Either ASN1Error [ASN1] forall a. ASN1Decoding a => a -> ByteString -> Either ASN1Error [ASN1] decodeASN1' BER BER , DER -> [ASN1] -> ByteString forall a. ASN1Encoding a => a -> [ASN1] -> ByteString encodeASN1' DER DER ) PU ByteString XS.xpBase64Binary xpASN1Object :: ASN1Object a => XP.PU a xpASN1Object :: forall a. ASN1Object a => PU a xpASN1Object = ([ASN1] -> Either String a, a -> [ASN1]) -> PU [ASN1] -> PU a forall a b. (a -> Either String b, b -> a) -> PU a -> PU b XP.xpWrapEither ( (String -> Either String a) -> ((a, [ASN1]) -> Either String a) -> Either String (a, [ASN1]) -> Either String a forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either String -> Either String a forall a b. a -> Either a b Left (a, [ASN1]) -> Either String a forall {b} {a}. (b, [a]) -> Either String b check (Either String (a, [ASN1]) -> Either String a) -> ([ASN1] -> Either String (a, [ASN1])) -> [ASN1] -> Either String a forall b c a. (b -> c) -> (a -> b) -> a -> c . [ASN1] -> Either String (a, [ASN1]) forall a. ASN1Object a => [ASN1] -> Either String (a, [ASN1]) fromASN1 , (a -> ASN1S forall a. ASN1Object a => a -> ASN1S `toASN1` []) ) PU [ASN1] xpASN1 where check :: (b, [a]) -> Either String b check (b x, []) = b -> Either String b forall a b. b -> Either a b Right b x check (b, [a]) _ = String -> Either String b forall a b. a -> Either a b Left String "trailing ASN1 data" xpX509Signed :: (Show a, Eq a, ASN1Object a) => XP.PU (X509.SignedExact a) xpX509Signed :: forall a. (Show a, Eq a, ASN1Object a) => PU (SignedExact a) xpX509Signed = (ByteString -> Either String (SignedExact a), SignedExact a -> ByteString) -> PU ByteString -> PU (SignedExact a) forall a b. (a -> Either String b, b -> a) -> PU a -> PU b XP.xpWrapEither ( ByteString -> Either String (SignedExact a) forall a. (Show a, Eq a, ASN1Object a) => ByteString -> Either String (SignedExact a) X509.decodeSignedObject , SignedExact a -> ByteString forall a. (Show a, Eq a, ASN1Object a) => SignedExact a -> ByteString X509.encodeSignedObject ) PU ByteString XS.xpBase64Binary