{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
module Network.OAuth2.Provider.Twitter where
import Data.Aeson
import Data.Char (toLower)
import Data.Map.Strict qualified as Map
import Data.Set qualified as Set
import Data.Text.Lazy (Text)
import GHC.Generics
import Network.OAuth.OAuth2
import Network.OAuth2.Experiment
import URI.ByteString.QQ
data = deriving (Twitter -> Twitter -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Twitter -> Twitter -> Bool
$c/= :: Twitter -> Twitter -> Bool
== :: Twitter -> Twitter -> Bool
$c== :: Twitter -> Twitter -> Bool
Eq, Int -> Twitter -> ShowS
[Twitter] -> ShowS
Twitter -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Twitter] -> ShowS
$cshowList :: [Twitter] -> ShowS
show :: Twitter -> String
$cshow :: Twitter -> String
showsPrec :: Int -> Twitter -> ShowS
$cshowsPrec :: Int -> Twitter -> ShowS
Show)
type instance IdpUserInfo Twitter = TwitterUserResp
defaultTwitterApp :: IdpApplication 'AuthorizationCode Twitter
=
AuthorizationCodeIdpApplication
{ $sel:idpAppClientId:AuthorizationCodeIdpApplication :: ClientId
idpAppClientId = ClientId
""
, $sel:idpAppClientSecret:AuthorizationCodeIdpApplication :: ClientSecret
idpAppClientSecret = ClientSecret
""
, $sel:idpAppScope:AuthorizationCodeIdpApplication :: Set Scope
idpAppScope = forall a. Ord a => [a] -> Set a
Set.fromList [Scope
"tweet.read", Scope
"users.read"]
, $sel:idpAppAuthorizeState:AuthorizationCodeIdpApplication :: AuthorizeState
idpAppAuthorizeState = AuthorizeState
"CHANGE_ME"
, $sel:idpAppAuthorizeExtraParams:AuthorizationCodeIdpApplication :: Map Text Text
idpAppAuthorizeExtraParams = forall k a. Map k a
Map.empty
, $sel:idpAppRedirectUri:AuthorizationCodeIdpApplication :: URI
idpAppRedirectUri = [uri|http://localhost|]
, $sel:idpAppName:AuthorizationCodeIdpApplication :: Text
idpAppName = Text
"default-twitter-App"
, $sel:idpAppTokenRequestAuthenticationMethod:AuthorizationCodeIdpApplication :: ClientAuthenticationMethod
idpAppTokenRequestAuthenticationMethod = ClientAuthenticationMethod
ClientSecretBasic
, $sel:idp:AuthorizationCodeIdpApplication :: Idp Twitter
idp = Idp Twitter
defaultTwitterIdp
}
defaultTwitterIdp :: Idp Twitter
=
Idp
{ $sel:idpFetchUserInfo:Idp :: forall (m :: * -> *).
(FromJSON (IdpUserInfo Twitter), MonadIO m) =>
Manager
-> AccessToken -> URI -> ExceptT ByteString m (IdpUserInfo Twitter)
idpFetchUserInfo = forall a (m :: * -> *).
(FromJSON a, MonadIO m) =>
Manager -> AccessToken -> URI -> ExceptT ByteString m a
authGetJSON @(IdpUserInfo Twitter)
, $sel:idpUserInfoEndpoint:Idp :: URI
idpUserInfoEndpoint = [uri|https://api.twitter.com/2/users/me|]
, $sel:idpAuthorizeEndpoint:Idp :: URI
idpAuthorizeEndpoint = [uri|https://twitter.com/i/oauth2/authorize|]
, $sel:idpTokenEndpoint:Idp :: URI
idpTokenEndpoint = [uri|https://api.twitter.com/2/oauth2/token|]
}
data =
{ TwitterUser -> Text
name :: Text
, TwitterUser -> Text
id :: Text
, TwitterUser -> Text
username :: Text
}
deriving (Int -> TwitterUser -> ShowS
[TwitterUser] -> ShowS
TwitterUser -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TwitterUser] -> ShowS
$cshowList :: [TwitterUser] -> ShowS
show :: TwitterUser -> String
$cshow :: TwitterUser -> String
showsPrec :: Int -> TwitterUser -> ShowS
$cshowsPrec :: Int -> TwitterUser -> ShowS
Show, forall x. Rep TwitterUser x -> TwitterUser
forall x. TwitterUser -> Rep TwitterUser x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TwitterUser x -> TwitterUser
$cfrom :: forall x. TwitterUser -> Rep TwitterUser x
Generic)
newtype = { :: TwitterUser}
deriving (Int -> TwitterUserResp -> ShowS
[TwitterUserResp] -> ShowS
TwitterUserResp -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TwitterUserResp] -> ShowS
$cshowList :: [TwitterUserResp] -> ShowS
show :: TwitterUserResp -> String
$cshow :: TwitterUserResp -> String
showsPrec :: Int -> TwitterUserResp -> ShowS
$cshowsPrec :: Int -> TwitterUserResp -> ShowS
Show, forall x. Rep TwitterUserResp x -> TwitterUserResp
forall x. TwitterUserResp -> Rep TwitterUserResp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TwitterUserResp x -> TwitterUserResp
$cfrom :: forall x. TwitterUserResp -> Rep TwitterUserResp x
Generic)
instance FromJSON TwitterUserResp where
parseJSON :: Value -> Parser TwitterUserResp
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options
defaultOptions {fieldLabelModifier :: ShowS
fieldLabelModifier = forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> [a] -> [a]
drop Int
15})
instance FromJSON TwitterUser