{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Captcha.TwoCaptcha.Internal.Types.ReCaptchaV2 where
import Captcha.Internal (renderCookies)
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), HasDataS (dataS), HasInvisible (invisible), HasUserAgent (userAgent), ReCaptchaV2)
import Captcha.TwoCaptcha.Internal (TwoCaptcha, defaultOptions, parseProxy, parseProxyType)
import Control.Lens ((&), (.~), (^.))
import Control.Monad.Cont (MonadIO)
import Control.Monad.Reader (MonadReader)
import Data.Aeson (object)
import Data.Maybe (maybeToList)
import Data.String.Conversions (cs)
import Network.Wreq (param)
instance (HasCaptchaEnv r, MonadReader r m, MonadIO m) => CaptchaRequest TwoCaptcha ReCaptchaV2 r m where
request :: ReCaptchaV2 -> Text -> m (Response ByteString)
request ReCaptchaV2
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
.~ [ReCaptchaV2
captcha ReCaptchaV2 -> Getting Text ReCaptchaV2 Text -> Text
forall s a. s -> Getting a s a -> a
^. Getting Text ReCaptchaV2 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
"googlekey" (([Text] -> Identity [Text]) -> Options -> Identity Options)
-> [Text] -> Options -> Options
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [ReCaptchaV2
captcha ReCaptchaV2 -> Getting Text ReCaptchaV2 Text -> Text
forall s a. s -> Getting a s a -> a
^. Getting Text ReCaptchaV2 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
.~ [ReCaptchaV2
captcha ReCaptchaV2 -> Getting Text ReCaptchaV2 Text -> Text
forall s a. s -> Getting a s a -> a
^. Getting Text ReCaptchaV2 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
"data-s" (([Text] -> Identity [Text]) -> Options -> Identity Options)
-> [Text] -> Options -> Options
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Maybe Text -> [Text]
forall a. Maybe a -> [a]
maybeToList (ReCaptchaV2
captcha ReCaptchaV2
-> Getting (Maybe Text) ReCaptchaV2 (Maybe Text) -> Maybe Text
forall s a. s -> Getting a s a -> a
^. Getting (Maybe Text) ReCaptchaV2 (Maybe Text)
forall s a. HasDataS s a => Lens' s a
dataS)
Options -> (Options -> Options) -> Options
forall a b. a -> (a -> b) -> b
& Text -> Lens' Options [Text]
param Text
"invisible" (([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) -> (Bool -> String) -> Bool -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> String
forall a. Show a => a -> String
show (Bool -> Text) -> Bool -> Text
forall a b. (a -> b) -> a -> b
$ ReCaptchaV2
captcha ReCaptchaV2 -> Getting Bool ReCaptchaV2 Bool -> Bool
forall s a. s -> Getting a s a -> a
^. Getting Bool ReCaptchaV2 Bool
forall s a. HasInvisible s a => Lens' s a
invisible]
Options -> (Options -> Options) -> Options
forall a b. a -> (a -> b) -> b
& Text -> Lens' Options [Text]
param Text
"userAgent" (([Text] -> Identity [Text]) -> Options -> Identity Options)
-> [Text] -> Options -> Options
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Maybe Text -> [Text]
forall a. Maybe a -> [a]
maybeToList (ReCaptchaV2
captcha ReCaptchaV2
-> Getting (Maybe Text) ReCaptchaV2 (Maybe Text) -> Maybe Text
forall s a. s -> Getting a s a -> a
^. Getting (Maybe Text) ReCaptchaV2 (Maybe Text)
forall s a. HasUserAgent s a => Lens' s a
userAgent)
Options -> (Options -> Options) -> Options
forall a b. a -> (a -> b) -> b
& Text -> Lens' Options [Text]
param Text
"cookies" (([Text] -> Identity [Text]) -> Options -> Identity Options)
-> [Text] -> Options -> Options
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [ReCaptchaV2 -> Text
forall a. HasCookies a Cookies => a -> Text
renderCookies ReCaptchaV2
captcha]
Options -> (Options -> Options) -> Options
forall a b. a -> (a -> b) -> b
& Text -> Lens' Options [Text]
param Text
"proxy" (([Text] -> Identity [Text]) -> Options -> Identity Options)
-> [Text] -> Options -> Options
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ReCaptchaV2 -> [Text]
forall a. HasProxy a (Maybe Proxy) => a -> [Text]
parseProxy ReCaptchaV2
captcha
Options -> (Options -> Options) -> Options
forall a b. a -> (a -> b) -> b
& Text -> Lens' Options [Text]
param Text
"proxytype" (([Text] -> Identity [Text]) -> Options -> Identity Options)
-> [Text] -> Options -> Options
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ReCaptchaV2 -> [Text]
forall a. HasProxy a (Maybe Proxy) => a -> [Text]
parseProxyType ReCaptchaV2
captcha