{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}

module Network.OAuth2.Provider.ZOHO where

import Data.Aeson
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 ZOHO = ZOHO deriving (ZOHO -> ZOHO -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ZOHO -> ZOHO -> Bool
$c/= :: ZOHO -> ZOHO -> Bool
== :: ZOHO -> ZOHO -> Bool
$c== :: ZOHO -> ZOHO -> Bool
Eq, Int -> ZOHO -> ShowS
[ZOHO] -> ShowS
ZOHO -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ZOHO] -> ShowS
$cshowList :: [ZOHO] -> ShowS
show :: ZOHO -> String
$cshow :: ZOHO -> String
showsPrec :: Int -> ZOHO -> ShowS
$cshowsPrec :: Int -> ZOHO -> ShowS
Show)

type instance IdpUserInfo ZOHO = ZOHOUserResp

defaultZohoApp :: IdpApplication 'AuthorizationCode ZOHO
defaultZohoApp :: IdpApplication 'AuthorizationCode ZOHO
defaultZohoApp =
  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
"ZohoCRM.users.READ"]
    , $sel:idpAppAuthorizeExtraParams:AuthorizationCodeIdpApplication :: Map Text Text
idpAppAuthorizeExtraParams = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Text
"access_type", Text
"offline"), (Text
"prompt", Text
"consent")]
    , $sel:idpAppAuthorizeState:AuthorizationCodeIdpApplication :: AuthorizeState
idpAppAuthorizeState = AuthorizeState
"CHANGE_ME"
    , $sel:idpAppRedirectUri:AuthorizationCodeIdpApplication :: URI
idpAppRedirectUri = [uri|http://localhost/oauth2/callback|]
    , $sel:idpAppName:AuthorizationCodeIdpApplication :: Text
idpAppName = Text
"default-zoho-App"
    , $sel:idpAppTokenRequestAuthenticationMethod:AuthorizationCodeIdpApplication :: ClientAuthenticationMethod
idpAppTokenRequestAuthenticationMethod = ClientAuthenticationMethod
ClientSecretBasic
    , $sel:idp:AuthorizationCodeIdpApplication :: Idp ZOHO
idp = Idp ZOHO
defaultZohoIdp
    }

defaultZohoIdp :: Idp ZOHO
defaultZohoIdp :: Idp ZOHO
defaultZohoIdp =
  Idp
    { $sel:idpFetchUserInfo:Idp :: forall (m :: * -> *).
(FromJSON (IdpUserInfo ZOHO), MonadIO m) =>
Manager
-> AccessToken -> URI -> ExceptT ByteString m (IdpUserInfo ZOHO)
idpFetchUserInfo = forall a (m :: * -> *).
(FromJSON a, MonadIO m) =>
Manager -> AccessToken -> URI -> ExceptT ByteString m a
authGetJSON @(IdpUserInfo ZOHO)
    , $sel:idpUserInfoEndpoint:Idp :: URI
idpUserInfoEndpoint = [uri|https://www.zohoapis.com/crm/v2/users|]
    , $sel:idpAuthorizeEndpoint:Idp :: URI
idpAuthorizeEndpoint = [uri|https://accounts.zoho.com/oauth/v2/auth|]
    , $sel:idpTokenEndpoint:Idp :: URI
idpTokenEndpoint = [uri|https://accounts.zoho.com/oauth/v2/token|]
    }

-- `oauth/user/info` url does not work and find answer from
-- https://help.zoho.com/portal/community/topic/oauth2-api-better-document-oauth-user-info
data ZOHOUser = ZOHOUser
  { ZOHOUser -> Text
email :: Text
  , ZOHOUser -> Text
fullName :: Text
  }
  deriving (Int -> ZOHOUser -> ShowS
[ZOHOUser] -> ShowS
ZOHOUser -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ZOHOUser] -> ShowS
$cshowList :: [ZOHOUser] -> ShowS
show :: ZOHOUser -> String
$cshow :: ZOHOUser -> String
showsPrec :: Int -> ZOHOUser -> ShowS
$cshowsPrec :: Int -> ZOHOUser -> ShowS
Show, forall x. Rep ZOHOUser x -> ZOHOUser
forall x. ZOHOUser -> Rep ZOHOUser x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ZOHOUser x -> ZOHOUser
$cfrom :: forall x. ZOHOUser -> Rep ZOHOUser x
Generic)

newtype ZOHOUserResp = ZOHOUserResp {ZOHOUserResp -> [ZOHOUser]
users :: [ZOHOUser]}
  deriving (Int -> ZOHOUserResp -> ShowS
[ZOHOUserResp] -> ShowS
ZOHOUserResp -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ZOHOUserResp] -> ShowS
$cshowList :: [ZOHOUserResp] -> ShowS
show :: ZOHOUserResp -> String
$cshow :: ZOHOUserResp -> String
showsPrec :: Int -> ZOHOUserResp -> ShowS
$cshowsPrec :: Int -> ZOHOUserResp -> ShowS
Show, forall x. Rep ZOHOUserResp x -> ZOHOUserResp
forall x. ZOHOUserResp -> Rep ZOHOUserResp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ZOHOUserResp x -> ZOHOUserResp
$cfrom :: forall x. ZOHOUserResp -> Rep ZOHOUserResp x
Generic)

instance FromJSON ZOHOUserResp

instance FromJSON ZOHOUser where
  parseJSON :: Value -> Parser ZOHOUser
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions {fieldLabelModifier :: ShowS
fieldLabelModifier = Char -> ShowS
camelTo2 Char
'_'}