{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
module Network.OAuth.OAuth2.AuthorizationRequest where
import Data.Aeson
import Data.Function (on)
import Data.List qualified as List
import Data.Text.Encoding qualified as T
import GHC.Generics (Generic)
import Lens.Micro (over)
import Network.OAuth.OAuth2.Internal
import URI.ByteString
instance FromJSON Errors where
parseJSON :: Value -> Parser Errors
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions {constructorTagModifier :: String -> String
constructorTagModifier = Char -> String -> String
camelTo2 Char
'_'}
data Errors
= InvalidRequest
| UnauthorizedClient
| AccessDenied
| UnsupportedResponseType
| InvalidScope
| ServerError
| TemporarilyUnavailable
deriving (Int -> Errors -> String -> String
[Errors] -> String -> String
Errors -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Errors] -> String -> String
$cshowList :: [Errors] -> String -> String
show :: Errors -> String
$cshow :: Errors -> String
showsPrec :: Int -> Errors -> String -> String
$cshowsPrec :: Int -> Errors -> String -> String
Show, Errors -> Errors -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Errors -> Errors -> Bool
$c/= :: Errors -> Errors -> Bool
== :: Errors -> Errors -> Bool
$c== :: Errors -> Errors -> Bool
Eq, forall x. Rep Errors x -> Errors
forall x. Errors -> Rep Errors x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Errors x -> Errors
$cfrom :: forall x. Errors -> Rep Errors x
Generic)
authorizationUrl :: OAuth2 -> URI
authorizationUrl :: OAuth2 -> URI
authorizationUrl = QueryParams -> OAuth2 -> URI
authorizationUrlWithParams []
authorizationUrlWithParams :: QueryParams -> OAuth2 -> URI
authorizationUrlWithParams :: QueryParams -> OAuth2 -> URI
authorizationUrlWithParams QueryParams
qs OAuth2
oa = forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (forall a. Lens' (URIRef a) Query
queryL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' Query QueryParams
queryPairsL) (forall a. [a] -> [a] -> [a]
++ QueryParams
queryParts) (OAuth2 -> URI
oauth2AuthorizeEndpoint OAuth2
oa)
where
queryParts :: QueryParams
queryParts =
forall a. (a -> a -> Bool) -> [a] -> [a]
List.nubBy (forall a. Eq a => a -> a -> Bool
(==) forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` forall a b. (a, b) -> a
fst) forall a b. (a -> b) -> a -> b
$
QueryParams
qs
forall a. [a] -> [a] -> [a]
++ [ (ByteString
"client_id", Text -> ByteString
T.encodeUtf8 forall a b. (a -> b) -> a -> b
$ OAuth2 -> Text
oauth2ClientId OAuth2
oa)
, (ByteString
"response_type", ByteString
"code")
, (ByteString
"redirect_uri", forall a. URIRef a -> ByteString
serializeURIRef' forall a b. (a -> b) -> a -> b
$ OAuth2 -> URI
oauth2RedirectUri OAuth2
oa)
]