{-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module SAML2.Metadata.Metadata where
import Data.Foldable (fold)
import qualified Network.URI as URI
import qualified Text.XML.HXT.Arrow.Pickle.Schema as XPS
import qualified Text.XML.HXT.DOM.QualifiedName as HXT
import SAML2.Lens
import SAML2.XML
import qualified Text.XML.HXT.Arrow.Pickle.Xml.Invertible as XP
import qualified SAML2.XML.Schema as XS
import qualified SAML2.XML.Signature.Types as DS
import qualified SAML2.XML.Encryption as XEnc
import SAML2.Core.Namespaces
import SAML2.Core.Versioning
import SAML2.Core.Identifiers
import qualified SAML2.Core.Assertions as SAML
import SAML2.Bindings.Identifiers
ns :: Namespace
ns :: Namespace
ns = String -> URI -> Namespace
mkNamespace String
"md" (URI -> Namespace) -> URI -> Namespace
forall a b. (a -> b) -> a -> b
$ SAMLVersion -> [String] -> URI
samlURN SAMLVersion
SAML20 [String
"metadata"]
xpElem :: String -> XP.PU a -> XP.PU a
xpElem :: forall a. String -> PU a -> PU a
xpElem = Namespace -> String -> PU a -> PU a
forall a. Namespace -> String -> PU a -> PU a
xpTrimElemNS Namespace
ns
type EntityID = AnyURI
xpEntityID :: XP.PU EntityID
xpEntityID :: PU URI
xpEntityID = PU URI
XS.xpAnyURI
data Endpoint = Endpoint
{ Endpoint -> IdentifiedURI Binding
endpointBinding :: IdentifiedURI Binding
, Endpoint -> URI
endpointLocation :: AnyURI
, Endpoint -> Maybe URI
endpointResponseLocation :: Maybe AnyURI
, Endpoint -> Nodes
endpointAttrs :: Nodes
, Endpoint -> Nodes
endpointXML :: Nodes
} deriving (Endpoint -> Endpoint -> Bool
(Endpoint -> Endpoint -> Bool)
-> (Endpoint -> Endpoint -> Bool) -> Eq Endpoint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Endpoint -> Endpoint -> Bool
== :: Endpoint -> Endpoint -> Bool
$c/= :: Endpoint -> Endpoint -> Bool
/= :: Endpoint -> Endpoint -> Bool
Eq, Int -> Endpoint -> ShowS
[Endpoint] -> ShowS
Endpoint -> String
(Int -> Endpoint -> ShowS)
-> (Endpoint -> String) -> ([Endpoint] -> ShowS) -> Show Endpoint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Endpoint -> ShowS
showsPrec :: Int -> Endpoint -> ShowS
$cshow :: Endpoint -> String
show :: Endpoint -> String
$cshowList :: [Endpoint] -> ShowS
showList :: [Endpoint] -> ShowS
Show)
instance XP.XmlPickler Endpoint where
xpickle :: PU Endpoint
xpickle = [XP.biCase|
((((b, l), r), a), x) <-> Endpoint b l r a x|]
Bijection
(->)
((((IdentifiedURI Binding, URI), Maybe URI), Nodes), Nodes)
Endpoint
-> PU ((((IdentifiedURI Binding, URI), Maybe URI), Nodes), Nodes)
-> PU Endpoint
forall (f :: * -> *) a b. Functor f => (a <-> b) -> f a -> f b
XP.>$< (String -> PU (IdentifiedURI Binding) -> PU (IdentifiedURI Binding)
forall a. String -> PU a -> PU a
XP.xpAttr String
"Binding" PU (IdentifiedURI Binding)
forall a. XmlPickler a => PU a
XP.xpickle
PU (IdentifiedURI Binding)
-> PU URI -> PU (IdentifiedURI Binding, URI)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< String -> PU URI -> PU URI
forall a. String -> PU a -> PU a
XP.xpAttr String
"Location" PU URI
XS.xpAnyURI
PU (IdentifiedURI Binding, URI)
-> PU (Maybe URI) -> PU ((IdentifiedURI Binding, URI), Maybe URI)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< String -> PU URI -> PU (Maybe URI)
forall a. String -> PU a -> PU (Maybe a)
XP.xpAttrImplied String
"ResponseLocation" PU URI
XS.xpAnyURI
PU ((IdentifiedURI Binding, URI), Maybe URI)
-> PU Nodes
-> PU (((IdentifiedURI Binding, URI), Maybe URI), Nodes)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Nodes
XP.xpAnyAttrs
PU (((IdentifiedURI Binding, URI), Maybe URI), Nodes)
-> PU Nodes
-> PU ((((IdentifiedURI Binding, URI), Maybe URI), Nodes), Nodes)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU (NTree XNode) -> PU Nodes
forall a. PU a -> PU [a]
XP.xpList PU (NTree XNode)
xpTrimAnyElem)
data IndexedEndpoint = IndexedEndpoint
{ IndexedEndpoint -> Endpoint
indexedEndpoint :: Endpoint
, IndexedEndpoint -> UnsignedShort
indexedEndpointIndex :: XS.UnsignedShort
, IndexedEndpoint -> Bool
indexedEndpointIsDefault :: XS.Boolean
} deriving (IndexedEndpoint -> IndexedEndpoint -> Bool
(IndexedEndpoint -> IndexedEndpoint -> Bool)
-> (IndexedEndpoint -> IndexedEndpoint -> Bool)
-> Eq IndexedEndpoint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IndexedEndpoint -> IndexedEndpoint -> Bool
== :: IndexedEndpoint -> IndexedEndpoint -> Bool
$c/= :: IndexedEndpoint -> IndexedEndpoint -> Bool
/= :: IndexedEndpoint -> IndexedEndpoint -> Bool
Eq, Int -> IndexedEndpoint -> ShowS
[IndexedEndpoint] -> ShowS
IndexedEndpoint -> String
(Int -> IndexedEndpoint -> ShowS)
-> (IndexedEndpoint -> String)
-> ([IndexedEndpoint] -> ShowS)
-> Show IndexedEndpoint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IndexedEndpoint -> ShowS
showsPrec :: Int -> IndexedEndpoint -> ShowS
$cshow :: IndexedEndpoint -> String
show :: IndexedEndpoint -> String
$cshowList :: [IndexedEndpoint] -> ShowS
showList :: [IndexedEndpoint] -> ShowS
Show)
instance XP.XmlPickler IndexedEndpoint where
xpickle :: PU IndexedEndpoint
xpickle = [XP.biCase|
((i, d), e) <-> IndexedEndpoint e i d|]
Bijection (->) ((UnsignedShort, Bool), Endpoint) IndexedEndpoint
-> PU ((UnsignedShort, Bool), Endpoint) -> PU IndexedEndpoint
forall (f :: * -> *) a b. Functor f => (a <-> b) -> f a -> f b
XP.>$< (String -> PU UnsignedShort -> PU UnsignedShort
forall a. String -> PU a -> PU a
XP.xpAttr String
"index" PU UnsignedShort
XS.xpUnsignedShort
PU UnsignedShort -> PU Bool -> PU (UnsignedShort, Bool)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< Bool -> PU Bool -> PU Bool
forall a. Eq a => a -> PU a -> PU a
XP.xpDefault Bool
False (String -> PU Bool -> PU Bool
forall a. String -> PU a -> PU a
XP.xpAttr String
"isDefault" PU Bool
XS.xpBoolean)
PU (UnsignedShort, Bool)
-> PU Endpoint -> PU ((UnsignedShort, Bool), Endpoint)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Endpoint
forall a. XmlPickler a => PU a
XP.xpickle)
data Localized a = Localized
{ forall a. Localized a -> String
localizedLang :: XS.Language
, forall a. Localized a -> a
localized :: a
} deriving (Localized a -> Localized a -> Bool
(Localized a -> Localized a -> Bool)
-> (Localized a -> Localized a -> Bool) -> Eq (Localized a)
forall a. Eq a => Localized a -> Localized a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => Localized a -> Localized a -> Bool
== :: Localized a -> Localized a -> Bool
$c/= :: forall a. Eq a => Localized a -> Localized a -> Bool
/= :: Localized a -> Localized a -> Bool
Eq, Int -> Localized a -> ShowS
[Localized a] -> ShowS
Localized a -> String
(Int -> Localized a -> ShowS)
-> (Localized a -> String)
-> ([Localized a] -> ShowS)
-> Show (Localized a)
forall a. Show a => Int -> Localized a -> ShowS
forall a. Show a => [Localized a] -> ShowS
forall a. Show a => Localized a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Localized a -> ShowS
showsPrec :: Int -> Localized a -> ShowS
$cshow :: forall a. Show a => Localized a -> String
show :: Localized a -> String
$cshowList :: forall a. Show a => [Localized a] -> ShowS
showList :: [Localized a] -> ShowS
Show)
xpLocalized :: XP.PU a -> XP.PU (Localized a)
xpLocalized :: forall a. PU a -> PU (Localized a)
xpLocalized PU a
p = [XP.biCase|
(l, x) <-> Localized l x|]
Bijection (->) (String, a) (Localized a)
-> PU (String, a) -> PU (Localized a)
forall (f :: * -> *) a b. Functor f => (a <-> b) -> f a -> f b
XP.>$< (PU String
xpXmlLang
PU String -> PU a -> PU (String, a)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU a
p)
type LocalizedName = Localized XS.String
instance XP.XmlPickler LocalizedName where
xpickle :: PU LocalizedName
xpickle = PU String -> PU LocalizedName
forall a. PU a -> PU (Localized a)
xpLocalized PU String
XS.xpString
type LocalizedURI = Localized XS.AnyURI
instance XP.XmlPickler LocalizedURI where
xpickle :: PU LocalizedURI
xpickle = PU URI -> PU LocalizedURI
forall a. PU a -> PU (Localized a)
xpLocalized PU URI
XS.xpAnyURI
data Metadata
= EntityDescriptor
{ Metadata -> URI
entityID :: EntityID
, Metadata -> Maybe String
metadataID :: Maybe XS.ID
, Metadata -> Maybe DateTime
metadataValidUntil :: Maybe XS.DateTime
, Metadata -> Maybe Duration
metadataCacheDuration :: Maybe XS.Duration
, Metadata -> Nodes
entityAttrs :: Nodes
, Metadata -> Maybe Signature
metadataSignature :: Maybe DS.Signature
, Metadata -> Extensions
metadataExtensions :: Extensions
, Metadata -> Descriptors
entityDescriptors :: Descriptors
, Metadata -> Maybe Organization
entityOrganization :: Maybe Organization
, Metadata -> [Contact]
entityContactPerson :: [Contact]
, Metadata -> [AdditionalMetadataLocation]
entityAditionalMetadataLocation :: [AdditionalMetadataLocation]
}
| EntitiesDescriptor
{ metadataID :: Maybe XS.ID
, metadataValidUntil :: Maybe XS.DateTime
, metadataCacheDuration :: Maybe XS.Duration
, Metadata -> Maybe String
entitiesName :: Maybe XS.String
, metadataSignature :: Maybe DS.Signature
, metadataExtensions :: Extensions
, Metadata -> List1 Metadata
entities :: List1 Metadata
}
deriving (Metadata -> Metadata -> Bool
(Metadata -> Metadata -> Bool)
-> (Metadata -> Metadata -> Bool) -> Eq Metadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Metadata -> Metadata -> Bool
== :: Metadata -> Metadata -> Bool
$c/= :: Metadata -> Metadata -> Bool
/= :: Metadata -> Metadata -> Bool
Eq, Int -> Metadata -> ShowS
[Metadata] -> ShowS
Metadata -> String
(Int -> Metadata -> ShowS)
-> (Metadata -> String) -> ([Metadata] -> ShowS) -> Show Metadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Metadata -> ShowS
showsPrec :: Int -> Metadata -> ShowS
$cshow :: Metadata -> String
show :: Metadata -> String
$cshowList :: [Metadata] -> ShowS
showList :: [Metadata] -> ShowS
Show)
instance XP.XmlPickler Metadata where
xpickle :: PU Metadata
xpickle = [XP.biCase|
Left ((((((((((e, i), vu), cd), xa), sig), ext), desc), org), cp), aml) <-> EntityDescriptor e i vu cd xa sig ext desc org cp aml
Right ((((((i, vu), cd), n), sig), ext), l) <-> EntitiesDescriptor i vu cd n sig ext l|]
Bijection
(->)
(Either
((((((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
Descriptors),
Maybe Organization),
[Contact]),
[AdditionalMetadataLocation])
((((((Maybe String, Maybe DateTime), Maybe Duration),
Maybe String),
Maybe Signature),
Extensions),
List1 Metadata))
Metadata
-> PU
(Either
((((((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
Descriptors),
Maybe Organization),
[Contact]),
[AdditionalMetadataLocation])
((((((Maybe String, Maybe DateTime), Maybe Duration),
Maybe String),
Maybe Signature),
Extensions),
List1 Metadata))
-> PU Metadata
forall (f :: * -> *) a b. Functor f => (a <-> b) -> f a -> f b
XP.>$< (String
-> PU
((((((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
Descriptors),
Maybe Organization),
[Contact]),
[AdditionalMetadataLocation])
-> PU
((((((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
Descriptors),
Maybe Organization),
[Contact]),
[AdditionalMetadataLocation])
forall a. String -> PU a -> PU a
xpElem String
"EntityDescriptor"
(String -> PU URI -> PU URI
forall a. String -> PU a -> PU a
XP.xpAttr String
"entityID" PU URI
xpEntityID
PU URI -> PU (Maybe String) -> PU (URI, Maybe String)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< String -> PU String -> PU (Maybe String)
forall a. String -> PU a -> PU (Maybe a)
XP.xpAttrImplied String
"ID" PU String
XS.xpID
PU (URI, Maybe String)
-> PU (Maybe DateTime) -> PU ((URI, Maybe String), Maybe DateTime)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< String -> PU DateTime -> PU (Maybe DateTime)
forall a. String -> PU a -> PU (Maybe a)
XP.xpAttrImplied String
"validUntil" PU DateTime
XS.xpDateTime
PU ((URI, Maybe String), Maybe DateTime)
-> PU (Maybe Duration)
-> PU (((URI, Maybe String), Maybe DateTime), Maybe Duration)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< String -> PU Duration -> PU (Maybe Duration)
forall a. String -> PU a -> PU (Maybe a)
XP.xpAttrImplied String
"cacheDuration" PU Duration
XS.xpDuration
PU (((URI, Maybe String), Maybe DateTime), Maybe Duration)
-> PU Nodes
-> PU
((((URI, Maybe String), Maybe DateTime), Maybe Duration), Nodes)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Nodes
XP.xpAnyAttrs
PU ((((URI, Maybe String), Maybe DateTime), Maybe Duration), Nodes)
-> PU (Maybe Signature)
-> PU
(((((URI, Maybe String), Maybe DateTime), Maybe Duration), Nodes),
Maybe Signature)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU (Maybe Signature)
forall a. XmlPickler a => PU a
XP.xpickle
PU
(((((URI, Maybe String), Maybe DateTime), Maybe Duration), Nodes),
Maybe Signature)
-> PU Extensions
-> PU
((((((URI, Maybe String), Maybe DateTime), Maybe Duration), Nodes),
Maybe Signature),
Extensions)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Extensions
forall a. XmlPickler a => PU a
XP.xpickle
PU
((((((URI, Maybe String), Maybe DateTime), Maybe Duration), Nodes),
Maybe Signature),
Extensions)
-> PU Descriptors
-> PU
(((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
Descriptors)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Descriptors
forall a. XmlPickler a => PU a
XP.xpickle
PU
(((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
Descriptors)
-> PU (Maybe Organization)
-> PU
((((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
Descriptors),
Maybe Organization)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU (Maybe Organization)
forall a. XmlPickler a => PU a
XP.xpickle
PU
((((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
Descriptors),
Maybe Organization)
-> PU [Contact]
-> PU
(((((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
Descriptors),
Maybe Organization),
[Contact])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Contact -> PU [Contact]
forall a. PU a -> PU [a]
XP.xpList PU Contact
forall a. XmlPickler a => PU a
XP.xpickle
PU
(((((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
Descriptors),
Maybe Organization),
[Contact])
-> PU [AdditionalMetadataLocation]
-> PU
((((((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
Descriptors),
Maybe Organization),
[Contact]),
[AdditionalMetadataLocation])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU AdditionalMetadataLocation -> PU [AdditionalMetadataLocation]
forall a. PU a -> PU [a]
XP.xpList PU AdditionalMetadataLocation
forall a. XmlPickler a => PU a
XP.xpickle)
PU
((((((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
Descriptors),
Maybe Organization),
[Contact]),
[AdditionalMetadataLocation])
-> PU
((((((Maybe String, Maybe DateTime), Maybe Duration),
Maybe String),
Maybe Signature),
Extensions),
List1 Metadata)
-> PU
(Either
((((((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
Descriptors),
Maybe Organization),
[Contact]),
[AdditionalMetadataLocation])
((((((Maybe String, Maybe DateTime), Maybe Duration),
Maybe String),
Maybe Signature),
Extensions),
List1 Metadata))
forall a b. PU a -> PU b -> PU (Either a b)
forall (f :: * -> *) a b.
MonoidalAlt f =>
f a -> f b -> f (Either a b)
XP.>|< String
-> PU
((((((Maybe String, Maybe DateTime), Maybe Duration),
Maybe String),
Maybe Signature),
Extensions),
List1 Metadata)
-> PU
((((((Maybe String, Maybe DateTime), Maybe Duration),
Maybe String),
Maybe Signature),
Extensions),
List1 Metadata)
forall a. String -> PU a -> PU a
xpElem String
"EntitiesDescriptor"
(String -> PU String -> PU (Maybe String)
forall a. String -> PU a -> PU (Maybe a)
XP.xpAttrImplied String
"ID" PU String
XS.xpID
PU (Maybe String)
-> PU (Maybe DateTime) -> PU (Maybe String, Maybe DateTime)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< String -> PU DateTime -> PU (Maybe DateTime)
forall a. String -> PU a -> PU (Maybe a)
XP.xpAttrImplied String
"validUntil" PU DateTime
XS.xpDateTime
PU (Maybe String, Maybe DateTime)
-> PU (Maybe Duration)
-> PU ((Maybe String, Maybe DateTime), Maybe Duration)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< String -> PU Duration -> PU (Maybe Duration)
forall a. String -> PU a -> PU (Maybe a)
XP.xpAttrImplied String
"cacheDuration" PU Duration
XS.xpDuration
PU ((Maybe String, Maybe DateTime), Maybe Duration)
-> PU (Maybe String)
-> PU
(((Maybe String, Maybe DateTime), Maybe Duration), Maybe String)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< String -> PU String -> PU (Maybe String)
forall a. String -> PU a -> PU (Maybe a)
XP.xpAttrImplied String
"Name" PU String
XS.xpString
PU (((Maybe String, Maybe DateTime), Maybe Duration), Maybe String)
-> PU (Maybe Signature)
-> PU
((((Maybe String, Maybe DateTime), Maybe Duration), Maybe String),
Maybe Signature)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU (Maybe Signature)
forall a. XmlPickler a => PU a
XP.xpickle
PU
((((Maybe String, Maybe DateTime), Maybe Duration), Maybe String),
Maybe Signature)
-> PU Extensions
-> PU
(((((Maybe String, Maybe DateTime), Maybe Duration), Maybe String),
Maybe Signature),
Extensions)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Extensions
forall a. XmlPickler a => PU a
XP.xpickle
PU
(((((Maybe String, Maybe DateTime), Maybe Duration), Maybe String),
Maybe Signature),
Extensions)
-> PU (List1 Metadata)
-> PU
((((((Maybe String, Maybe DateTime), Maybe Duration),
Maybe String),
Maybe Signature),
Extensions),
List1 Metadata)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Metadata -> PU (List1 Metadata)
forall a. PU a -> PU (List1 a)
xpList1 PU Metadata
forall a. XmlPickler a => PU a
XP.xpickle))
instance DS.Signable Metadata where
signature' :: Lens' Metadata (Maybe Signature)
signature' = $(fieldLens 'metadataSignature)
signedID :: Metadata -> String
signedID = Maybe String -> String
forall m. Monoid m => Maybe m -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold (Maybe String -> String)
-> (Metadata -> Maybe String) -> Metadata -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Metadata -> Maybe String
metadataID
newtype Extensions = Extensions{ Extensions -> Nodes
extensions :: Nodes }
deriving (Extensions -> Extensions -> Bool
(Extensions -> Extensions -> Bool)
-> (Extensions -> Extensions -> Bool) -> Eq Extensions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Extensions -> Extensions -> Bool
== :: Extensions -> Extensions -> Bool
$c/= :: Extensions -> Extensions -> Bool
/= :: Extensions -> Extensions -> Bool
Eq, Int -> Extensions -> ShowS
[Extensions] -> ShowS
Extensions -> String
(Int -> Extensions -> ShowS)
-> (Extensions -> String)
-> ([Extensions] -> ShowS)
-> Show Extensions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Extensions -> ShowS
showsPrec :: Int -> Extensions -> ShowS
$cshow :: Extensions -> String
show :: Extensions -> String
$cshowList :: [Extensions] -> ShowS
showList :: [Extensions] -> ShowS
Show
#if MIN_VERSION_base(4,11,0)
, NonEmpty Extensions -> Extensions
Extensions -> Extensions -> Extensions
(Extensions -> Extensions -> Extensions)
-> (NonEmpty Extensions -> Extensions)
-> (forall b. Integral b => b -> Extensions -> Extensions)
-> Semigroup Extensions
forall b. Integral b => b -> Extensions -> Extensions
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: Extensions -> Extensions -> Extensions
<> :: Extensions -> Extensions -> Extensions
$csconcat :: NonEmpty Extensions -> Extensions
sconcat :: NonEmpty Extensions -> Extensions
$cstimes :: forall b. Integral b => b -> Extensions -> Extensions
stimes :: forall b. Integral b => b -> Extensions -> Extensions
Semigroup
#endif
, Semigroup Extensions
Extensions
Semigroup Extensions =>
Extensions
-> (Extensions -> Extensions -> Extensions)
-> ([Extensions] -> Extensions)
-> Monoid Extensions
[Extensions] -> Extensions
Extensions -> Extensions -> Extensions
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
$cmempty :: Extensions
mempty :: Extensions
$cmappend :: Extensions -> Extensions -> Extensions
mappend :: Extensions -> Extensions -> Extensions
$cmconcat :: [Extensions] -> Extensions
mconcat :: [Extensions] -> Extensions
Monoid)
instance XP.XmlPickler Extensions where
xpickle :: PU Extensions
xpickle = Extensions -> PU Extensions -> PU Extensions
forall a. Eq a => a -> PU a -> PU a
XP.xpDefault (Nodes -> Extensions
Extensions []) (PU Extensions -> PU Extensions) -> PU Extensions -> PU Extensions
forall a b. (a -> b) -> a -> b
$
String -> PU Extensions -> PU Extensions
forall a. String -> PU a -> PU a
xpElem String
"Extensions" (PU Extensions -> PU Extensions) -> PU Extensions -> PU Extensions
forall a b. (a -> b) -> a -> b
$ [XP.biCase|
x <-> Extensions x|]
Bijection (->) Nodes Extensions -> PU Nodes -> PU Extensions
forall (f :: * -> *) a b. Functor f => (a <-> b) -> f a -> f b
XP.>$< (PU (NTree XNode) -> PU Nodes
forall a. PU a -> PU [a]
XP.xpList1 PU (NTree XNode)
xpTrimAnyElem)
data Descriptors
= Descriptors{ Descriptors -> List1 Descriptor
descriptors :: List1 Descriptor }
| AffiliationDescriptor
{ Descriptors -> URI
affiliationDescriptorAffiliationOwnerID :: EntityID
, Descriptors -> Maybe String
affiliationDescriptorID :: Maybe XS.ID
, Descriptors -> Maybe DateTime
affiliationDescriptorValidUntil :: Maybe XS.DateTime
, Descriptors -> Maybe Duration
affiliationDescriptorCacheDuration :: Maybe XS.Duration
, Descriptors -> Nodes
affiliationDescriptorAttrs :: Nodes
, Descriptors -> Maybe Signature
affiliationDescriptorSignature :: Maybe DS.Signature
, Descriptors -> Extensions
affiliationDescriptorExtensions :: Extensions
, Descriptors -> List1 URI
affiliationDescriptorAffiliateMember :: List1 EntityID
, Descriptors -> [KeyDescriptor]
affiliationDescriptorKeyDescriptor :: [KeyDescriptor]
}
deriving (Descriptors -> Descriptors -> Bool
(Descriptors -> Descriptors -> Bool)
-> (Descriptors -> Descriptors -> Bool) -> Eq Descriptors
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Descriptors -> Descriptors -> Bool
== :: Descriptors -> Descriptors -> Bool
$c/= :: Descriptors -> Descriptors -> Bool
/= :: Descriptors -> Descriptors -> Bool
Eq, Int -> Descriptors -> ShowS
[Descriptors] -> ShowS
Descriptors -> String
(Int -> Descriptors -> ShowS)
-> (Descriptors -> String)
-> ([Descriptors] -> ShowS)
-> Show Descriptors
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Descriptors -> ShowS
showsPrec :: Int -> Descriptors -> ShowS
$cshow :: Descriptors -> String
show :: Descriptors -> String
$cshowList :: [Descriptors] -> ShowS
showList :: [Descriptors] -> ShowS
Show)
instance XP.XmlPickler Descriptors where
xpickle :: PU Descriptors
xpickle = [XP.biCase|
Left l <-> Descriptors l
Right ((((((((o, i), vu), cd), a), sig), ext), am), kd) <-> AffiliationDescriptor o i vu cd a sig ext am kd|]
Bijection
(->)
(Either
(List1 Descriptor)
((((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
List1 URI),
[KeyDescriptor]))
Descriptors
-> PU
(Either
(List1 Descriptor)
((((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
List1 URI),
[KeyDescriptor]))
-> PU Descriptors
forall (f :: * -> *) a b. Functor f => (a <-> b) -> f a -> f b
XP.>$< (PU Descriptor -> PU (List1 Descriptor)
forall a. PU a -> PU (List1 a)
xpList1 PU Descriptor
forall a. XmlPickler a => PU a
XP.xpickle
PU (List1 Descriptor)
-> PU
((((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
List1 URI),
[KeyDescriptor])
-> PU
(Either
(List1 Descriptor)
((((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
List1 URI),
[KeyDescriptor]))
forall a b. PU a -> PU b -> PU (Either a b)
forall (f :: * -> *) a b.
MonoidalAlt f =>
f a -> f b -> f (Either a b)
XP.>|< String
-> PU
((((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
List1 URI),
[KeyDescriptor])
-> PU
((((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
List1 URI),
[KeyDescriptor])
forall a. String -> PU a -> PU a
xpElem String
"AffiliationDescriptor"
(String -> PU URI -> PU URI
forall a. String -> PU a -> PU a
XP.xpAttr String
"affiliationOwnerID" PU URI
xpEntityID
PU URI -> PU (Maybe String) -> PU (URI, Maybe String)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< String -> PU String -> PU (Maybe String)
forall a. String -> PU a -> PU (Maybe a)
XP.xpAttrImplied String
"ID" PU String
XS.xpID
PU (URI, Maybe String)
-> PU (Maybe DateTime) -> PU ((URI, Maybe String), Maybe DateTime)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< String -> PU DateTime -> PU (Maybe DateTime)
forall a. String -> PU a -> PU (Maybe a)
XP.xpAttrImplied String
"validUntil" PU DateTime
XS.xpDateTime
PU ((URI, Maybe String), Maybe DateTime)
-> PU (Maybe Duration)
-> PU (((URI, Maybe String), Maybe DateTime), Maybe Duration)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< String -> PU Duration -> PU (Maybe Duration)
forall a. String -> PU a -> PU (Maybe a)
XP.xpAttrImplied String
"cacheDuration" PU Duration
XS.xpDuration
PU (((URI, Maybe String), Maybe DateTime), Maybe Duration)
-> PU Nodes
-> PU
((((URI, Maybe String), Maybe DateTime), Maybe Duration), Nodes)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Nodes
XP.xpAnyAttrs
PU ((((URI, Maybe String), Maybe DateTime), Maybe Duration), Nodes)
-> PU (Maybe Signature)
-> PU
(((((URI, Maybe String), Maybe DateTime), Maybe Duration), Nodes),
Maybe Signature)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU (Maybe Signature)
forall a. XmlPickler a => PU a
XP.xpickle
PU
(((((URI, Maybe String), Maybe DateTime), Maybe Duration), Nodes),
Maybe Signature)
-> PU Extensions
-> PU
((((((URI, Maybe String), Maybe DateTime), Maybe Duration), Nodes),
Maybe Signature),
Extensions)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Extensions
forall a. XmlPickler a => PU a
XP.xpickle
PU
((((((URI, Maybe String), Maybe DateTime), Maybe Duration), Nodes),
Maybe Signature),
Extensions)
-> PU (List1 URI)
-> PU
(((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
List1 URI)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU URI -> PU (List1 URI)
forall a. PU a -> PU (List1 a)
xpList1 (String -> PU URI -> PU URI
forall a. String -> PU a -> PU a
xpElem String
"AffiliateMember" PU URI
xpEntityID)
PU
(((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
List1 URI)
-> PU [KeyDescriptor]
-> PU
((((((((URI, Maybe String), Maybe DateTime), Maybe Duration),
Nodes),
Maybe Signature),
Extensions),
List1 URI),
[KeyDescriptor])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU KeyDescriptor -> PU [KeyDescriptor]
forall a. PU a -> PU [a]
XP.xpList PU KeyDescriptor
forall a. XmlPickler a => PU a
XP.xpickle))
data Descriptor
= Descriptor
{ Descriptor -> RoleDescriptor
descriptorRole :: !RoleDescriptor
}
| ExtendedRoleDescriptor
{ Descriptor -> String
descriptorRoleExtensionType :: !(XS.String)
, descriptorRole :: !RoleDescriptor
, Descriptor -> Nodes
descriptorAdditionalNodes :: !Nodes
}
| IDPSSODescriptor
{ descriptorRole :: !RoleDescriptor
, :: !SSODescriptor
, Descriptor -> Bool
descriptorWantAuthnRequestsSigned :: XS.Boolean
, Descriptor -> List1 Endpoint
descriptorSingleSignOnService :: List1 Endpoint
, Descriptor -> [Endpoint]
descriptorNameIDMappingService :: [Endpoint]
, Descriptor -> [Endpoint]
descriptorAssertionIDRequestService :: [Endpoint]
, Descriptor -> [URI]
descriptorAttributeProfile :: [XS.AnyURI]
, Descriptor -> [Attribute]
descriptorAttribute :: [SAML.Attribute]
}
| SPSSODescriptor
{ descriptorRole :: !RoleDescriptor
, :: !SSODescriptor
, Descriptor -> Bool
descriptorAuthnRequestsSigned :: XS.Boolean
, Descriptor -> Bool
descriptorWantAssertionsSigned :: XS.Boolean
, Descriptor -> List1 IndexedEndpoint
descriptorAssertionConsumerService :: List1 IndexedEndpoint
, Descriptor -> [AttributeConsumingService]
descriptorAttributeConsumingService :: [AttributeConsumingService]
}
| AuthnAuthorityDescriptor
{ descriptorRole :: !RoleDescriptor
, Descriptor -> List1 Endpoint
descriptorAuthnQueryService :: List1 Endpoint
, descriptorAssertionIDRequestService :: [Endpoint]
, Descriptor -> [IdentifiedURI NameIDFormat]
descriptorNameIDFormat :: [IdentifiedURI NameIDFormat]
}
| AttributeAuthorityDescriptor
{ descriptorRole :: !RoleDescriptor
, Descriptor -> List1 Endpoint
descriptorAttributeService :: List1 Endpoint
, descriptorAssertionIDRequestService :: [Endpoint]
, descriptorNameIDFormat :: [IdentifiedURI NameIDFormat]
, descriptorAttributeProfile :: [XS.AnyURI]
, descriptorAttribute :: [SAML.Attribute]
}
| PDPDescriptor
{ descriptorRole :: !RoleDescriptor
, Descriptor -> List1 Endpoint
descriptorAuthzService :: List1 Endpoint
, descriptorAssertionIDRequestService :: [Endpoint]
, descriptorNameIDFormat :: [IdentifiedURI NameIDFormat]
}
deriving (Descriptor -> Descriptor -> Bool
(Descriptor -> Descriptor -> Bool)
-> (Descriptor -> Descriptor -> Bool) -> Eq Descriptor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Descriptor -> Descriptor -> Bool
== :: Descriptor -> Descriptor -> Bool
$c/= :: Descriptor -> Descriptor -> Bool
/= :: Descriptor -> Descriptor -> Bool
Eq, Int -> Descriptor -> ShowS
[Descriptor] -> ShowS
Descriptor -> String
(Int -> Descriptor -> ShowS)
-> (Descriptor -> String)
-> ([Descriptor] -> ShowS)
-> Show Descriptor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Descriptor -> ShowS
showsPrec :: Int -> Descriptor -> ShowS
$cshow :: Descriptor -> String
show :: Descriptor -> String
$cshowList :: [Descriptor] -> ShowS
showList :: [Descriptor] -> ShowS
Show)
xsiTypeQName :: HXT.QName
xsiTypeQName :: QName
xsiTypeQName = String -> String -> String -> QName
HXT.mkQName String
"xsi" String
"type" String
"http://www.w3.org/2001/XMLSchema-instance"
instance XP.XmlPickler Descriptor where
xpickle :: PU Descriptor
xpickle = [XP.biCase|
Left (Left (Left (Left (Left (Left ((t, rde), an)))))) <-> ExtendedRoleDescriptor t rde an
Left (Left (Left (Left (Left (Right r))))) <-> Descriptor r
Left (Left (Left (Left (Right (((((((ws, r), s), sso), nim), air), ap), a))))) <-> IDPSSODescriptor r s ws sso nim air ap a
Left (Left (Left (Right (((((a, w), r), s), e), t)))) <-> SPSSODescriptor r s a w e t
Left (Left (Right (((r, a), s), n))) <-> AuthnAuthorityDescriptor r a s n
Left (Right (((((r, a), s), n), tp), t)) <-> AttributeAuthorityDescriptor r a s n tp t
Right (((r, a), s), n) <-> PDPDescriptor r a s n|]
Bijection
(->)
(Either
(Either
(Either
(Either
(Either
(Either ((String, RoleDescriptor), Nodes) RoleDescriptor)
(((((((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint),
[Endpoint]),
[Endpoint]),
[URI]),
[Attribute]))
(((((Bool, Bool), RoleDescriptor), SSODescriptor),
List1 IndexedEndpoint),
[AttributeConsumingService]))
(((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat]))
(((((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat]),
[URI]),
[Attribute]))
(((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat]))
Descriptor
-> PU
(Either
(Either
(Either
(Either
(Either
(Either ((String, RoleDescriptor), Nodes) RoleDescriptor)
(((((((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint),
[Endpoint]),
[Endpoint]),
[URI]),
[Attribute]))
(((((Bool, Bool), RoleDescriptor), SSODescriptor),
List1 IndexedEndpoint),
[AttributeConsumingService]))
(((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat]))
(((((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat]),
[URI]),
[Attribute]))
(((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat]))
-> PU Descriptor
forall (f :: * -> *) a b. Functor f => (a <-> b) -> f a -> f b
XP.>$< (String
-> PU ((String, RoleDescriptor), Nodes)
-> PU ((String, RoleDescriptor), Nodes)
forall a. String -> PU a -> PU a
xpElem String
"RoleDescriptor"
(QName -> PU String -> PU String
forall a. QName -> PU a -> PU a
XP.xpAttrQN QName
xsiTypeQName PU String
XS.xpString
PU String -> PU RoleDescriptor -> PU (String, RoleDescriptor)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU RoleDescriptor
forall a. XmlPickler a => PU a
XP.xpickle
PU (String, RoleDescriptor)
-> PU Nodes -> PU ((String, RoleDescriptor), Nodes)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Nodes
XP.xpTrees)
PU ((String, RoleDescriptor), Nodes)
-> PU RoleDescriptor
-> PU (Either ((String, RoleDescriptor), Nodes) RoleDescriptor)
forall a b. PU a -> PU b -> PU (Either a b)
forall (f :: * -> *) a b.
MonoidalAlt f =>
f a -> f b -> f (Either a b)
XP.>|< String -> PU RoleDescriptor -> PU RoleDescriptor
forall a. String -> PU a -> PU a
xpElem String
"RoleDescriptor" PU RoleDescriptor
forall a. XmlPickler a => PU a
XP.xpickle
PU (Either ((String, RoleDescriptor), Nodes) RoleDescriptor)
-> PU
(((((((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint),
[Endpoint]),
[Endpoint]),
[URI]),
[Attribute])
-> PU
(Either
(Either ((String, RoleDescriptor), Nodes) RoleDescriptor)
(((((((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint),
[Endpoint]),
[Endpoint]),
[URI]),
[Attribute]))
forall a b. PU a -> PU b -> PU (Either a b)
forall (f :: * -> *) a b.
MonoidalAlt f =>
f a -> f b -> f (Either a b)
XP.>|< String
-> PU
(((((((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint),
[Endpoint]),
[Endpoint]),
[URI]),
[Attribute])
-> PU
(((((((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint),
[Endpoint]),
[Endpoint]),
[URI]),
[Attribute])
forall a. String -> PU a -> PU a
xpElem String
"IDPSSODescriptor"
(Bool -> PU Bool -> PU Bool
forall a. Eq a => a -> PU a -> PU a
XP.xpDefault Bool
False (String -> PU Bool -> PU Bool
forall a. String -> PU a -> PU a
XP.xpAttr String
"WantAuthnRequestsSigned" PU Bool
XS.xpBoolean)
PU Bool -> PU RoleDescriptor -> PU (Bool, RoleDescriptor)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU RoleDescriptor
forall a. XmlPickler a => PU a
XP.xpickle
PU (Bool, RoleDescriptor)
-> PU SSODescriptor -> PU ((Bool, RoleDescriptor), SSODescriptor)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU SSODescriptor
forall a. XmlPickler a => PU a
XP.xpickle
PU ((Bool, RoleDescriptor), SSODescriptor)
-> PU (List1 Endpoint)
-> PU (((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Endpoint -> PU (List1 Endpoint)
forall a. PU a -> PU (List1 a)
xpList1 (String -> PU Endpoint -> PU Endpoint
forall a. String -> PU a -> PU a
xpElem String
"SingleSignOnService" PU Endpoint
forall a. XmlPickler a => PU a
XP.xpickle)
PU (((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint)
-> PU [Endpoint]
-> PU
((((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint),
[Endpoint])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Endpoint -> PU [Endpoint]
forall a. PU a -> PU [a]
XP.xpList (String -> PU Endpoint -> PU Endpoint
forall a. String -> PU a -> PU a
xpElem String
"NameIDMappingService" PU Endpoint
forall a. XmlPickler a => PU a
XP.xpickle)
PU
((((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint),
[Endpoint])
-> PU [Endpoint]
-> PU
(((((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint),
[Endpoint]),
[Endpoint])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Endpoint -> PU [Endpoint]
forall a. PU a -> PU [a]
XP.xpList (String -> PU Endpoint -> PU Endpoint
forall a. String -> PU a -> PU a
xpElem String
"AssertionIDRequestService" PU Endpoint
forall a. XmlPickler a => PU a
XP.xpickle)
PU
(((((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint),
[Endpoint]),
[Endpoint])
-> PU [URI]
-> PU
((((((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint),
[Endpoint]),
[Endpoint]),
[URI])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU URI -> PU [URI]
forall a. PU a -> PU [a]
XP.xpList (String -> PU URI -> PU URI
forall a. String -> PU a -> PU a
xpElem String
"AttributeProfile" PU URI
XS.xpAnyURI)
PU
((((((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint),
[Endpoint]),
[Endpoint]),
[URI])
-> PU [Attribute]
-> PU
(((((((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint),
[Endpoint]),
[Endpoint]),
[URI]),
[Attribute])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Attribute -> PU [Attribute]
forall a. PU a -> PU [a]
XP.xpList PU Attribute
forall a. XmlPickler a => PU a
XP.xpickle)
PU
(Either
(Either ((String, RoleDescriptor), Nodes) RoleDescriptor)
(((((((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint),
[Endpoint]),
[Endpoint]),
[URI]),
[Attribute]))
-> PU
(((((Bool, Bool), RoleDescriptor), SSODescriptor),
List1 IndexedEndpoint),
[AttributeConsumingService])
-> PU
(Either
(Either
(Either ((String, RoleDescriptor), Nodes) RoleDescriptor)
(((((((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint),
[Endpoint]),
[Endpoint]),
[URI]),
[Attribute]))
(((((Bool, Bool), RoleDescriptor), SSODescriptor),
List1 IndexedEndpoint),
[AttributeConsumingService]))
forall a b. PU a -> PU b -> PU (Either a b)
forall (f :: * -> *) a b.
MonoidalAlt f =>
f a -> f b -> f (Either a b)
XP.>|< String
-> PU
(((((Bool, Bool), RoleDescriptor), SSODescriptor),
List1 IndexedEndpoint),
[AttributeConsumingService])
-> PU
(((((Bool, Bool), RoleDescriptor), SSODescriptor),
List1 IndexedEndpoint),
[AttributeConsumingService])
forall a. String -> PU a -> PU a
xpElem String
"SPSSODescriptor"
(Bool -> PU Bool -> PU Bool
forall a. Eq a => a -> PU a -> PU a
XP.xpDefault Bool
False (String -> PU Bool -> PU Bool
forall a. String -> PU a -> PU a
XP.xpAttr String
"AuthnRequestsSigned" PU Bool
XS.xpBoolean)
PU Bool -> PU Bool -> PU (Bool, Bool)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< Bool -> PU Bool -> PU Bool
forall a. Eq a => a -> PU a -> PU a
XP.xpDefault Bool
False (String -> PU Bool -> PU Bool
forall a. String -> PU a -> PU a
XP.xpAttr String
"WantAssertionsSigned" PU Bool
XS.xpBoolean)
PU (Bool, Bool)
-> PU RoleDescriptor -> PU ((Bool, Bool), RoleDescriptor)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU RoleDescriptor
forall a. XmlPickler a => PU a
XP.xpickle
PU ((Bool, Bool), RoleDescriptor)
-> PU SSODescriptor
-> PU (((Bool, Bool), RoleDescriptor), SSODescriptor)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU SSODescriptor
forall a. XmlPickler a => PU a
XP.xpickle
PU (((Bool, Bool), RoleDescriptor), SSODescriptor)
-> PU (List1 IndexedEndpoint)
-> PU
((((Bool, Bool), RoleDescriptor), SSODescriptor),
List1 IndexedEndpoint)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU IndexedEndpoint -> PU (List1 IndexedEndpoint)
forall a. PU a -> PU (List1 a)
xpList1 (String -> PU IndexedEndpoint -> PU IndexedEndpoint
forall a. String -> PU a -> PU a
xpElem String
"AssertionConsumerService" PU IndexedEndpoint
forall a. XmlPickler a => PU a
XP.xpickle)
PU
((((Bool, Bool), RoleDescriptor), SSODescriptor),
List1 IndexedEndpoint)
-> PU [AttributeConsumingService]
-> PU
(((((Bool, Bool), RoleDescriptor), SSODescriptor),
List1 IndexedEndpoint),
[AttributeConsumingService])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU AttributeConsumingService -> PU [AttributeConsumingService]
forall a. PU a -> PU [a]
XP.xpList PU AttributeConsumingService
forall a. XmlPickler a => PU a
XP.xpickle)
PU
(Either
(Either
(Either ((String, RoleDescriptor), Nodes) RoleDescriptor)
(((((((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint),
[Endpoint]),
[Endpoint]),
[URI]),
[Attribute]))
(((((Bool, Bool), RoleDescriptor), SSODescriptor),
List1 IndexedEndpoint),
[AttributeConsumingService]))
-> PU
(((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat])
-> PU
(Either
(Either
(Either
(Either ((String, RoleDescriptor), Nodes) RoleDescriptor)
(((((((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint),
[Endpoint]),
[Endpoint]),
[URI]),
[Attribute]))
(((((Bool, Bool), RoleDescriptor), SSODescriptor),
List1 IndexedEndpoint),
[AttributeConsumingService]))
(((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat]))
forall a b. PU a -> PU b -> PU (Either a b)
forall (f :: * -> *) a b.
MonoidalAlt f =>
f a -> f b -> f (Either a b)
XP.>|< String
-> PU
(((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat])
-> PU
(((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat])
forall a. String -> PU a -> PU a
xpElem String
"AuthnAuthorityDescriptor"
(PU RoleDescriptor
forall a. XmlPickler a => PU a
XP.xpickle
PU RoleDescriptor
-> PU (List1 Endpoint) -> PU (RoleDescriptor, List1 Endpoint)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Endpoint -> PU (List1 Endpoint)
forall a. PU a -> PU (List1 a)
xpList1 (String -> PU Endpoint -> PU Endpoint
forall a. String -> PU a -> PU a
xpElem String
"AuthnQueryService" PU Endpoint
forall a. XmlPickler a => PU a
XP.xpickle)
PU (RoleDescriptor, List1 Endpoint)
-> PU [Endpoint]
-> PU ((RoleDescriptor, List1 Endpoint), [Endpoint])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Endpoint -> PU [Endpoint]
forall a. PU a -> PU [a]
XP.xpList (String -> PU Endpoint -> PU Endpoint
forall a. String -> PU a -> PU a
xpElem String
"AssertionIDRequestService" PU Endpoint
forall a. XmlPickler a => PU a
XP.xpickle)
PU ((RoleDescriptor, List1 Endpoint), [Endpoint])
-> PU [IdentifiedURI NameIDFormat]
-> PU
(((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU (IdentifiedURI NameIDFormat) -> PU [IdentifiedURI NameIDFormat]
forall a. PU a -> PU [a]
XP.xpList (String
-> PU (IdentifiedURI NameIDFormat)
-> PU (IdentifiedURI NameIDFormat)
forall a. String -> PU a -> PU a
xpElem String
"NameIDFormat" PU (IdentifiedURI NameIDFormat)
forall a. XmlPickler a => PU a
XP.xpickle))
PU
(Either
(Either
(Either
(Either ((String, RoleDescriptor), Nodes) RoleDescriptor)
(((((((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint),
[Endpoint]),
[Endpoint]),
[URI]),
[Attribute]))
(((((Bool, Bool), RoleDescriptor), SSODescriptor),
List1 IndexedEndpoint),
[AttributeConsumingService]))
(((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat]))
-> PU
(((((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat]),
[URI]),
[Attribute])
-> PU
(Either
(Either
(Either
(Either
(Either ((String, RoleDescriptor), Nodes) RoleDescriptor)
(((((((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint),
[Endpoint]),
[Endpoint]),
[URI]),
[Attribute]))
(((((Bool, Bool), RoleDescriptor), SSODescriptor),
List1 IndexedEndpoint),
[AttributeConsumingService]))
(((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat]))
(((((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat]),
[URI]),
[Attribute]))
forall a b. PU a -> PU b -> PU (Either a b)
forall (f :: * -> *) a b.
MonoidalAlt f =>
f a -> f b -> f (Either a b)
XP.>|< String
-> PU
(((((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat]),
[URI]),
[Attribute])
-> PU
(((((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat]),
[URI]),
[Attribute])
forall a. String -> PU a -> PU a
xpElem String
"AttributeAuthorityDescriptor"
(PU RoleDescriptor
forall a. XmlPickler a => PU a
XP.xpickle
PU RoleDescriptor
-> PU (List1 Endpoint) -> PU (RoleDescriptor, List1 Endpoint)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Endpoint -> PU (List1 Endpoint)
forall a. PU a -> PU (List1 a)
xpList1 (String -> PU Endpoint -> PU Endpoint
forall a. String -> PU a -> PU a
xpElem String
"AttributeService" PU Endpoint
forall a. XmlPickler a => PU a
XP.xpickle)
PU (RoleDescriptor, List1 Endpoint)
-> PU [Endpoint]
-> PU ((RoleDescriptor, List1 Endpoint), [Endpoint])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Endpoint -> PU [Endpoint]
forall a. PU a -> PU [a]
XP.xpList (String -> PU Endpoint -> PU Endpoint
forall a. String -> PU a -> PU a
xpElem String
"AssertionIDRequestService" PU Endpoint
forall a. XmlPickler a => PU a
XP.xpickle)
PU ((RoleDescriptor, List1 Endpoint), [Endpoint])
-> PU [IdentifiedURI NameIDFormat]
-> PU
(((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU (IdentifiedURI NameIDFormat) -> PU [IdentifiedURI NameIDFormat]
forall a. PU a -> PU [a]
XP.xpList (String
-> PU (IdentifiedURI NameIDFormat)
-> PU (IdentifiedURI NameIDFormat)
forall a. String -> PU a -> PU a
xpElem String
"NameIDFormat" PU (IdentifiedURI NameIDFormat)
forall a. XmlPickler a => PU a
XP.xpickle)
PU
(((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat])
-> PU [URI]
-> PU
((((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat]),
[URI])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU URI -> PU [URI]
forall a. PU a -> PU [a]
XP.xpList (String -> PU URI -> PU URI
forall a. String -> PU a -> PU a
xpElem String
"AttributeProfile" PU URI
XS.xpAnyURI)
PU
((((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat]),
[URI])
-> PU [Attribute]
-> PU
(((((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat]),
[URI]),
[Attribute])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Attribute -> PU [Attribute]
forall a. PU a -> PU [a]
XP.xpList PU Attribute
forall a. XmlPickler a => PU a
XP.xpickle)
PU
(Either
(Either
(Either
(Either
(Either ((String, RoleDescriptor), Nodes) RoleDescriptor)
(((((((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint),
[Endpoint]),
[Endpoint]),
[URI]),
[Attribute]))
(((((Bool, Bool), RoleDescriptor), SSODescriptor),
List1 IndexedEndpoint),
[AttributeConsumingService]))
(((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat]))
(((((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat]),
[URI]),
[Attribute]))
-> PU
(((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat])
-> PU
(Either
(Either
(Either
(Either
(Either
(Either ((String, RoleDescriptor), Nodes) RoleDescriptor)
(((((((Bool, RoleDescriptor), SSODescriptor), List1 Endpoint),
[Endpoint]),
[Endpoint]),
[URI]),
[Attribute]))
(((((Bool, Bool), RoleDescriptor), SSODescriptor),
List1 IndexedEndpoint),
[AttributeConsumingService]))
(((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat]))
(((((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat]),
[URI]),
[Attribute]))
(((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat]))
forall a b. PU a -> PU b -> PU (Either a b)
forall (f :: * -> *) a b.
MonoidalAlt f =>
f a -> f b -> f (Either a b)
XP.>|< String
-> PU
(((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat])
-> PU
(((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat])
forall a. String -> PU a -> PU a
xpElem String
"PDPDescriptor"
(PU RoleDescriptor
forall a. XmlPickler a => PU a
XP.xpickle
PU RoleDescriptor
-> PU (List1 Endpoint) -> PU (RoleDescriptor, List1 Endpoint)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Endpoint -> PU (List1 Endpoint)
forall a. PU a -> PU (List1 a)
xpList1 (String -> PU Endpoint -> PU Endpoint
forall a. String -> PU a -> PU a
xpElem String
"AuthzService" PU Endpoint
forall a. XmlPickler a => PU a
XP.xpickle)
PU (RoleDescriptor, List1 Endpoint)
-> PU [Endpoint]
-> PU ((RoleDescriptor, List1 Endpoint), [Endpoint])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Endpoint -> PU [Endpoint]
forall a. PU a -> PU [a]
XP.xpList (String -> PU Endpoint -> PU Endpoint
forall a. String -> PU a -> PU a
xpElem String
"AssertionIDRequestService" PU Endpoint
forall a. XmlPickler a => PU a
XP.xpickle)
PU ((RoleDescriptor, List1 Endpoint), [Endpoint])
-> PU [IdentifiedURI NameIDFormat]
-> PU
(((RoleDescriptor, List1 Endpoint), [Endpoint]),
[IdentifiedURI NameIDFormat])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU (IdentifiedURI NameIDFormat) -> PU [IdentifiedURI NameIDFormat]
forall a. PU a -> PU [a]
XP.xpList (String
-> PU (IdentifiedURI NameIDFormat)
-> PU (IdentifiedURI NameIDFormat)
forall a. String -> PU a -> PU a
xpElem String
"NameIDFormat" PU (IdentifiedURI NameIDFormat)
forall a. XmlPickler a => PU a
XP.xpickle)))
data Organization = Organization
{ Organization -> Nodes
organizationAttrs :: Nodes
, Organization -> Extensions
organizationExtensions :: Extensions
, Organization -> List1 LocalizedName
organizationName :: List1 LocalizedName
, Organization -> List1 LocalizedName
organizationDisplayName :: List1 LocalizedName
, Organization -> List1 LocalizedURI
organizationURL :: List1 LocalizedURI
} deriving (Organization -> Organization -> Bool
(Organization -> Organization -> Bool)
-> (Organization -> Organization -> Bool) -> Eq Organization
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Organization -> Organization -> Bool
== :: Organization -> Organization -> Bool
$c/= :: Organization -> Organization -> Bool
/= :: Organization -> Organization -> Bool
Eq, Int -> Organization -> ShowS
[Organization] -> ShowS
Organization -> String
(Int -> Organization -> ShowS)
-> (Organization -> String)
-> ([Organization] -> ShowS)
-> Show Organization
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Organization -> ShowS
showsPrec :: Int -> Organization -> ShowS
$cshow :: Organization -> String
show :: Organization -> String
$cshowList :: [Organization] -> ShowS
showList :: [Organization] -> ShowS
Show)
instance XP.XmlPickler Organization where
xpickle :: PU Organization
xpickle = String -> PU Organization -> PU Organization
forall a. String -> PU a -> PU a
xpElem String
"Organization" (PU Organization -> PU Organization)
-> PU Organization -> PU Organization
forall a b. (a -> b) -> a -> b
$
[XP.biCase|
((((a, e), n), d), u) <-> Organization a e n d u|]
Bijection
(->)
((((Nodes, Extensions), List1 LocalizedName), List1 LocalizedName),
List1 LocalizedURI)
Organization
-> PU
((((Nodes, Extensions), List1 LocalizedName), List1 LocalizedName),
List1 LocalizedURI)
-> PU Organization
forall (f :: * -> *) a b. Functor f => (a <-> b) -> f a -> f b
XP.>$< (PU Nodes
XP.xpAnyAttrs
PU Nodes -> PU Extensions -> PU (Nodes, Extensions)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Extensions
forall a. XmlPickler a => PU a
XP.xpickle
PU (Nodes, Extensions)
-> PU (List1 LocalizedName)
-> PU ((Nodes, Extensions), List1 LocalizedName)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU LocalizedName -> PU (List1 LocalizedName)
forall a. PU a -> PU (List1 a)
xpList1 (String -> PU LocalizedName -> PU LocalizedName
forall a. String -> PU a -> PU a
xpElem String
"OrganizationName" PU LocalizedName
forall a. XmlPickler a => PU a
XP.xpickle)
PU ((Nodes, Extensions), List1 LocalizedName)
-> PU (List1 LocalizedName)
-> PU
(((Nodes, Extensions), List1 LocalizedName), List1 LocalizedName)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU LocalizedName -> PU (List1 LocalizedName)
forall a. PU a -> PU (List1 a)
xpList1 (String -> PU LocalizedName -> PU LocalizedName
forall a. String -> PU a -> PU a
xpElem String
"OrganizationDisplayName" PU LocalizedName
forall a. XmlPickler a => PU a
XP.xpickle)
PU
(((Nodes, Extensions), List1 LocalizedName), List1 LocalizedName)
-> PU (List1 LocalizedURI)
-> PU
((((Nodes, Extensions), List1 LocalizedName), List1 LocalizedName),
List1 LocalizedURI)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU LocalizedURI -> PU (List1 LocalizedURI)
forall a. PU a -> PU (List1 a)
xpList1 (String -> PU LocalizedURI -> PU LocalizedURI
forall a. String -> PU a -> PU a
xpElem String
"OrganizationURL" PU LocalizedURI
forall a. XmlPickler a => PU a
XP.xpickle))
data Contact = ContactPerson
{ Contact -> ContactType
contactType :: ContactType
, Contact -> Nodes
contactAttrs :: Nodes
, Contact -> Extensions
contactExtensions :: Extensions
, Contact -> Maybe String
contactCompany :: Maybe XS.String
, Contact -> Maybe String
contactGivenName :: Maybe XS.String
, Contact -> Maybe String
contactSurName :: Maybe XS.String
, Contact -> [URI]
contactEmailAddress :: [XS.AnyURI]
, Contact -> [String]
contactTelephoneNumber :: [XS.String]
} deriving (Contact -> Contact -> Bool
(Contact -> Contact -> Bool)
-> (Contact -> Contact -> Bool) -> Eq Contact
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Contact -> Contact -> Bool
== :: Contact -> Contact -> Bool
$c/= :: Contact -> Contact -> Bool
/= :: Contact -> Contact -> Bool
Eq, Int -> Contact -> ShowS
[Contact] -> ShowS
Contact -> String
(Int -> Contact -> ShowS)
-> (Contact -> String) -> ([Contact] -> ShowS) -> Show Contact
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Contact -> ShowS
showsPrec :: Int -> Contact -> ShowS
$cshow :: Contact -> String
show :: Contact -> String
$cshowList :: [Contact] -> ShowS
showList :: [Contact] -> ShowS
Show)
instance XP.XmlPickler Contact where
xpickle :: PU Contact
xpickle = String -> PU Contact -> PU Contact
forall a. String -> PU a -> PU a
xpElem String
"ContactPerson" (PU Contact -> PU Contact) -> PU Contact -> PU Contact
forall a b. (a -> b) -> a -> b
$
[XP.biCase|
(((((((t, a), ext), c), g), s), e), tn) <-> ContactPerson t a ext c g s e tn|]
Bijection
(->)
(((((((ContactType, Nodes), Extensions), Maybe String),
Maybe String),
Maybe String),
[URI]),
[String])
Contact
-> PU
(((((((ContactType, Nodes), Extensions), Maybe String),
Maybe String),
Maybe String),
[URI]),
[String])
-> PU Contact
forall (f :: * -> *) a b. Functor f => (a <-> b) -> f a -> f b
XP.>$< (String -> PU ContactType -> PU ContactType
forall a. String -> PU a -> PU a
XP.xpAttr String
"contactType" PU ContactType
forall a. XmlPickler a => PU a
XP.xpickle
PU ContactType -> PU Nodes -> PU (ContactType, Nodes)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Nodes
XP.xpAnyAttrs
PU (ContactType, Nodes)
-> PU Extensions -> PU ((ContactType, Nodes), Extensions)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Extensions
forall a. XmlPickler a => PU a
XP.xpickle
PU ((ContactType, Nodes), Extensions)
-> PU (Maybe String)
-> PU (((ContactType, Nodes), Extensions), Maybe String)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU String -> PU (Maybe String)
forall a. PU a -> PU (Maybe a)
XP.xpOption (String -> PU String -> PU String
forall a. String -> PU a -> PU a
xpElem String
"Company" PU String
XS.xpString)
PU (((ContactType, Nodes), Extensions), Maybe String)
-> PU (Maybe String)
-> PU
((((ContactType, Nodes), Extensions), Maybe String), Maybe String)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU String -> PU (Maybe String)
forall a. PU a -> PU (Maybe a)
XP.xpOption (String -> PU String -> PU String
forall a. String -> PU a -> PU a
xpElem String
"GivenName" PU String
XS.xpString)
PU
((((ContactType, Nodes), Extensions), Maybe String), Maybe String)
-> PU (Maybe String)
-> PU
(((((ContactType, Nodes), Extensions), Maybe String),
Maybe String),
Maybe String)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU String -> PU (Maybe String)
forall a. PU a -> PU (Maybe a)
XP.xpOption (String -> PU String -> PU String
forall a. String -> PU a -> PU a
xpElem String
"SurName" PU String
XS.xpString)
PU
(((((ContactType, Nodes), Extensions), Maybe String),
Maybe String),
Maybe String)
-> PU [URI]
-> PU
((((((ContactType, Nodes), Extensions), Maybe String),
Maybe String),
Maybe String),
[URI])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU URI -> PU [URI]
forall a. PU a -> PU [a]
XP.xpList (String -> PU URI -> PU URI
forall a. String -> PU a -> PU a
xpElem String
"EmailAddress" PU URI
XS.xpAnyURI)
PU
((((((ContactType, Nodes), Extensions), Maybe String),
Maybe String),
Maybe String),
[URI])
-> PU [String]
-> PU
(((((((ContactType, Nodes), Extensions), Maybe String),
Maybe String),
Maybe String),
[URI]),
[String])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU String -> PU [String]
forall a. PU a -> PU [a]
XP.xpList (String -> PU String -> PU String
forall a. String -> PU a -> PU a
xpElem String
"TelephoneNumber" PU String
XS.xpString))
data ContactType
= ContactTypeTechnical
| ContactTypeSupport
| ContactTypeAdministrative
| ContactTypeBilling
| ContactTypeOther
deriving (ContactType -> ContactType -> Bool
(ContactType -> ContactType -> Bool)
-> (ContactType -> ContactType -> Bool) -> Eq ContactType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ContactType -> ContactType -> Bool
== :: ContactType -> ContactType -> Bool
$c/= :: ContactType -> ContactType -> Bool
/= :: ContactType -> ContactType -> Bool
Eq, Int -> ContactType
ContactType -> Int
ContactType -> [ContactType]
ContactType -> ContactType
ContactType -> ContactType -> [ContactType]
ContactType -> ContactType -> ContactType -> [ContactType]
(ContactType -> ContactType)
-> (ContactType -> ContactType)
-> (Int -> ContactType)
-> (ContactType -> Int)
-> (ContactType -> [ContactType])
-> (ContactType -> ContactType -> [ContactType])
-> (ContactType -> ContactType -> [ContactType])
-> (ContactType -> ContactType -> ContactType -> [ContactType])
-> Enum ContactType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ContactType -> ContactType
succ :: ContactType -> ContactType
$cpred :: ContactType -> ContactType
pred :: ContactType -> ContactType
$ctoEnum :: Int -> ContactType
toEnum :: Int -> ContactType
$cfromEnum :: ContactType -> Int
fromEnum :: ContactType -> Int
$cenumFrom :: ContactType -> [ContactType]
enumFrom :: ContactType -> [ContactType]
$cenumFromThen :: ContactType -> ContactType -> [ContactType]
enumFromThen :: ContactType -> ContactType -> [ContactType]
$cenumFromTo :: ContactType -> ContactType -> [ContactType]
enumFromTo :: ContactType -> ContactType -> [ContactType]
$cenumFromThenTo :: ContactType -> ContactType -> ContactType -> [ContactType]
enumFromThenTo :: ContactType -> ContactType -> ContactType -> [ContactType]
Enum, ContactType
ContactType -> ContactType -> Bounded ContactType
forall a. a -> a -> Bounded a
$cminBound :: ContactType
minBound :: ContactType
$cmaxBound :: ContactType
maxBound :: ContactType
Bounded, Int -> ContactType -> ShowS
[ContactType] -> ShowS
ContactType -> String
(Int -> ContactType -> ShowS)
-> (ContactType -> String)
-> ([ContactType] -> ShowS)
-> Show ContactType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ContactType -> ShowS
showsPrec :: Int -> ContactType -> ShowS
$cshow :: ContactType -> String
show :: ContactType -> String
$cshowList :: [ContactType] -> ShowS
showList :: [ContactType] -> ShowS
Show)
instance Identifiable XString ContactType where
identifier :: ContactType -> String
identifier ContactType
ContactTypeTechnical = String
"technical"
identifier ContactType
ContactTypeSupport = String
"support"
identifier ContactType
ContactTypeAdministrative = String
"administrative"
identifier ContactType
ContactTypeBilling = String
"billing"
identifier ContactType
ContactTypeOther = String
"other"
instance XP.XmlPickler ContactType where
xpickle :: PU ContactType
xpickle = PU String -> String -> PU ContactType
forall b a. Identifiable b a => PU b -> String -> PU a
xpIdentifier (Schema -> PU String
XP.xpTextDT (String -> String -> Attributes -> Schema
XPS.scDT (Namespace -> String
namespaceURIString Namespace
ns) String
"ContactTypeType" [])) String
"ContactTypeType"
data AdditionalMetadataLocation = AdditionalMetadataLocation
{ AdditionalMetadataLocation -> URI
additionalMetadataLocationNamespace :: XS.AnyURI
, AdditionalMetadataLocation -> URI
additionalMetadataLocation :: XS.AnyURI
} deriving (AdditionalMetadataLocation -> AdditionalMetadataLocation -> Bool
(AdditionalMetadataLocation -> AdditionalMetadataLocation -> Bool)
-> (AdditionalMetadataLocation
-> AdditionalMetadataLocation -> Bool)
-> Eq AdditionalMetadataLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AdditionalMetadataLocation -> AdditionalMetadataLocation -> Bool
== :: AdditionalMetadataLocation -> AdditionalMetadataLocation -> Bool
$c/= :: AdditionalMetadataLocation -> AdditionalMetadataLocation -> Bool
/= :: AdditionalMetadataLocation -> AdditionalMetadataLocation -> Bool
Eq, Int -> AdditionalMetadataLocation -> ShowS
[AdditionalMetadataLocation] -> ShowS
AdditionalMetadataLocation -> String
(Int -> AdditionalMetadataLocation -> ShowS)
-> (AdditionalMetadataLocation -> String)
-> ([AdditionalMetadataLocation] -> ShowS)
-> Show AdditionalMetadataLocation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AdditionalMetadataLocation -> ShowS
showsPrec :: Int -> AdditionalMetadataLocation -> ShowS
$cshow :: AdditionalMetadataLocation -> String
show :: AdditionalMetadataLocation -> String
$cshowList :: [AdditionalMetadataLocation] -> ShowS
showList :: [AdditionalMetadataLocation] -> ShowS
Show)
instance XP.XmlPickler AdditionalMetadataLocation where
xpickle :: PU AdditionalMetadataLocation
xpickle = String
-> PU AdditionalMetadataLocation -> PU AdditionalMetadataLocation
forall a. String -> PU a -> PU a
xpElem String
"AdditionalMetadataLocation" (PU AdditionalMetadataLocation -> PU AdditionalMetadataLocation)
-> PU AdditionalMetadataLocation -> PU AdditionalMetadataLocation
forall a b. (a -> b) -> a -> b
$
[XP.biCase|
(n, l) <-> AdditionalMetadataLocation n l|]
Bijection (->) (URI, URI) AdditionalMetadataLocation
-> PU (URI, URI) -> PU AdditionalMetadataLocation
forall (f :: * -> *) a b. Functor f => (a <-> b) -> f a -> f b
XP.>$< (String -> PU URI -> PU URI
forall a. String -> PU a -> PU a
XP.xpAttr String
"namespace" PU URI
XS.xpAnyURI
PU URI -> PU URI -> PU (URI, URI)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU URI
XS.xpAnyURI)
data RoleDescriptor = RoleDescriptor
{ RoleDescriptor -> Maybe String
roleDescriptorID :: Maybe XS.ID
, RoleDescriptor -> Maybe DateTime
roleDescriptorValidUntil :: Maybe XS.DateTime
, RoleDescriptor -> Maybe Duration
roleDescriptorCacheDuration :: Maybe XS.Duration
, RoleDescriptor -> [URI]
roleDescriptorProtocolSupportEnumeration :: [XS.AnyURI]
, RoleDescriptor -> Maybe URI
roleDescriptorErrorURL :: Maybe XS.AnyURI
, RoleDescriptor -> Nodes
roleDescriptorAttrs :: Nodes
, RoleDescriptor -> Maybe Signature
roleDescriptorSignature :: Maybe DS.Signature
, RoleDescriptor -> Extensions
roleDescriptorExtensions :: Extensions
, RoleDescriptor -> [KeyDescriptor]
roleDescriptorKeyDescriptor :: [KeyDescriptor]
, RoleDescriptor -> Maybe Organization
roleDescriptorOrganization :: Maybe Organization
, RoleDescriptor -> [Contact]
roleDescriptorContactPerson :: [Contact]
} deriving (RoleDescriptor -> RoleDescriptor -> Bool
(RoleDescriptor -> RoleDescriptor -> Bool)
-> (RoleDescriptor -> RoleDescriptor -> Bool) -> Eq RoleDescriptor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RoleDescriptor -> RoleDescriptor -> Bool
== :: RoleDescriptor -> RoleDescriptor -> Bool
$c/= :: RoleDescriptor -> RoleDescriptor -> Bool
/= :: RoleDescriptor -> RoleDescriptor -> Bool
Eq, Int -> RoleDescriptor -> ShowS
[RoleDescriptor] -> ShowS
RoleDescriptor -> String
(Int -> RoleDescriptor -> ShowS)
-> (RoleDescriptor -> String)
-> ([RoleDescriptor] -> ShowS)
-> Show RoleDescriptor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RoleDescriptor -> ShowS
showsPrec :: Int -> RoleDescriptor -> ShowS
$cshow :: RoleDescriptor -> String
show :: RoleDescriptor -> String
$cshowList :: [RoleDescriptor] -> ShowS
showList :: [RoleDescriptor] -> ShowS
Show)
instance XP.XmlPickler RoleDescriptor where
xpickle :: PU RoleDescriptor
xpickle = [XP.biCase|
((((((((((i, vu), cd), ps), eu), a), sig), ext), key), org), cp) <-> RoleDescriptor i vu cd ps eu a sig ext key org cp|]
Bijection
(->)
((((((((((Maybe String, Maybe DateTime), Maybe Duration), [URI]),
Maybe URI),
Nodes),
Maybe Signature),
Extensions),
[KeyDescriptor]),
Maybe Organization),
[Contact])
RoleDescriptor
-> PU
((((((((((Maybe String, Maybe DateTime), Maybe Duration), [URI]),
Maybe URI),
Nodes),
Maybe Signature),
Extensions),
[KeyDescriptor]),
Maybe Organization),
[Contact])
-> PU RoleDescriptor
forall (f :: * -> *) a b. Functor f => (a <-> b) -> f a -> f b
XP.>$< (String -> PU String -> PU (Maybe String)
forall a. String -> PU a -> PU (Maybe a)
XP.xpAttrImplied String
"ID" PU String
XS.xpID
PU (Maybe String)
-> PU (Maybe DateTime) -> PU (Maybe String, Maybe DateTime)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< String -> PU DateTime -> PU (Maybe DateTime)
forall a. String -> PU a -> PU (Maybe a)
XP.xpAttrImplied String
"validUntil" PU DateTime
XS.xpDateTime
PU (Maybe String, Maybe DateTime)
-> PU (Maybe Duration)
-> PU ((Maybe String, Maybe DateTime), Maybe Duration)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< String -> PU Duration -> PU (Maybe Duration)
forall a. String -> PU a -> PU (Maybe a)
XP.xpAttrImplied String
"cacheDuration" PU Duration
XS.xpDuration
PU ((Maybe String, Maybe DateTime), Maybe Duration)
-> PU [URI]
-> PU (((Maybe String, Maybe DateTime), Maybe Duration), [URI])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< String -> PU [URI] -> PU [URI]
forall a. String -> PU a -> PU a
XP.xpAttr String
"protocolSupportEnumeration" PU [URI]
xpAnyURIList
PU (((Maybe String, Maybe DateTime), Maybe Duration), [URI])
-> PU (Maybe URI)
-> PU
((((Maybe String, Maybe DateTime), Maybe Duration), [URI]),
Maybe URI)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< String -> PU URI -> PU (Maybe URI)
forall a. String -> PU a -> PU (Maybe a)
XP.xpAttrImplied String
"errorURL" PU URI
XS.xpAnyURI
PU
((((Maybe String, Maybe DateTime), Maybe Duration), [URI]),
Maybe URI)
-> PU Nodes
-> PU
(((((Maybe String, Maybe DateTime), Maybe Duration), [URI]),
Maybe URI),
Nodes)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Nodes
XP.xpAnyAttrs
PU
(((((Maybe String, Maybe DateTime), Maybe Duration), [URI]),
Maybe URI),
Nodes)
-> PU (Maybe Signature)
-> PU
((((((Maybe String, Maybe DateTime), Maybe Duration), [URI]),
Maybe URI),
Nodes),
Maybe Signature)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU (Maybe Signature)
forall a. XmlPickler a => PU a
XP.xpickle
PU
((((((Maybe String, Maybe DateTime), Maybe Duration), [URI]),
Maybe URI),
Nodes),
Maybe Signature)
-> PU Extensions
-> PU
(((((((Maybe String, Maybe DateTime), Maybe Duration), [URI]),
Maybe URI),
Nodes),
Maybe Signature),
Extensions)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Extensions
forall a. XmlPickler a => PU a
XP.xpickle
PU
(((((((Maybe String, Maybe DateTime), Maybe Duration), [URI]),
Maybe URI),
Nodes),
Maybe Signature),
Extensions)
-> PU [KeyDescriptor]
-> PU
((((((((Maybe String, Maybe DateTime), Maybe Duration), [URI]),
Maybe URI),
Nodes),
Maybe Signature),
Extensions),
[KeyDescriptor])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU KeyDescriptor -> PU [KeyDescriptor]
forall a. PU a -> PU [a]
XP.xpList PU KeyDescriptor
forall a. XmlPickler a => PU a
XP.xpickle
PU
((((((((Maybe String, Maybe DateTime), Maybe Duration), [URI]),
Maybe URI),
Nodes),
Maybe Signature),
Extensions),
[KeyDescriptor])
-> PU (Maybe Organization)
-> PU
(((((((((Maybe String, Maybe DateTime), Maybe Duration), [URI]),
Maybe URI),
Nodes),
Maybe Signature),
Extensions),
[KeyDescriptor]),
Maybe Organization)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Organization -> PU (Maybe Organization)
forall a. PU a -> PU (Maybe a)
XP.xpOption PU Organization
forall a. XmlPickler a => PU a
XP.xpickle
PU
(((((((((Maybe String, Maybe DateTime), Maybe Duration), [URI]),
Maybe URI),
Nodes),
Maybe Signature),
Extensions),
[KeyDescriptor]),
Maybe Organization)
-> PU [Contact]
-> PU
((((((((((Maybe String, Maybe DateTime), Maybe Duration), [URI]),
Maybe URI),
Nodes),
Maybe Signature),
Extensions),
[KeyDescriptor]),
Maybe Organization),
[Contact])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Contact -> PU [Contact]
forall a. PU a -> PU [a]
XP.xpList PU Contact
forall a. XmlPickler a => PU a
XP.xpickle)
where
xpAnyURIList :: PU [URI]
xpAnyURIList = (String -> Either String [URI], [URI] -> String)
-> PU String -> PU [URI]
forall a b. (a -> Either String b, b -> a) -> PU a -> PU b
XP.xpWrapEither
( (String -> Either String URI) -> [String] -> Either String [URI]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Either String URI
-> (URI -> Either String URI) -> Maybe URI -> Either String URI
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Either String URI
forall a b. a -> Either a b
Left String
"invalid anyURI") URI -> Either String URI
forall a b. b -> Either a b
Right (Maybe URI -> Either String URI)
-> (String -> Maybe URI) -> String -> Either String URI
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe URI
URI.parseURIReference) ([String] -> Either String [URI])
-> (String -> [String]) -> String -> Either String [URI]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
words
, ShowS
forall a. HasCallStack => [a] -> [a]
tail ShowS -> ([URI] -> String) -> [URI] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (URI -> ShowS) -> String -> [URI] -> String
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) (Char
' 'Char -> ShowS
forall a. a -> [a] -> [a]
:) (ShowS -> ShowS) -> (URI -> ShowS) -> URI -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS -> URI -> ShowS
URI.uriToString ShowS
forall a. a -> a
id) String
""
) (PU String -> PU [URI]) -> PU String -> PU [URI]
forall a b. (a -> b) -> a -> b
$ Schema -> PU String
XP.xpTextDT (Schema -> PU String) -> Schema -> PU String
forall a b. (a -> b) -> a -> b
$ String -> String -> Attributes -> Schema
XPS.scDT (Namespace -> String
namespaceURIString Namespace
ns) String
"anyURIListType" []
instance DS.Signable RoleDescriptor where
signature' :: Lens' RoleDescriptor (Maybe Signature)
signature' = $(fieldLens 'roleDescriptorSignature)
signedID :: RoleDescriptor -> String
signedID = Maybe String -> String
forall m. Monoid m => Maybe m -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold (Maybe String -> String)
-> (RoleDescriptor -> Maybe String) -> RoleDescriptor -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RoleDescriptor -> Maybe String
roleDescriptorID
data KeyDescriptor = KeyDescriptor
{ KeyDescriptor -> KeyTypes
keyDescriptorUse :: KeyTypes
, KeyDescriptor -> KeyInfo
keyDescriptorKeyInfo :: DS.KeyInfo
, KeyDescriptor -> [EncryptionMethod]
keyDescriptorEncryptionMethod :: [XEnc.EncryptionMethod]
} deriving (KeyDescriptor -> KeyDescriptor -> Bool
(KeyDescriptor -> KeyDescriptor -> Bool)
-> (KeyDescriptor -> KeyDescriptor -> Bool) -> Eq KeyDescriptor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: KeyDescriptor -> KeyDescriptor -> Bool
== :: KeyDescriptor -> KeyDescriptor -> Bool
$c/= :: KeyDescriptor -> KeyDescriptor -> Bool
/= :: KeyDescriptor -> KeyDescriptor -> Bool
Eq, Int -> KeyDescriptor -> ShowS
[KeyDescriptor] -> ShowS
KeyDescriptor -> String
(Int -> KeyDescriptor -> ShowS)
-> (KeyDescriptor -> String)
-> ([KeyDescriptor] -> ShowS)
-> Show KeyDescriptor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> KeyDescriptor -> ShowS
showsPrec :: Int -> KeyDescriptor -> ShowS
$cshow :: KeyDescriptor -> String
show :: KeyDescriptor -> String
$cshowList :: [KeyDescriptor] -> ShowS
showList :: [KeyDescriptor] -> ShowS
Show)
instance XP.XmlPickler KeyDescriptor where
xpickle :: PU KeyDescriptor
xpickle = String -> PU KeyDescriptor -> PU KeyDescriptor
forall a. String -> PU a -> PU a
xpElem String
"KeyDescriptor" (PU KeyDescriptor -> PU KeyDescriptor)
-> PU KeyDescriptor -> PU KeyDescriptor
forall a b. (a -> b) -> a -> b
$
[XP.biCase|
((t, i), m) <-> KeyDescriptor t i m|]
Bijection
(->) ((KeyTypes, KeyInfo), [EncryptionMethod]) KeyDescriptor
-> PU ((KeyTypes, KeyInfo), [EncryptionMethod]) -> PU KeyDescriptor
forall (f :: * -> *) a b. Functor f => (a <-> b) -> f a -> f b
XP.>$< (KeyTypes -> PU KeyTypes -> PU KeyTypes
forall a. Eq a => a -> PU a -> PU a
XP.xpDefault KeyTypes
KeyTypeBoth (String -> PU KeyTypes -> PU KeyTypes
forall a. String -> PU a -> PU a
XP.xpAttr String
"use" PU KeyTypes
forall a. XmlPickler a => PU a
XP.xpickle)
PU KeyTypes -> PU KeyInfo -> PU (KeyTypes, KeyInfo)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU KeyInfo
forall a. XmlPickler a => PU a
XP.xpickle
PU (KeyTypes, KeyInfo)
-> PU [EncryptionMethod]
-> PU ((KeyTypes, KeyInfo), [EncryptionMethod])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU EncryptionMethod -> PU [EncryptionMethod]
forall a. PU a -> PU [a]
XP.xpList (String -> PU EncryptionMethod -> PU EncryptionMethod
forall a. String -> PU a -> PU a
xpElem String
"EncryptionMethod" PU EncryptionMethod
XEnc.xpEncryptionMethodType))
data KeyTypes
= KeyTypeSigning
| KeyTypeEncryption
| KeyTypeBoth
deriving (KeyTypes -> KeyTypes -> Bool
(KeyTypes -> KeyTypes -> Bool)
-> (KeyTypes -> KeyTypes -> Bool) -> Eq KeyTypes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: KeyTypes -> KeyTypes -> Bool
== :: KeyTypes -> KeyTypes -> Bool
$c/= :: KeyTypes -> KeyTypes -> Bool
/= :: KeyTypes -> KeyTypes -> Bool
Eq, Int -> KeyTypes
KeyTypes -> Int
KeyTypes -> [KeyTypes]
KeyTypes -> KeyTypes
KeyTypes -> KeyTypes -> [KeyTypes]
KeyTypes -> KeyTypes -> KeyTypes -> [KeyTypes]
(KeyTypes -> KeyTypes)
-> (KeyTypes -> KeyTypes)
-> (Int -> KeyTypes)
-> (KeyTypes -> Int)
-> (KeyTypes -> [KeyTypes])
-> (KeyTypes -> KeyTypes -> [KeyTypes])
-> (KeyTypes -> KeyTypes -> [KeyTypes])
-> (KeyTypes -> KeyTypes -> KeyTypes -> [KeyTypes])
-> Enum KeyTypes
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: KeyTypes -> KeyTypes
succ :: KeyTypes -> KeyTypes
$cpred :: KeyTypes -> KeyTypes
pred :: KeyTypes -> KeyTypes
$ctoEnum :: Int -> KeyTypes
toEnum :: Int -> KeyTypes
$cfromEnum :: KeyTypes -> Int
fromEnum :: KeyTypes -> Int
$cenumFrom :: KeyTypes -> [KeyTypes]
enumFrom :: KeyTypes -> [KeyTypes]
$cenumFromThen :: KeyTypes -> KeyTypes -> [KeyTypes]
enumFromThen :: KeyTypes -> KeyTypes -> [KeyTypes]
$cenumFromTo :: KeyTypes -> KeyTypes -> [KeyTypes]
enumFromTo :: KeyTypes -> KeyTypes -> [KeyTypes]
$cenumFromThenTo :: KeyTypes -> KeyTypes -> KeyTypes -> [KeyTypes]
enumFromThenTo :: KeyTypes -> KeyTypes -> KeyTypes -> [KeyTypes]
Enum, KeyTypes
KeyTypes -> KeyTypes -> Bounded KeyTypes
forall a. a -> a -> Bounded a
$cminBound :: KeyTypes
minBound :: KeyTypes
$cmaxBound :: KeyTypes
maxBound :: KeyTypes
Bounded, Int -> KeyTypes -> ShowS
[KeyTypes] -> ShowS
KeyTypes -> String
(Int -> KeyTypes -> ShowS)
-> (KeyTypes -> String) -> ([KeyTypes] -> ShowS) -> Show KeyTypes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> KeyTypes -> ShowS
showsPrec :: Int -> KeyTypes -> ShowS
$cshow :: KeyTypes -> String
show :: KeyTypes -> String
$cshowList :: [KeyTypes] -> ShowS
showList :: [KeyTypes] -> ShowS
Show)
keyType :: KeyTypes -> KeyTypes -> Bool
keyType :: KeyTypes -> KeyTypes -> Bool
keyType KeyTypes
_ KeyTypes
KeyTypeBoth = Bool
True
keyType KeyTypes
k KeyTypes
t = KeyTypes
k KeyTypes -> KeyTypes -> Bool
forall a. Eq a => a -> a -> Bool
== KeyTypes
t
instance Identifiable XString KeyTypes where
identifier :: KeyTypes -> String
identifier KeyTypes
KeyTypeSigning = String
"signing"
identifier KeyTypes
KeyTypeEncryption = String
"encryption"
identifier KeyTypes
KeyTypeBoth = String
""
identifiedValues :: [KeyTypes]
identifiedValues = [KeyTypes
KeyTypeEncryption, KeyTypes
KeyTypeSigning]
instance XP.XmlPickler KeyTypes where
xpickle :: PU KeyTypes
xpickle = PU String -> String -> PU KeyTypes
forall b a. Identifiable b a => PU b -> String -> PU a
xpIdentifier (Schema -> PU String
XP.xpTextDT (String -> String -> Attributes -> Schema
XPS.scDT (Namespace -> String
namespaceURIString Namespace
ns) String
"KeyTypes" [])) String
"KeyTypes"
data SSODescriptor = SSODescriptor
{ SSODescriptor -> [IndexedEndpoint]
ssoDescriptorArtifactResolutionService :: [IndexedEndpoint]
, SSODescriptor -> [Endpoint]
ssoDescriptorSingleLogoutService :: [Endpoint]
, SSODescriptor -> [Endpoint]
ssoDescriptorManageNameIDService :: [Endpoint]
, SSODescriptor -> [IdentifiedURI NameIDFormat]
ssoDescriptorNameIDFormat :: [IdentifiedURI NameIDFormat]
} deriving (SSODescriptor -> SSODescriptor -> Bool
(SSODescriptor -> SSODescriptor -> Bool)
-> (SSODescriptor -> SSODescriptor -> Bool) -> Eq SSODescriptor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SSODescriptor -> SSODescriptor -> Bool
== :: SSODescriptor -> SSODescriptor -> Bool
$c/= :: SSODescriptor -> SSODescriptor -> Bool
/= :: SSODescriptor -> SSODescriptor -> Bool
Eq, Int -> SSODescriptor -> ShowS
[SSODescriptor] -> ShowS
SSODescriptor -> String
(Int -> SSODescriptor -> ShowS)
-> (SSODescriptor -> String)
-> ([SSODescriptor] -> ShowS)
-> Show SSODescriptor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SSODescriptor -> ShowS
showsPrec :: Int -> SSODescriptor -> ShowS
$cshow :: SSODescriptor -> String
show :: SSODescriptor -> String
$cshowList :: [SSODescriptor] -> ShowS
showList :: [SSODescriptor] -> ShowS
Show)
instance XP.XmlPickler SSODescriptor where
xpickle :: PU SSODescriptor
xpickle = [XP.biCase|
(((a, s), m), n) <-> SSODescriptor a s m n|]
Bijection
(->)
((([IndexedEndpoint], [Endpoint]), [Endpoint]),
[IdentifiedURI NameIDFormat])
SSODescriptor
-> PU
((([IndexedEndpoint], [Endpoint]), [Endpoint]),
[IdentifiedURI NameIDFormat])
-> PU SSODescriptor
forall (f :: * -> *) a b. Functor f => (a <-> b) -> f a -> f b
XP.>$< (PU IndexedEndpoint -> PU [IndexedEndpoint]
forall a. PU a -> PU [a]
XP.xpList (String -> PU IndexedEndpoint -> PU IndexedEndpoint
forall a. String -> PU a -> PU a
xpElem String
"ArtifactResolutionService" PU IndexedEndpoint
forall a. XmlPickler a => PU a
XP.xpickle)
PU [IndexedEndpoint]
-> PU [Endpoint] -> PU ([IndexedEndpoint], [Endpoint])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Endpoint -> PU [Endpoint]
forall a. PU a -> PU [a]
XP.xpList (String -> PU Endpoint -> PU Endpoint
forall a. String -> PU a -> PU a
xpElem String
"SingleLogoutService" PU Endpoint
forall a. XmlPickler a => PU a
XP.xpickle)
PU ([IndexedEndpoint], [Endpoint])
-> PU [Endpoint]
-> PU (([IndexedEndpoint], [Endpoint]), [Endpoint])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Endpoint -> PU [Endpoint]
forall a. PU a -> PU [a]
XP.xpList (String -> PU Endpoint -> PU Endpoint
forall a. String -> PU a -> PU a
xpElem String
"ManageNameIDService" PU Endpoint
forall a. XmlPickler a => PU a
XP.xpickle)
PU (([IndexedEndpoint], [Endpoint]), [Endpoint])
-> PU [IdentifiedURI NameIDFormat]
-> PU
((([IndexedEndpoint], [Endpoint]), [Endpoint]),
[IdentifiedURI NameIDFormat])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU (IdentifiedURI NameIDFormat) -> PU [IdentifiedURI NameIDFormat]
forall a. PU a -> PU [a]
XP.xpList (String
-> PU (IdentifiedURI NameIDFormat)
-> PU (IdentifiedURI NameIDFormat)
forall a. String -> PU a -> PU a
xpElem String
"NameIDFormat" PU (IdentifiedURI NameIDFormat)
forall a. XmlPickler a => PU a
XP.xpickle))
data AttributeConsumingService = AttributeConsumingService
{ AttributeConsumingService -> UnsignedShort
attributeConsumingServiceIndex :: XS.UnsignedShort
, AttributeConsumingService -> Bool
attributeConsumingServiceIsDefault :: Bool
, AttributeConsumingService -> List1 LocalizedName
attributeConsumingServiceServiceName :: List1 LocalizedName
, AttributeConsumingService -> [LocalizedName]
attributeConsumingServiceServiceDescription :: [LocalizedName]
, AttributeConsumingService -> List1 RequestedAttribute
attributeConsumingServiceRequestedAttribute :: List1 RequestedAttribute
} deriving (AttributeConsumingService -> AttributeConsumingService -> Bool
(AttributeConsumingService -> AttributeConsumingService -> Bool)
-> (AttributeConsumingService -> AttributeConsumingService -> Bool)
-> Eq AttributeConsumingService
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AttributeConsumingService -> AttributeConsumingService -> Bool
== :: AttributeConsumingService -> AttributeConsumingService -> Bool
$c/= :: AttributeConsumingService -> AttributeConsumingService -> Bool
/= :: AttributeConsumingService -> AttributeConsumingService -> Bool
Eq, Int -> AttributeConsumingService -> ShowS
[AttributeConsumingService] -> ShowS
AttributeConsumingService -> String
(Int -> AttributeConsumingService -> ShowS)
-> (AttributeConsumingService -> String)
-> ([AttributeConsumingService] -> ShowS)
-> Show AttributeConsumingService
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AttributeConsumingService -> ShowS
showsPrec :: Int -> AttributeConsumingService -> ShowS
$cshow :: AttributeConsumingService -> String
show :: AttributeConsumingService -> String
$cshowList :: [AttributeConsumingService] -> ShowS
showList :: [AttributeConsumingService] -> ShowS
Show)
instance XP.XmlPickler AttributeConsumingService where
xpickle :: PU AttributeConsumingService
xpickle = String
-> PU AttributeConsumingService -> PU AttributeConsumingService
forall a. String -> PU a -> PU a
xpElem String
"AttributeConsumingService" (PU AttributeConsumingService -> PU AttributeConsumingService)
-> PU AttributeConsumingService -> PU AttributeConsumingService
forall a b. (a -> b) -> a -> b
$
[XP.biCase|
((((i, d), sn), sd), ra) <-> AttributeConsumingService i d sn sd ra|]
Bijection
(->)
((((UnsignedShort, Bool), List1 LocalizedName), [LocalizedName]),
List1 RequestedAttribute)
AttributeConsumingService
-> PU
((((UnsignedShort, Bool), List1 LocalizedName), [LocalizedName]),
List1 RequestedAttribute)
-> PU AttributeConsumingService
forall (f :: * -> *) a b. Functor f => (a <-> b) -> f a -> f b
XP.>$< (String -> PU UnsignedShort -> PU UnsignedShort
forall a. String -> PU a -> PU a
XP.xpAttr String
"index" PU UnsignedShort
XS.xpUnsignedShort
PU UnsignedShort -> PU Bool -> PU (UnsignedShort, Bool)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< Bool -> PU Bool -> PU Bool
forall a. Eq a => a -> PU a -> PU a
XP.xpDefault Bool
False (String -> PU Bool -> PU Bool
forall a. String -> PU a -> PU a
XP.xpAttr String
"isDefault" PU Bool
XS.xpBoolean)
PU (UnsignedShort, Bool)
-> PU (List1 LocalizedName)
-> PU ((UnsignedShort, Bool), List1 LocalizedName)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU LocalizedName -> PU (List1 LocalizedName)
forall a. PU a -> PU (List1 a)
xpList1 (String -> PU LocalizedName -> PU LocalizedName
forall a. String -> PU a -> PU a
xpElem String
"ServiceName" PU LocalizedName
forall a. XmlPickler a => PU a
XP.xpickle)
PU ((UnsignedShort, Bool), List1 LocalizedName)
-> PU [LocalizedName]
-> PU
(((UnsignedShort, Bool), List1 LocalizedName), [LocalizedName])
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU LocalizedName -> PU [LocalizedName]
forall a. PU a -> PU [a]
XP.xpList (String -> PU LocalizedName -> PU LocalizedName
forall a. String -> PU a -> PU a
xpElem String
"ServiceDescription" PU LocalizedName
forall a. XmlPickler a => PU a
XP.xpickle)
PU (((UnsignedShort, Bool), List1 LocalizedName), [LocalizedName])
-> PU (List1 RequestedAttribute)
-> PU
((((UnsignedShort, Bool), List1 LocalizedName), [LocalizedName]),
List1 RequestedAttribute)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU RequestedAttribute -> PU (List1 RequestedAttribute)
forall a. PU a -> PU (List1 a)
xpList1 PU RequestedAttribute
forall a. XmlPickler a => PU a
XP.xpickle)
data RequestedAttribute = RequestedAttribute
{ RequestedAttribute -> Attribute
requestedAttribute :: !SAML.Attribute
, RequestedAttribute -> Bool
requestedAttributeIsRequired :: Bool
} deriving (RequestedAttribute -> RequestedAttribute -> Bool
(RequestedAttribute -> RequestedAttribute -> Bool)
-> (RequestedAttribute -> RequestedAttribute -> Bool)
-> Eq RequestedAttribute
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RequestedAttribute -> RequestedAttribute -> Bool
== :: RequestedAttribute -> RequestedAttribute -> Bool
$c/= :: RequestedAttribute -> RequestedAttribute -> Bool
/= :: RequestedAttribute -> RequestedAttribute -> Bool
Eq, Int -> RequestedAttribute -> ShowS
[RequestedAttribute] -> ShowS
RequestedAttribute -> String
(Int -> RequestedAttribute -> ShowS)
-> (RequestedAttribute -> String)
-> ([RequestedAttribute] -> ShowS)
-> Show RequestedAttribute
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequestedAttribute -> ShowS
showsPrec :: Int -> RequestedAttribute -> ShowS
$cshow :: RequestedAttribute -> String
show :: RequestedAttribute -> String
$cshowList :: [RequestedAttribute] -> ShowS
showList :: [RequestedAttribute] -> ShowS
Show)
instance XP.XmlPickler RequestedAttribute where
xpickle :: PU RequestedAttribute
xpickle = String -> PU RequestedAttribute -> PU RequestedAttribute
forall a. String -> PU a -> PU a
xpElem String
"RequestedAttribute" (PU RequestedAttribute -> PU RequestedAttribute)
-> PU RequestedAttribute -> PU RequestedAttribute
forall a b. (a -> b) -> a -> b
$
[XP.biCase|
(r, a) <-> RequestedAttribute a r|]
Bijection (->) (Bool, Attribute) RequestedAttribute
-> PU (Bool, Attribute) -> PU RequestedAttribute
forall (f :: * -> *) a b. Functor f => (a <-> b) -> f a -> f b
XP.>$< (Bool -> PU Bool -> PU Bool
forall a. Eq a => a -> PU a -> PU a
XP.xpDefault Bool
False (String -> PU Bool -> PU Bool
forall a. String -> PU a -> PU a
XP.xpAttr String
"isRequired" PU Bool
XS.xpBoolean)
PU Bool -> PU Attribute -> PU (Bool, Attribute)
forall a b. PU a -> PU b -> PU (a, b)
forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
XP.>*< PU Attribute
SAML.xpAttributeType)