wai-saml2-0.5: SAML2 assertion validation as WAI middleware
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.Wai.SAML2.NameIDFormat

Description

This modules defines the NameIDFormat type, which specifies the format of name identifiers in an assertion.

Since: 0.4

Synopsis

Documentation

data NameIDFormat Source #

Format of the subject identifier. See 8.3 Name Identifier Format Identifiers in https://docs.oasis-open.org/security/saml/v2.0/saml-core-2.0-os.pdf

Constructors

Unspecified

The interpretation is left to individual implementations

EmailAddress

addr-spec as defined in IETF RFC 2822

X509SubjectName

contents of the ds:X509SubjectName element in the XML Signature Recommendation

WindowsDomainQualifiedName

String of the form DomainNameUserName

KerberosPrincipalName

Kerberos principal name using the format name[/instance]REALM@

Entity

identifier of an entity that provides SAML-based services (such as a SAML authority, requester, or responder) or is a participant in SAML profiles (such as a service provider supporting the browser SSO profile)

Provider

identifier of a provider of SAML-based services (such as a SAML authority) or a participant in SAML profiles (such as a service provider supporting the browser profiles)

Federated

persistent opaque identifier that corresponds to an identity federation between an identity provider and a service provider

Transient

an identifier with transient semantics and SHOULD be treated as an opaque and temporary value by the relying party

Persistent

persistent opaque identifier for a principal that is specific to an identity provider and a service provider or affiliation of service providers

Instances

Instances details
Generic NameIDFormat Source # 
Instance details

Defined in Network.Wai.SAML2.NameIDFormat

Associated Types

type Rep NameIDFormat :: Type -> Type #

Show NameIDFormat Source # 
Instance details

Defined in Network.Wai.SAML2.NameIDFormat

Eq NameIDFormat Source # 
Instance details

Defined in Network.Wai.SAML2.NameIDFormat

Ord NameIDFormat Source # 
Instance details

Defined in Network.Wai.SAML2.NameIDFormat

type Rep NameIDFormat Source # 
Instance details

Defined in Network.Wai.SAML2.NameIDFormat

type Rep NameIDFormat = D1 ('MetaData "NameIDFormat" "Network.Wai.SAML2.NameIDFormat" "wai-saml2-0.5-JhcCjiw6yf1IP4K8IkOrnf" 'False) (((C1 ('MetaCons "Unspecified" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EmailAddress" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "X509SubjectName" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WindowsDomainQualifiedName" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KerberosPrincipalName" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Entity" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Provider" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Federated" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Transient" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Persistent" 'PrefixI 'False) (U1 :: Type -> Type)))))

parseNameIDFormat :: MonadFail m => Text -> m NameIDFormat Source #

Parse a NameIDFormat (prefixed by urn:oasis:names:tc:SAML:*:nameid-format).

showNameIDFormat :: NameIDFormat -> Text Source #

Displays a NameIDFormat value as a Text value.