{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
-- |
-- SAML-Defined Identifiers
--
-- <https://docs.oasis-open.org/security/saml/v2.0/saml-core-2.0-os.pdf saml-core-2.0-os> §8
module SAML2.Core.Identifiers where

import Data.Default (Default(..))

import SAML2.XML
import SAML2.Core.Namespaces
import SAML2.Core.Versioning

-- |§8.1
data ActionNamespace
  = ActionNamespaceRWEDC -- ^§8.1.1: Read Write Execute Delete Control
  | ActionNamespaceRWEDCNegation -- ^§8.1.2: RWEDC ~RWEDC
  | ActionNamespaceGHPP -- ^§8.1.3: GET HEAD PUT POST
  | ActionNamespaceUNIX -- ^§8.1.4: octal
  deriving (ActionNamespace -> ActionNamespace -> Bool
(ActionNamespace -> ActionNamespace -> Bool)
-> (ActionNamespace -> ActionNamespace -> Bool)
-> Eq ActionNamespace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ActionNamespace -> ActionNamespace -> Bool
$c/= :: ActionNamespace -> ActionNamespace -> Bool
== :: ActionNamespace -> ActionNamespace -> Bool
$c== :: ActionNamespace -> ActionNamespace -> Bool
Eq, Int -> ActionNamespace
ActionNamespace -> Int
ActionNamespace -> [ActionNamespace]
ActionNamespace -> ActionNamespace
ActionNamespace -> ActionNamespace -> [ActionNamespace]
ActionNamespace
-> ActionNamespace -> ActionNamespace -> [ActionNamespace]
(ActionNamespace -> ActionNamespace)
-> (ActionNamespace -> ActionNamespace)
-> (Int -> ActionNamespace)
-> (ActionNamespace -> Int)
-> (ActionNamespace -> [ActionNamespace])
-> (ActionNamespace -> ActionNamespace -> [ActionNamespace])
-> (ActionNamespace -> ActionNamespace -> [ActionNamespace])
-> (ActionNamespace
    -> ActionNamespace -> ActionNamespace -> [ActionNamespace])
-> Enum ActionNamespace
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ActionNamespace
-> ActionNamespace -> ActionNamespace -> [ActionNamespace]
$cenumFromThenTo :: ActionNamespace
-> ActionNamespace -> ActionNamespace -> [ActionNamespace]
enumFromTo :: ActionNamespace -> ActionNamespace -> [ActionNamespace]
$cenumFromTo :: ActionNamespace -> ActionNamespace -> [ActionNamespace]
enumFromThen :: ActionNamespace -> ActionNamespace -> [ActionNamespace]
$cenumFromThen :: ActionNamespace -> ActionNamespace -> [ActionNamespace]
enumFrom :: ActionNamespace -> [ActionNamespace]
$cenumFrom :: ActionNamespace -> [ActionNamespace]
fromEnum :: ActionNamespace -> Int
$cfromEnum :: ActionNamespace -> Int
toEnum :: Int -> ActionNamespace
$ctoEnum :: Int -> ActionNamespace
pred :: ActionNamespace -> ActionNamespace
$cpred :: ActionNamespace -> ActionNamespace
succ :: ActionNamespace -> ActionNamespace
$csucc :: ActionNamespace -> ActionNamespace
Enum, ActionNamespace
ActionNamespace -> ActionNamespace -> Bounded ActionNamespace
forall a. a -> a -> Bounded a
maxBound :: ActionNamespace
$cmaxBound :: ActionNamespace
minBound :: ActionNamespace
$cminBound :: ActionNamespace
Bounded, Int -> ActionNamespace -> ShowS
[ActionNamespace] -> ShowS
ActionNamespace -> String
(Int -> ActionNamespace -> ShowS)
-> (ActionNamespace -> String)
-> ([ActionNamespace] -> ShowS)
-> Show ActionNamespace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ActionNamespace] -> ShowS
$cshowList :: [ActionNamespace] -> ShowS
show :: ActionNamespace -> String
$cshow :: ActionNamespace -> String
showsPrec :: Int -> ActionNamespace -> ShowS
$cshowsPrec :: Int -> ActionNamespace -> ShowS
Show)

instance Identifiable URI ActionNamespace where
  identifier :: ActionNamespace -> URI
identifier = String -> (SAMLVersion, String) -> URI
samlURNIdentifier String
"action" ((SAMLVersion, String) -> URI)
-> (ActionNamespace -> (SAMLVersion, String))
-> ActionNamespace
-> URI
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ActionNamespace -> (SAMLVersion, String)
f where
    f :: ActionNamespace -> (SAMLVersion, String)
f ActionNamespace
ActionNamespaceRWEDC          = (SAMLVersion
SAML10, String
"rwedc")
    f ActionNamespace
ActionNamespaceRWEDCNegation  = (SAMLVersion
SAML10, String
"rwedc-negation")
    f ActionNamespace
ActionNamespaceGHPP           = (SAMLVersion
SAML10, String
"ghpp")
    f ActionNamespace
ActionNamespaceUNIX           = (SAMLVersion
SAML10, String
"unix")

-- |§8.2
data AttributeNameFormat
  = AttributeNameFormatUnspecified -- ^§8.2.1: Text
  | AttributeNameFormatURI -- ^§8.2.2: URI
  | AttributeNameFormatBasic -- ^§8.2.3: Name
  deriving (AttributeNameFormat -> AttributeNameFormat -> Bool
(AttributeNameFormat -> AttributeNameFormat -> Bool)
-> (AttributeNameFormat -> AttributeNameFormat -> Bool)
-> Eq AttributeNameFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttributeNameFormat -> AttributeNameFormat -> Bool
$c/= :: AttributeNameFormat -> AttributeNameFormat -> Bool
== :: AttributeNameFormat -> AttributeNameFormat -> Bool
$c== :: AttributeNameFormat -> AttributeNameFormat -> Bool
Eq, Int -> AttributeNameFormat
AttributeNameFormat -> Int
AttributeNameFormat -> [AttributeNameFormat]
AttributeNameFormat -> AttributeNameFormat
AttributeNameFormat -> AttributeNameFormat -> [AttributeNameFormat]
AttributeNameFormat
-> AttributeNameFormat
-> AttributeNameFormat
-> [AttributeNameFormat]
(AttributeNameFormat -> AttributeNameFormat)
-> (AttributeNameFormat -> AttributeNameFormat)
-> (Int -> AttributeNameFormat)
-> (AttributeNameFormat -> Int)
-> (AttributeNameFormat -> [AttributeNameFormat])
-> (AttributeNameFormat
    -> AttributeNameFormat -> [AttributeNameFormat])
-> (AttributeNameFormat
    -> AttributeNameFormat -> [AttributeNameFormat])
-> (AttributeNameFormat
    -> AttributeNameFormat
    -> AttributeNameFormat
    -> [AttributeNameFormat])
-> Enum AttributeNameFormat
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: AttributeNameFormat
-> AttributeNameFormat
-> AttributeNameFormat
-> [AttributeNameFormat]
$cenumFromThenTo :: AttributeNameFormat
-> AttributeNameFormat
-> AttributeNameFormat
-> [AttributeNameFormat]
enumFromTo :: AttributeNameFormat -> AttributeNameFormat -> [AttributeNameFormat]
$cenumFromTo :: AttributeNameFormat -> AttributeNameFormat -> [AttributeNameFormat]
enumFromThen :: AttributeNameFormat -> AttributeNameFormat -> [AttributeNameFormat]
$cenumFromThen :: AttributeNameFormat -> AttributeNameFormat -> [AttributeNameFormat]
enumFrom :: AttributeNameFormat -> [AttributeNameFormat]
$cenumFrom :: AttributeNameFormat -> [AttributeNameFormat]
fromEnum :: AttributeNameFormat -> Int
$cfromEnum :: AttributeNameFormat -> Int
toEnum :: Int -> AttributeNameFormat
$ctoEnum :: Int -> AttributeNameFormat
pred :: AttributeNameFormat -> AttributeNameFormat
$cpred :: AttributeNameFormat -> AttributeNameFormat
succ :: AttributeNameFormat -> AttributeNameFormat
$csucc :: AttributeNameFormat -> AttributeNameFormat
Enum, AttributeNameFormat
AttributeNameFormat
-> AttributeNameFormat -> Bounded AttributeNameFormat
forall a. a -> a -> Bounded a
maxBound :: AttributeNameFormat
$cmaxBound :: AttributeNameFormat
minBound :: AttributeNameFormat
$cminBound :: AttributeNameFormat
Bounded, Int -> AttributeNameFormat -> ShowS
[AttributeNameFormat] -> ShowS
AttributeNameFormat -> String
(Int -> AttributeNameFormat -> ShowS)
-> (AttributeNameFormat -> String)
-> ([AttributeNameFormat] -> ShowS)
-> Show AttributeNameFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttributeNameFormat] -> ShowS
$cshowList :: [AttributeNameFormat] -> ShowS
show :: AttributeNameFormat -> String
$cshow :: AttributeNameFormat -> String
showsPrec :: Int -> AttributeNameFormat -> ShowS
$cshowsPrec :: Int -> AttributeNameFormat -> ShowS
Show)

instance Identifiable URI AttributeNameFormat where
  identifier :: AttributeNameFormat -> URI
identifier = String -> (SAMLVersion, String) -> URI
samlURNIdentifier String
"attrname-format" ((SAMLVersion, String) -> URI)
-> (AttributeNameFormat -> (SAMLVersion, String))
-> AttributeNameFormat
-> URI
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AttributeNameFormat -> (SAMLVersion, String)
f where
    f :: AttributeNameFormat -> (SAMLVersion, String)
f AttributeNameFormat
AttributeNameFormatUnspecified = (SAMLVersion
SAML20, String
"unspecified")
    f AttributeNameFormat
AttributeNameFormatURI         = (SAMLVersion
SAML20, String
"uri")
    f AttributeNameFormat
AttributeNameFormatBasic       = (SAMLVersion
SAML20, String
"basic")

-- |§8.3
data NameIDFormat
  = NameIDFormatUnspecified -- ^§8.3.1: Text
  | NameIDFormatEmail -- ^§8.3.2: rfc2822
  | NameIDFormatX509 -- ^§8.3.3: XML signature
  | NameIDFormatWindows -- ^§8.3.4: Maybe Domain, User
  | NameIDFormatKerberos -- ^§8.3.5: rfc1510
  | NameIDFormatEntity -- ^§8.3.6: SAML endpoint (BaseId and SPProvidedID must be Nothing)
  | NameIDFormatPersistent -- ^§8.3.7: String <= 256 char (NameQualifier same as idp ident/Nothing, SPNameQualifier same as sp ident/Nothing, SPProvidedID alt ident from sp)
  | NameIDFormatTransient -- ^§8.3.8: String <= 256 char
  | NameIDFormatEncrypted -- ^§3.4.1.1: only for NameIDPolicy
  deriving (NameIDFormat -> NameIDFormat -> Bool
(NameIDFormat -> NameIDFormat -> Bool)
-> (NameIDFormat -> NameIDFormat -> Bool) -> Eq NameIDFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NameIDFormat -> NameIDFormat -> Bool
$c/= :: NameIDFormat -> NameIDFormat -> Bool
== :: NameIDFormat -> NameIDFormat -> Bool
$c== :: NameIDFormat -> NameIDFormat -> Bool
Eq, Int -> NameIDFormat
NameIDFormat -> Int
NameIDFormat -> [NameIDFormat]
NameIDFormat -> NameIDFormat
NameIDFormat -> NameIDFormat -> [NameIDFormat]
NameIDFormat -> NameIDFormat -> NameIDFormat -> [NameIDFormat]
(NameIDFormat -> NameIDFormat)
-> (NameIDFormat -> NameIDFormat)
-> (Int -> NameIDFormat)
-> (NameIDFormat -> Int)
-> (NameIDFormat -> [NameIDFormat])
-> (NameIDFormat -> NameIDFormat -> [NameIDFormat])
-> (NameIDFormat -> NameIDFormat -> [NameIDFormat])
-> (NameIDFormat -> NameIDFormat -> NameIDFormat -> [NameIDFormat])
-> Enum NameIDFormat
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: NameIDFormat -> NameIDFormat -> NameIDFormat -> [NameIDFormat]
$cenumFromThenTo :: NameIDFormat -> NameIDFormat -> NameIDFormat -> [NameIDFormat]
enumFromTo :: NameIDFormat -> NameIDFormat -> [NameIDFormat]
$cenumFromTo :: NameIDFormat -> NameIDFormat -> [NameIDFormat]
enumFromThen :: NameIDFormat -> NameIDFormat -> [NameIDFormat]
$cenumFromThen :: NameIDFormat -> NameIDFormat -> [NameIDFormat]
enumFrom :: NameIDFormat -> [NameIDFormat]
$cenumFrom :: NameIDFormat -> [NameIDFormat]
fromEnum :: NameIDFormat -> Int
$cfromEnum :: NameIDFormat -> Int
toEnum :: Int -> NameIDFormat
$ctoEnum :: Int -> NameIDFormat
pred :: NameIDFormat -> NameIDFormat
$cpred :: NameIDFormat -> NameIDFormat
succ :: NameIDFormat -> NameIDFormat
$csucc :: NameIDFormat -> NameIDFormat
Enum, NameIDFormat
NameIDFormat -> NameIDFormat -> Bounded NameIDFormat
forall a. a -> a -> Bounded a
maxBound :: NameIDFormat
$cmaxBound :: NameIDFormat
minBound :: NameIDFormat
$cminBound :: NameIDFormat
Bounded, Int -> NameIDFormat -> ShowS
[NameIDFormat] -> ShowS
NameIDFormat -> String
(Int -> NameIDFormat -> ShowS)
-> (NameIDFormat -> String)
-> ([NameIDFormat] -> ShowS)
-> Show NameIDFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NameIDFormat] -> ShowS
$cshowList :: [NameIDFormat] -> ShowS
show :: NameIDFormat -> String
$cshow :: NameIDFormat -> String
showsPrec :: Int -> NameIDFormat -> ShowS
$cshowsPrec :: Int -> NameIDFormat -> ShowS
Show)
  
instance Default NameIDFormat where
  def :: NameIDFormat
def = NameIDFormat
NameIDFormatUnspecified

instance Identifiable URI NameIDFormat where
  identifier :: NameIDFormat -> URI
identifier = String -> (SAMLVersion, String) -> URI
samlURNIdentifier String
"nameid-format" ((SAMLVersion, String) -> URI)
-> (NameIDFormat -> (SAMLVersion, String)) -> NameIDFormat -> URI
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NameIDFormat -> (SAMLVersion, String)
f where
    f :: NameIDFormat -> (SAMLVersion, String)
f NameIDFormat
NameIDFormatUnspecified = (SAMLVersion
SAML11, String
"unspecified")
    f NameIDFormat
NameIDFormatEmail       = (SAMLVersion
SAML11, String
"emailAddress")
    f NameIDFormat
NameIDFormatX509        = (SAMLVersion
SAML11, String
"X509SubjectName")
    f NameIDFormat
NameIDFormatWindows     = (SAMLVersion
SAML11, String
"WindowsDomainQualifiedName")
    f NameIDFormat
NameIDFormatKerberos    = (SAMLVersion
SAML20, String
"kerberos")
    f NameIDFormat
NameIDFormatEntity      = (SAMLVersion
SAML20, String
"entity")
    f NameIDFormat
NameIDFormatPersistent  = (SAMLVersion
SAML20, String
"persistent")
    f NameIDFormat
NameIDFormatTransient   = (SAMLVersion
SAML20, String
"transient")
    f NameIDFormat
NameIDFormatEncrypted   = (SAMLVersion
SAML20, String
"encrypted")

-- |§8.4
data Consent
  = ConsentUnspecified -- ^§8.4.1
  | ConsentObtained -- ^§8.4.2
  | ConsentPrior -- ^§8.4.3
  | ConsentImplicit -- ^§8.4.4
  | ConsentExplicit -- ^§8.4.5
  | ConsentUnavailable -- ^§8.4.6
  | ConsentInapplicable -- ^§8.4.7
  deriving (Consent -> Consent -> Bool
(Consent -> Consent -> Bool)
-> (Consent -> Consent -> Bool) -> Eq Consent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Consent -> Consent -> Bool
$c/= :: Consent -> Consent -> Bool
== :: Consent -> Consent -> Bool
$c== :: Consent -> Consent -> Bool
Eq, Int -> Consent
Consent -> Int
Consent -> [Consent]
Consent -> Consent
Consent -> Consent -> [Consent]
Consent -> Consent -> Consent -> [Consent]
(Consent -> Consent)
-> (Consent -> Consent)
-> (Int -> Consent)
-> (Consent -> Int)
-> (Consent -> [Consent])
-> (Consent -> Consent -> [Consent])
-> (Consent -> Consent -> [Consent])
-> (Consent -> Consent -> Consent -> [Consent])
-> Enum Consent
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Consent -> Consent -> Consent -> [Consent]
$cenumFromThenTo :: Consent -> Consent -> Consent -> [Consent]
enumFromTo :: Consent -> Consent -> [Consent]
$cenumFromTo :: Consent -> Consent -> [Consent]
enumFromThen :: Consent -> Consent -> [Consent]
$cenumFromThen :: Consent -> Consent -> [Consent]
enumFrom :: Consent -> [Consent]
$cenumFrom :: Consent -> [Consent]
fromEnum :: Consent -> Int
$cfromEnum :: Consent -> Int
toEnum :: Int -> Consent
$ctoEnum :: Int -> Consent
pred :: Consent -> Consent
$cpred :: Consent -> Consent
succ :: Consent -> Consent
$csucc :: Consent -> Consent
Enum, Consent
Consent -> Consent -> Bounded Consent
forall a. a -> a -> Bounded a
maxBound :: Consent
$cmaxBound :: Consent
minBound :: Consent
$cminBound :: Consent
Bounded, Int -> Consent -> ShowS
[Consent] -> ShowS
Consent -> String
(Int -> Consent -> ShowS)
-> (Consent -> String) -> ([Consent] -> ShowS) -> Show Consent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Consent] -> ShowS
$cshowList :: [Consent] -> ShowS
show :: Consent -> String
$cshow :: Consent -> String
showsPrec :: Int -> Consent -> ShowS
$cshowsPrec :: Int -> Consent -> ShowS
Show)

instance Default Consent where
  def :: Consent
def = Consent
ConsentUnspecified

instance Identifiable URI Consent where
  identifier :: Consent -> URI
identifier = String -> (SAMLVersion, String) -> URI
samlURNIdentifier String
"consent" ((SAMLVersion, String) -> URI)
-> (Consent -> (SAMLVersion, String)) -> Consent -> URI
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Consent -> (SAMLVersion, String)
f where
    f :: Consent -> (SAMLVersion, String)
f Consent
ConsentUnspecified  = (SAMLVersion
SAML20, String
"unspecified")
    f Consent
ConsentObtained     = (SAMLVersion
SAML20, String
"obtained")
    f Consent
ConsentPrior        = (SAMLVersion
SAML20, String
"prior")
    f Consent
ConsentImplicit     = (SAMLVersion
SAML20, String
"current-implicit")
    f Consent
ConsentExplicit     = (SAMLVersion
SAML20, String
"current-explicit")
    f Consent
ConsentUnavailable  = (SAMLVersion
SAML20, String
"unavailable")
    f Consent
ConsentInapplicable = (SAMLVersion
SAML20, String
"inapplicable")