{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Captcha.Internal.Types where
import Control.Lens.TH (makeFieldsNoPrefix)
import Data.Default (Default (def))
import Data.Text (Text)
import GHC.Generics (Generic)
import Time (Millisecond, Time)
import Web.Cookie (Cookies)
instance Default Bool where
def :: Bool
def = Bool
False
data ProxyProtocol = Http | Https | Socks4 | Socks5 deriving (Int -> ProxyProtocol -> ShowS
[ProxyProtocol] -> ShowS
ProxyProtocol -> String
(Int -> ProxyProtocol -> ShowS)
-> (ProxyProtocol -> String)
-> ([ProxyProtocol] -> ShowS)
-> Show ProxyProtocol
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProxyProtocol] -> ShowS
$cshowList :: [ProxyProtocol] -> ShowS
show :: ProxyProtocol -> String
$cshow :: ProxyProtocol -> String
showsPrec :: Int -> ProxyProtocol -> ShowS
$cshowsPrec :: Int -> ProxyProtocol -> ShowS
Show)
instance Default ProxyProtocol where
def :: ProxyProtocol
def = ProxyProtocol
Http
data ProxyAuth = ProxyAuth
{ ProxyAuth -> Text
_username :: Text,
ProxyAuth -> Text
_password :: Text
}
deriving ((forall x. ProxyAuth -> Rep ProxyAuth x)
-> (forall x. Rep ProxyAuth x -> ProxyAuth) -> Generic ProxyAuth
forall x. Rep ProxyAuth x -> ProxyAuth
forall x. ProxyAuth -> Rep ProxyAuth x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ProxyAuth x -> ProxyAuth
$cfrom :: forall x. ProxyAuth -> Rep ProxyAuth x
Generic, ProxyAuth
ProxyAuth -> Default ProxyAuth
forall a. a -> Default a
def :: ProxyAuth
$cdef :: ProxyAuth
Default, Int -> ProxyAuth -> ShowS
[ProxyAuth] -> ShowS
ProxyAuth -> String
(Int -> ProxyAuth -> ShowS)
-> (ProxyAuth -> String)
-> ([ProxyAuth] -> ShowS)
-> Show ProxyAuth
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProxyAuth] -> ShowS
$cshowList :: [ProxyAuth] -> ShowS
show :: ProxyAuth -> String
$cshow :: ProxyAuth -> String
showsPrec :: Int -> ProxyAuth -> ShowS
$cshowsPrec :: Int -> ProxyAuth -> ShowS
Show)
makeFieldsNoPrefix ''ProxyAuth
data Proxy = Proxy
{
Proxy -> Text
_address :: Text,
Proxy -> ProxyProtocol
_protocol :: ProxyProtocol,
Proxy -> Int
_port :: Int,
Proxy -> Maybe ProxyAuth
_auth :: Maybe ProxyAuth
}
deriving ((forall x. Proxy -> Rep Proxy x)
-> (forall x. Rep Proxy x -> Proxy) -> Generic Proxy
forall x. Rep Proxy x -> Proxy
forall x. Proxy -> Rep Proxy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Proxy x -> Proxy
$cfrom :: forall x. Proxy -> Rep Proxy x
Generic, Proxy
Proxy -> Default Proxy
forall a. a -> Default a
def :: Proxy
$cdef :: Proxy
Default, Int -> Proxy -> ShowS
[Proxy] -> ShowS
Proxy -> String
(Int -> Proxy -> ShowS)
-> (Proxy -> String) -> ([Proxy] -> ShowS) -> Show Proxy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Proxy] -> ShowS
$cshowList :: [Proxy] -> ShowS
show :: Proxy -> String
$cshow :: Proxy -> String
showsPrec :: Int -> Proxy -> ShowS
$cshowsPrec :: Int -> Proxy -> ShowS
Show)
makeFieldsNoPrefix ''Proxy
data ImageCaptcha = ImageCaptcha
{
ImageCaptcha -> Text
_apiKey :: Text,
ImageCaptcha -> Maybe (Time Millisecond)
_pollingInterval :: Maybe (Time Millisecond),
ImageCaptcha -> Maybe (Time Millisecond)
_timeoutDuration :: Maybe (Time Millisecond),
ImageCaptcha -> Text
_body :: Text
}
deriving ((forall x. ImageCaptcha -> Rep ImageCaptcha x)
-> (forall x. Rep ImageCaptcha x -> ImageCaptcha)
-> Generic ImageCaptcha
forall x. Rep ImageCaptcha x -> ImageCaptcha
forall x. ImageCaptcha -> Rep ImageCaptcha x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImageCaptcha x -> ImageCaptcha
$cfrom :: forall x. ImageCaptcha -> Rep ImageCaptcha x
Generic, ImageCaptcha
ImageCaptcha -> Default ImageCaptcha
forall a. a -> Default a
def :: ImageCaptcha
$cdef :: ImageCaptcha
Default, Int -> ImageCaptcha -> ShowS
[ImageCaptcha] -> ShowS
ImageCaptcha -> String
(Int -> ImageCaptcha -> ShowS)
-> (ImageCaptcha -> String)
-> ([ImageCaptcha] -> ShowS)
-> Show ImageCaptcha
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImageCaptcha] -> ShowS
$cshowList :: [ImageCaptcha] -> ShowS
show :: ImageCaptcha -> String
$cshow :: ImageCaptcha -> String
showsPrec :: Int -> ImageCaptcha -> ShowS
$cshowsPrec :: Int -> ImageCaptcha -> ShowS
Show)
makeFieldsNoPrefix ''ImageCaptcha
data TextCaptcha = TextCaptcha
{
TextCaptcha -> Text
_apiKey :: Text,
TextCaptcha -> Maybe (Time Millisecond)
_pollingInterval :: Maybe (Time Millisecond),
TextCaptcha -> Maybe (Time Millisecond)
_timeoutDuration :: Maybe (Time Millisecond),
TextCaptcha -> Text
_body :: Text
}
deriving ((forall x. TextCaptcha -> Rep TextCaptcha x)
-> (forall x. Rep TextCaptcha x -> TextCaptcha)
-> Generic TextCaptcha
forall x. Rep TextCaptcha x -> TextCaptcha
forall x. TextCaptcha -> Rep TextCaptcha x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TextCaptcha x -> TextCaptcha
$cfrom :: forall x. TextCaptcha -> Rep TextCaptcha x
Generic, TextCaptcha
TextCaptcha -> Default TextCaptcha
forall a. a -> Default a
def :: TextCaptcha
$cdef :: TextCaptcha
Default, Int -> TextCaptcha -> ShowS
[TextCaptcha] -> ShowS
TextCaptcha -> String
(Int -> TextCaptcha -> ShowS)
-> (TextCaptcha -> String)
-> ([TextCaptcha] -> ShowS)
-> Show TextCaptcha
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextCaptcha] -> ShowS
$cshowList :: [TextCaptcha] -> ShowS
show :: TextCaptcha -> String
$cshow :: TextCaptcha -> String
showsPrec :: Int -> TextCaptcha -> ShowS
$cshowsPrec :: Int -> TextCaptcha -> ShowS
Show)
makeFieldsNoPrefix ''TextCaptcha
data FunCaptcha = FunCaptcha
{
FunCaptcha -> Text
_apiKey :: Text,
FunCaptcha -> Maybe (Time Millisecond)
_pollingInterval :: Maybe (Time Millisecond),
FunCaptcha -> Maybe (Time Millisecond)
_timeoutDuration :: Maybe (Time Millisecond),
FunCaptcha -> Text
_captchaUrl :: Text,
FunCaptcha -> Text
_captchaKey :: Text,
FunCaptcha -> Maybe Text
_serviceUrl :: Maybe Text,
FunCaptcha -> Maybe Text
_userAgent :: Maybe Text,
FunCaptcha -> Maybe Proxy
_proxy :: Maybe Proxy,
FunCaptcha -> Cookies
_cookies :: Cookies
}
deriving ((forall x. FunCaptcha -> Rep FunCaptcha x)
-> (forall x. Rep FunCaptcha x -> FunCaptcha) -> Generic FunCaptcha
forall x. Rep FunCaptcha x -> FunCaptcha
forall x. FunCaptcha -> Rep FunCaptcha x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FunCaptcha x -> FunCaptcha
$cfrom :: forall x. FunCaptcha -> Rep FunCaptcha x
Generic, FunCaptcha
FunCaptcha -> Default FunCaptcha
forall a. a -> Default a
def :: FunCaptcha
$cdef :: FunCaptcha
Default, Int -> FunCaptcha -> ShowS
[FunCaptcha] -> ShowS
FunCaptcha -> String
(Int -> FunCaptcha -> ShowS)
-> (FunCaptcha -> String)
-> ([FunCaptcha] -> ShowS)
-> Show FunCaptcha
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FunCaptcha] -> ShowS
$cshowList :: [FunCaptcha] -> ShowS
show :: FunCaptcha -> String
$cshow :: FunCaptcha -> String
showsPrec :: Int -> FunCaptcha -> ShowS
$cshowsPrec :: Int -> FunCaptcha -> ShowS
Show)
makeFieldsNoPrefix ''FunCaptcha
data ReCaptchaV2 = ReCaptchaV2
{
ReCaptchaV2 -> Text
_apiKey :: Text,
ReCaptchaV2 -> Maybe (Time Millisecond)
_pollingInterval :: Maybe (Time Millisecond),
ReCaptchaV2 -> Maybe (Time Millisecond)
_timeoutDuration :: Maybe (Time Millisecond),
ReCaptchaV2 -> Text
_captchaUrl :: Text,
ReCaptchaV2 -> Text
_captchaKey :: Text,
ReCaptchaV2 -> Maybe Text
_dataS :: Maybe Text,
ReCaptchaV2 -> Bool
_invisible :: Bool,
ReCaptchaV2 -> Maybe Text
_userAgent :: Maybe Text,
ReCaptchaV2 -> Maybe Proxy
_proxy :: Maybe Proxy,
ReCaptchaV2 -> Cookies
_cookies :: Cookies
}
deriving ((forall x. ReCaptchaV2 -> Rep ReCaptchaV2 x)
-> (forall x. Rep ReCaptchaV2 x -> ReCaptchaV2)
-> Generic ReCaptchaV2
forall x. Rep ReCaptchaV2 x -> ReCaptchaV2
forall x. ReCaptchaV2 -> Rep ReCaptchaV2 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReCaptchaV2 x -> ReCaptchaV2
$cfrom :: forall x. ReCaptchaV2 -> Rep ReCaptchaV2 x
Generic, ReCaptchaV2
ReCaptchaV2 -> Default ReCaptchaV2
forall a. a -> Default a
def :: ReCaptchaV2
$cdef :: ReCaptchaV2
Default, Int -> ReCaptchaV2 -> ShowS
[ReCaptchaV2] -> ShowS
ReCaptchaV2 -> String
(Int -> ReCaptchaV2 -> ShowS)
-> (ReCaptchaV2 -> String)
-> ([ReCaptchaV2] -> ShowS)
-> Show ReCaptchaV2
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReCaptchaV2] -> ShowS
$cshowList :: [ReCaptchaV2] -> ShowS
show :: ReCaptchaV2 -> String
$cshow :: ReCaptchaV2 -> String
showsPrec :: Int -> ReCaptchaV2 -> ShowS
$cshowsPrec :: Int -> ReCaptchaV2 -> ShowS
Show)
makeFieldsNoPrefix ''ReCaptchaV2
data ReCaptchaV3 = ReCaptchaV3
{
ReCaptchaV3 -> Text
_apiKey :: Text,
ReCaptchaV3 -> Maybe (Time Millisecond)
_pollingInterval :: Maybe (Time Millisecond),
ReCaptchaV3 -> Maybe (Time Millisecond)
_timeoutDuration :: Maybe (Time Millisecond),
ReCaptchaV3 -> Text
_captchaUrl :: Text,
ReCaptchaV3 -> Text
_captchaKey :: Text,
ReCaptchaV3 -> Double
_minScore :: Double,
ReCaptchaV3 -> Maybe Text
_action :: Maybe Text,
ReCaptchaV3 -> Maybe Text
_userAgent :: Maybe Text,
ReCaptchaV3 -> Maybe Proxy
_proxy :: Maybe Proxy,
ReCaptchaV3 -> Cookies
_cookies :: Cookies
}
deriving ((forall x. ReCaptchaV3 -> Rep ReCaptchaV3 x)
-> (forall x. Rep ReCaptchaV3 x -> ReCaptchaV3)
-> Generic ReCaptchaV3
forall x. Rep ReCaptchaV3 x -> ReCaptchaV3
forall x. ReCaptchaV3 -> Rep ReCaptchaV3 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReCaptchaV3 x -> ReCaptchaV3
$cfrom :: forall x. ReCaptchaV3 -> Rep ReCaptchaV3 x
Generic, ReCaptchaV3
ReCaptchaV3 -> Default ReCaptchaV3
forall a. a -> Default a
def :: ReCaptchaV3
$cdef :: ReCaptchaV3
Default, Int -> ReCaptchaV3 -> ShowS
[ReCaptchaV3] -> ShowS
ReCaptchaV3 -> String
(Int -> ReCaptchaV3 -> ShowS)
-> (ReCaptchaV3 -> String)
-> ([ReCaptchaV3] -> ShowS)
-> Show ReCaptchaV3
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReCaptchaV3] -> ShowS
$cshowList :: [ReCaptchaV3] -> ShowS
show :: ReCaptchaV3 -> String
$cshow :: ReCaptchaV3 -> String
showsPrec :: Int -> ReCaptchaV3 -> ShowS
$cshowsPrec :: Int -> ReCaptchaV3 -> ShowS
Show)
makeFieldsNoPrefix ''ReCaptchaV3
data HCaptcha = HCaptcha
{
HCaptcha -> Text
_apiKey :: Text,
HCaptcha -> Maybe (Time Millisecond)
_pollingInterval :: Maybe (Time Millisecond),
HCaptcha -> Maybe (Time Millisecond)
_timeoutDuration :: Maybe (Time Millisecond),
HCaptcha -> Text
_captchaUrl :: Text,
HCaptcha -> Text
_captchaKey :: Text,
HCaptcha -> Bool
_invisible :: Bool,
HCaptcha -> Maybe Text
_rqData :: Maybe Text,
HCaptcha -> Maybe Text
_userAgent :: Maybe Text,
HCaptcha -> Maybe Proxy
_proxy :: Maybe Proxy,
HCaptcha -> Cookies
_cookies :: Cookies
}
deriving (Int -> HCaptcha -> ShowS
[HCaptcha] -> ShowS
HCaptcha -> String
(Int -> HCaptcha -> ShowS)
-> (HCaptcha -> String) -> ([HCaptcha] -> ShowS) -> Show HCaptcha
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HCaptcha] -> ShowS
$cshowList :: [HCaptcha] -> ShowS
show :: HCaptcha -> String
$cshow :: HCaptcha -> String
showsPrec :: Int -> HCaptcha -> ShowS
$cshowsPrec :: Int -> HCaptcha -> ShowS
Show, (forall x. HCaptcha -> Rep HCaptcha x)
-> (forall x. Rep HCaptcha x -> HCaptcha) -> Generic HCaptcha
forall x. Rep HCaptcha x -> HCaptcha
forall x. HCaptcha -> Rep HCaptcha x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HCaptcha x -> HCaptcha
$cfrom :: forall x. HCaptcha -> Rep HCaptcha x
Generic, HCaptcha
HCaptcha -> Default HCaptcha
forall a. a -> Default a
def :: HCaptcha
$cdef :: HCaptcha
Default)
makeFieldsNoPrefix ''HCaptcha