{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Captcha.TwoCaptcha.Internal.Types.FunCaptcha where
import Captcha.Internal.Monad (HasCaptchaEnv)
import Captcha.Internal.Monad.Class (CaptchaRequest (request))
import Captcha.Internal.Request (post)
import Captcha.Internal.Types (FunCaptcha, HasApiKey (apiKey), HasCaptchaKey (captchaKey), HasCaptchaUrl (captchaUrl), HasServiceUrl (serviceUrl), HasUserAgent (userAgent))
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 Network.Wreq (param)
instance (HasCaptchaEnv r, MonadReader r m, MonadIO m) => CaptchaRequest TwoCaptcha FunCaptcha r m where
request :: FunCaptcha -> Text -> m (Response ByteString)
request FunCaptcha
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
.~ [FunCaptcha
captcha FunCaptcha -> Getting Text FunCaptcha Text -> Text
forall s a. s -> Getting a s a -> a
^. Getting Text FunCaptcha 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
"funcaptcha"]
Options -> (Options -> Options) -> Options
forall a b. a -> (a -> b) -> b
& Text -> Lens' Options [Text]
param Text
"publickey" (([Text] -> Identity [Text]) -> Options -> Identity Options)
-> [Text] -> Options -> Options
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [FunCaptcha
captcha FunCaptcha -> Getting Text FunCaptcha Text -> Text
forall s a. s -> Getting a s a -> a
^. Getting Text FunCaptcha 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
.~ [FunCaptcha
captcha FunCaptcha -> Getting Text FunCaptcha Text -> Text
forall s a. s -> Getting a s a -> a
^. Getting Text FunCaptcha 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
"surl" (([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 (FunCaptcha
captcha FunCaptcha
-> Getting (Maybe Text) FunCaptcha (Maybe Text) -> Maybe Text
forall s a. s -> Getting a s a -> a
^. Getting (Maybe Text) FunCaptcha (Maybe Text)
forall s a. HasServiceUrl s a => Lens' s a
serviceUrl)
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 (FunCaptcha
captcha FunCaptcha
-> Getting (Maybe Text) FunCaptcha (Maybe Text) -> Maybe Text
forall s a. s -> Getting a s a -> a
^. Getting (Maybe Text) FunCaptcha (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
"proxy" (([Text] -> Identity [Text]) -> Options -> Identity Options)
-> [Text] -> Options -> Options
forall s t a b. ASetter s t a b -> b -> s -> t
.~ FunCaptcha -> [Text]
forall a. HasProxy a (Maybe Proxy) => a -> [Text]
parseProxy FunCaptcha
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
.~ FunCaptcha -> [Text]
forall a. HasProxy a (Maybe Proxy) => a -> [Text]
parseProxyType FunCaptcha
captcha