{-# LANGUAGE OverloadedStrings #-}
module Web.OIDC.Client.Settings
(
OIDC(..)
, def
, newOIDC
, setCredentials
) where
import Data.ByteString (ByteString)
import Data.Text (Text)
import Web.OIDC.Client.Discovery.Provider (Provider)
import qualified Web.OIDC.Client.Discovery.Provider as P
data OIDC = OIDC
{ OIDC -> Text
oidcAuthorizationServerUrl :: Text
, OIDC -> Text
oidcTokenEndpoint :: Text
, OIDC -> ByteString
oidcClientId :: ByteString
, OIDC -> ByteString
oidcClientSecret :: ByteString
, OIDC -> ByteString
oidcRedirectUri :: ByteString
, OIDC -> Provider
oidcProvider :: Provider
}
def :: OIDC
def :: OIDC
def = OIDC
{ oidcAuthorizationServerUrl :: Text
oidcAuthorizationServerUrl = forall a. HasCallStack => [Char] -> a
error [Char]
"You must specify authorizationServerUrl"
, oidcTokenEndpoint :: Text
oidcTokenEndpoint = forall a. HasCallStack => [Char] -> a
error [Char]
"You must specify tokenEndpoint"
, oidcClientId :: ByteString
oidcClientId = forall a. HasCallStack => [Char] -> a
error [Char]
"You must specify clientId"
, oidcClientSecret :: ByteString
oidcClientSecret = forall a. HasCallStack => [Char] -> a
error [Char]
"You must specify clientSecret"
, oidcRedirectUri :: ByteString
oidcRedirectUri = forall a. HasCallStack => [Char] -> a
error [Char]
"You must specify redirectUri"
, oidcProvider :: Provider
oidcProvider = forall a. HasCallStack => [Char] -> a
error [Char]
"You must specify provider"
}
newOIDC
:: Provider
-> OIDC
newOIDC :: Provider -> OIDC
newOIDC Provider
p =
OIDC
def { oidcAuthorizationServerUrl :: Text
oidcAuthorizationServerUrl = Configuration -> Text
P.authorizationEndpoint forall b c a. (b -> c) -> (a -> b) -> a -> c
. Provider -> Configuration
P.configuration forall a b. (a -> b) -> a -> b
$ Provider
p
, oidcTokenEndpoint :: Text
oidcTokenEndpoint = Configuration -> Text
P.tokenEndpoint forall b c a. (b -> c) -> (a -> b) -> a -> c
. Provider -> Configuration
P.configuration forall a b. (a -> b) -> a -> b
$ Provider
p
, oidcProvider :: Provider
oidcProvider = Provider
p
}
setCredentials
:: ByteString
-> ByteString
-> ByteString
-> OIDC
-> OIDC
setCredentials :: ByteString -> ByteString -> ByteString -> OIDC -> OIDC
setCredentials ByteString
cid ByteString
secret ByteString
redirect OIDC
oidc =
OIDC
oidc { oidcClientId :: ByteString
oidcClientId = ByteString
cid
, oidcClientSecret :: ByteString
oidcClientSecret = ByteString
secret
, oidcRedirectUri :: ByteString
oidcRedirectUri = ByteString
redirect
}