{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Captcha.TwoCaptcha.Internal.Types.ReCaptchaV3 where
import Captcha.Internal.Monad (HasCaptchaEnv)
import Captcha.Internal.Monad.Class (CaptchaRequest (request))
import Captcha.Internal.Request (post)
import Captcha.Internal.Types (HasApiKey (apiKey), HasCaptchaKey (captchaKey), HasCaptchaUrl (captchaUrl), HasMinScore (minScore), ReCaptchaV3)
import Captcha.TwoCaptcha.Internal (TwoCaptcha, defaultOptions)
import Control.Lens ((&), (.~), (^.))
import Control.Monad.Cont (MonadIO)
import Control.Monad.Reader (MonadReader)
import Data.Aeson (object)
import Data.String.Conversions (cs)
import Network.Wreq (param)
instance (HasCaptchaEnv r, MonadReader r m, MonadIO m) => CaptchaRequest TwoCaptcha ReCaptchaV3 r m where
request :: ReCaptchaV3 -> Text -> m (Response ByteString)
request ReCaptchaV3
captcha = (Text -> Value -> m (Response ByteString))
-> Value -> Text -> m (Response ByteString)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Options -> Text -> Value -> m (Response ByteString)
forall r (m :: * -> *) a.
(HasCaptchaEnv r, MonadReader r m, MonadIO m, Postable a) =>
Options -> Text -> a -> m (Response ByteString)
post Options
options) ([Pair] -> Value
object [])
where
options :: Options
options =
Options
defaultOptions
Options -> (Options -> Options) -> Options
forall a b. a -> (a -> b) -> b
& Text -> Lens' Options [Text]
param Text
"key" (([Text] -> Identity [Text]) -> Options -> Identity Options)
-> [Text] -> Options -> Options
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [ReCaptchaV3
captcha ReCaptchaV3 -> Getting Text ReCaptchaV3 Text -> Text
forall s a. s -> Getting a s a -> a
^. Getting Text ReCaptchaV3 Text
forall s a. HasApiKey s a => Lens' s a
apiKey]
Options -> (Options -> Options) -> Options
forall a b. a -> (a -> b) -> b
& Text -> Lens' Options [Text]
param Text
"method" (([Text] -> Identity [Text]) -> Options -> Identity Options)
-> [Text] -> Options -> Options
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Text
"userrecaptcha"]
Options -> (Options -> Options) -> Options
forall a b. a -> (a -> b) -> b
& Text -> Lens' Options [Text]
param Text
"version" (([Text] -> Identity [Text]) -> Options -> Identity Options)
-> [Text] -> Options -> Options
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Text
"v3"]
Options -> (Options -> Options) -> Options
forall a b. a -> (a -> b) -> b
& Text -> Lens' Options [Text]
param Text
"googlekey" (([Text] -> Identity [Text]) -> Options -> Identity Options)
-> [Text] -> Options -> Options
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [ReCaptchaV3
captcha ReCaptchaV3 -> Getting Text ReCaptchaV3 Text -> Text
forall s a. s -> Getting a s a -> a
^. Getting Text ReCaptchaV3 Text
forall s a. HasCaptchaKey s a => Lens' s a
captchaKey]
Options -> (Options -> Options) -> Options
forall a b. a -> (a -> b) -> b
& Text -> Lens' Options [Text]
param Text
"pageurl" (([Text] -> Identity [Text]) -> Options -> Identity Options)
-> [Text] -> Options -> Options
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [ReCaptchaV3
captcha ReCaptchaV3 -> Getting Text ReCaptchaV3 Text -> Text
forall s a. s -> Getting a s a -> a
^. Getting Text ReCaptchaV3 Text
forall s a. HasCaptchaUrl s a => Lens' s a
captchaUrl]
Options -> (Options -> Options) -> Options
forall a b. a -> (a -> b) -> b
& Text -> Lens' Options [Text]
param Text
"min_score" (([Text] -> Identity [Text]) -> Options -> Identity Options)
-> [Text] -> Options -> Options
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [String -> Text
forall a b. ConvertibleStrings a b => a -> b
cs (String -> Text) -> (Double -> String) -> Double -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> String
forall a. Show a => a -> String
show (Double -> Text) -> Double -> Text
forall a b. (a -> b) -> a -> b
$ ReCaptchaV3
captcha ReCaptchaV3 -> Getting Double ReCaptchaV3 Double -> Double
forall s a. s -> Getting a s a -> a
^. Getting Double ReCaptchaV3 Double
forall s a. HasMinScore s a => Lens' s a
minScore]