{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
-- |
-- Confirmation Method Identifiers
-- 
-- <https://docs.oasis-open.org/security/saml/v2.0/saml-profiles-2.0-os.pdf saml-profiles-2.0-os> §3
module SAML2.Profiles.ConfirmationMethod where

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

-- |§3
data ConfirmationMethod
  = ConfirmationMethodHolderOfKey
  | ConfirmationMethodSenderVouches
  | ConfirmationMethodBearer
  deriving (ConfirmationMethod -> ConfirmationMethod -> Bool
(ConfirmationMethod -> ConfirmationMethod -> Bool)
-> (ConfirmationMethod -> ConfirmationMethod -> Bool)
-> Eq ConfirmationMethod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConfirmationMethod -> ConfirmationMethod -> Bool
$c/= :: ConfirmationMethod -> ConfirmationMethod -> Bool
== :: ConfirmationMethod -> ConfirmationMethod -> Bool
$c== :: ConfirmationMethod -> ConfirmationMethod -> Bool
Eq, Int -> ConfirmationMethod
ConfirmationMethod -> Int
ConfirmationMethod -> [ConfirmationMethod]
ConfirmationMethod -> ConfirmationMethod
ConfirmationMethod -> ConfirmationMethod -> [ConfirmationMethod]
ConfirmationMethod
-> ConfirmationMethod -> ConfirmationMethod -> [ConfirmationMethod]
(ConfirmationMethod -> ConfirmationMethod)
-> (ConfirmationMethod -> ConfirmationMethod)
-> (Int -> ConfirmationMethod)
-> (ConfirmationMethod -> Int)
-> (ConfirmationMethod -> [ConfirmationMethod])
-> (ConfirmationMethod
    -> ConfirmationMethod -> [ConfirmationMethod])
-> (ConfirmationMethod
    -> ConfirmationMethod -> [ConfirmationMethod])
-> (ConfirmationMethod
    -> ConfirmationMethod
    -> ConfirmationMethod
    -> [ConfirmationMethod])
-> Enum ConfirmationMethod
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 :: ConfirmationMethod
-> ConfirmationMethod -> ConfirmationMethod -> [ConfirmationMethod]
$cenumFromThenTo :: ConfirmationMethod
-> ConfirmationMethod -> ConfirmationMethod -> [ConfirmationMethod]
enumFromTo :: ConfirmationMethod -> ConfirmationMethod -> [ConfirmationMethod]
$cenumFromTo :: ConfirmationMethod -> ConfirmationMethod -> [ConfirmationMethod]
enumFromThen :: ConfirmationMethod -> ConfirmationMethod -> [ConfirmationMethod]
$cenumFromThen :: ConfirmationMethod -> ConfirmationMethod -> [ConfirmationMethod]
enumFrom :: ConfirmationMethod -> [ConfirmationMethod]
$cenumFrom :: ConfirmationMethod -> [ConfirmationMethod]
fromEnum :: ConfirmationMethod -> Int
$cfromEnum :: ConfirmationMethod -> Int
toEnum :: Int -> ConfirmationMethod
$ctoEnum :: Int -> ConfirmationMethod
pred :: ConfirmationMethod -> ConfirmationMethod
$cpred :: ConfirmationMethod -> ConfirmationMethod
succ :: ConfirmationMethod -> ConfirmationMethod
$csucc :: ConfirmationMethod -> ConfirmationMethod
Enum, ConfirmationMethod
ConfirmationMethod
-> ConfirmationMethod -> Bounded ConfirmationMethod
forall a. a -> a -> Bounded a
maxBound :: ConfirmationMethod
$cmaxBound :: ConfirmationMethod
minBound :: ConfirmationMethod
$cminBound :: ConfirmationMethod
Bounded, Int -> ConfirmationMethod -> ShowS
[ConfirmationMethod] -> ShowS
ConfirmationMethod -> String
(Int -> ConfirmationMethod -> ShowS)
-> (ConfirmationMethod -> String)
-> ([ConfirmationMethod] -> ShowS)
-> Show ConfirmationMethod
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConfirmationMethod] -> ShowS
$cshowList :: [ConfirmationMethod] -> ShowS
show :: ConfirmationMethod -> String
$cshow :: ConfirmationMethod -> String
showsPrec :: Int -> ConfirmationMethod -> ShowS
$cshowsPrec :: Int -> ConfirmationMethod -> ShowS
Show)

instance Identifiable URI ConfirmationMethod where
  identifier :: ConfirmationMethod -> URI
identifier = String -> (SAMLVersion, String) -> URI
samlURNIdentifier String
"cm" ((SAMLVersion, String) -> URI)
-> (ConfirmationMethod -> (SAMLVersion, String))
-> ConfirmationMethod
-> URI
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfirmationMethod -> (SAMLVersion, String)
f where
    f :: ConfirmationMethod -> (SAMLVersion, String)
f ConfirmationMethod
ConfirmationMethodHolderOfKey   = (SAMLVersion
SAML20, String
"holder-of-key")
    f ConfirmationMethod
ConfirmationMethodSenderVouches = (SAMLVersion
SAML20, String
"sender-vouches")
    f ConfirmationMethod
ConfirmationMethodBearer        = (SAMLVersion
SAML20, String
"bearer")