{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
module Captcha.Internal.Monad.Class where
import Captcha.Internal.Types (HasApiKey, HasPollingInterval, HasTimeoutDuration)
import Data.Aeson (Value)
import Data.ByteString.Lazy (ByteString)
import Data.Text (Text)
import Network.Wreq (Response)
import Time (Millisecond, Time)
class Monad m => MonadCaptcha api r m where
type CaptchaError api r m
createTask ::
CaptchaRequest api ctx r m =>
ctx ->
m (Either (CaptchaError api r m) (CaptchaId ctx))
getTask ::
CaptchaResponse api ctx =>
Text ->
CaptchaId ctx ->
m (Either (CaptchaError api r m) Text)
solve ::
( CaptchaRequest api ctx r m,
CaptchaResponse api ctx,
HasApiKey ctx Text,
HasPollingInterval ctx (Maybe (Time Millisecond)),
HasTimeoutDuration ctx (Maybe (Time Millisecond))
) =>
ctx ->
m (Either (CaptchaError api r m) Text)
class CaptchaRequest api ctx r m where
request ::
ctx ->
Text ->
m (Response ByteString)
class CaptchaResponse api ctx where
parseResult :: Value -> Maybe Value
newtype CaptchaId ctx = CaptchaId
{ CaptchaId ctx -> Integer
unCaptchaId :: Integer
}
deriving (Int -> CaptchaId ctx -> ShowS
[CaptchaId ctx] -> ShowS
CaptchaId ctx -> String
(Int -> CaptchaId ctx -> ShowS)
-> (CaptchaId ctx -> String)
-> ([CaptchaId ctx] -> ShowS)
-> Show (CaptchaId ctx)
forall ctx. Int -> CaptchaId ctx -> ShowS
forall ctx. [CaptchaId ctx] -> ShowS
forall ctx. CaptchaId ctx -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CaptchaId ctx] -> ShowS
$cshowList :: forall ctx. [CaptchaId ctx] -> ShowS
show :: CaptchaId ctx -> String
$cshow :: forall ctx. CaptchaId ctx -> String
showsPrec :: Int -> CaptchaId ctx -> ShowS
$cshowsPrec :: forall ctx. Int -> CaptchaId ctx -> ShowS
Show, CaptchaId ctx -> CaptchaId ctx -> Bool
(CaptchaId ctx -> CaptchaId ctx -> Bool)
-> (CaptchaId ctx -> CaptchaId ctx -> Bool) -> Eq (CaptchaId ctx)
forall ctx. CaptchaId ctx -> CaptchaId ctx -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CaptchaId ctx -> CaptchaId ctx -> Bool
$c/= :: forall ctx. CaptchaId ctx -> CaptchaId ctx -> Bool
== :: CaptchaId ctx -> CaptchaId ctx -> Bool
$c== :: forall ctx. CaptchaId ctx -> CaptchaId ctx -> Bool
Eq, Eq (CaptchaId ctx)
Eq (CaptchaId ctx)
-> (CaptchaId ctx -> CaptchaId ctx -> Ordering)
-> (CaptchaId ctx -> CaptchaId ctx -> Bool)
-> (CaptchaId ctx -> CaptchaId ctx -> Bool)
-> (CaptchaId ctx -> CaptchaId ctx -> Bool)
-> (CaptchaId ctx -> CaptchaId ctx -> Bool)
-> (CaptchaId ctx -> CaptchaId ctx -> CaptchaId ctx)
-> (CaptchaId ctx -> CaptchaId ctx -> CaptchaId ctx)
-> Ord (CaptchaId ctx)
CaptchaId ctx -> CaptchaId ctx -> Bool
CaptchaId ctx -> CaptchaId ctx -> Ordering
CaptchaId ctx -> CaptchaId ctx -> CaptchaId ctx
forall ctx. Eq (CaptchaId ctx)
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall ctx. CaptchaId ctx -> CaptchaId ctx -> Bool
forall ctx. CaptchaId ctx -> CaptchaId ctx -> Ordering
forall ctx. CaptchaId ctx -> CaptchaId ctx -> CaptchaId ctx
min :: CaptchaId ctx -> CaptchaId ctx -> CaptchaId ctx
$cmin :: forall ctx. CaptchaId ctx -> CaptchaId ctx -> CaptchaId ctx
max :: CaptchaId ctx -> CaptchaId ctx -> CaptchaId ctx
$cmax :: forall ctx. CaptchaId ctx -> CaptchaId ctx -> CaptchaId ctx
>= :: CaptchaId ctx -> CaptchaId ctx -> Bool
$c>= :: forall ctx. CaptchaId ctx -> CaptchaId ctx -> Bool
> :: CaptchaId ctx -> CaptchaId ctx -> Bool
$c> :: forall ctx. CaptchaId ctx -> CaptchaId ctx -> Bool
<= :: CaptchaId ctx -> CaptchaId ctx -> Bool
$c<= :: forall ctx. CaptchaId ctx -> CaptchaId ctx -> Bool
< :: CaptchaId ctx -> CaptchaId ctx -> Bool
$c< :: forall ctx. CaptchaId ctx -> CaptchaId ctx -> Bool
compare :: CaptchaId ctx -> CaptchaId ctx -> Ordering
$ccompare :: forall ctx. CaptchaId ctx -> CaptchaId ctx -> Ordering
$cp1Ord :: forall ctx. Eq (CaptchaId ctx)
Ord)