{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# OPTIONS_GHC -Wno-orphans #-}

-- |
-- Module: Captcha.CapMonster.Internal.Types.Image
-- Copyright: (c) 2022 Edward Yang
-- License: MIT
--
-- This module is for internal-use and does not follow pvp versioning policies.
module Captcha.CapMonster.Internal.Types.Image where

import Captcha.CapMonster.Internal (CapMonster)
import Captcha.Internal.Monad (HasCaptchaEnv)
import Captcha.Internal.Monad.Class (CaptchaRequest (request), CaptchaResponse (parseResult))
import Captcha.Internal.Request (post)
import Captcha.Internal.Types (HasApiKey (apiKey), HasBody (body), ImageCaptcha)
import Control.Lens (preview, (^.))
import Control.Monad.IO.Class (MonadIO)
import Control.Monad.Reader (MonadReader)
import Data.Aeson.Lens (key)
import Data.Aeson.QQ (aesonQQ)
import Network.Wreq (defaults)

instance (HasCaptchaEnv r, MonadReader r m, MonadIO m) => CaptchaRequest CapMonster ImageCaptcha r m where
  request :: ImageCaptcha -> Text -> m (Response ByteString)
request ImageCaptcha
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
defaults) Value
payload
    where
      payload :: Value
payload =
        [aesonQQ|
          {
            clientKey: #{captcha ^. apiKey},
            task: {
              type: "ImageToTextTask",
              body: #{captcha ^. body}
            }
          }
        |]

instance CaptchaResponse CapMonster ImageCaptcha where
  parseResult :: Value -> Maybe Value
parseResult = Getting (First Value) Value Value -> Value -> Maybe Value
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview (Getting (First Value) Value Value -> Value -> Maybe Value)
-> Getting (First Value) Value Value -> Value -> Maybe Value
forall a b. (a -> b) -> a -> b
$ Text -> Traversal' Value Value
forall t. AsValue t => Text -> Traversal' t Value
key Text
"solution" Getting (First Value) Value Value
-> Getting (First Value) Value Value
-> Getting (First Value) Value Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Traversal' Value Value
forall t. AsValue t => Text -> Traversal' t Value
key Text
"text"