antigate-2.0.2: Interface for antigate.com captcha recognition API

Safe HaskellNone
LanguageHaskell98

Text.Recognition.Antigate

Contents

Description

Example:

{-# LANGUAGE OverloadedStrings #-}
import Text.Recognition.Antigate
import Data.Default
import Network
import Control.Monad
import Control.Monad.IO.Class
import Data.ByteString.Lazy hiding (putStrLn)
import System.Timeout

myApiKey :: ApiKey
myApiKey = "0123456789abcdef0123456789abcdef"{api_host="antigate.com"}

downloadJpegCaptcha :: Manager -> IO ByteString
downloadJpegCaptcha = undefined

answerCaptcha :: String -> Manager -> IO Bool
answerCaptcha = undefined

main :: IO ()
main = withSocketsDo $ do
    res <- timeout (30*1000000) $ withManager $ \m -> do
        bytes <- liftIO $ downloadJpegCaptcha m
        (id, answer) <- solveCaptcha def myApiKey def{phrase=True} "captcha.jpg" bytes m
        res <- liftIO $ answerCaptcha answer m
        unless res $ reportBad myApiKey id m
        return res
    case res of
        Nothing -> do
            putStrLn "Timed out"
        Just True -> do
            putStrLn "Solved successfully"
        Just False -> do
            putStrLn "Couldn't solve"

Synopsis

Documentation

data ApiKey Source #

Antigate API access key paired with service provider's host. At least these services claim to support Antigate API: Antigate, Captchabot, Decaptcher, ExpertDecoders, ImageTyperz, DeathByCaptcha and Pixodrom.

api_key :: ApiKey -> String Source #

This is a record selector

api_host :: ApiKey -> String Source #

default: "antigate.com". This is a record selector

data CaptchaConf Source #

Properties of the captcha to be solved. See http://antigate.com/panel.php?action=api

Constructors

CaptchaConf 

Fields

data ApiResult a Source #

Constructors

OK a 
CAPCHA_NOT_READY

captcha is not recognized yet, repeat request withing 1-5 seconds

ERROR_WRONG_USER_KEY

user authorization key is invalid (its length is not 32 bytes as it should be)

ERROR_WRONG_ID_FORMAT

the captcha ID you are sending is non-numeric

ERROR_KEY_DOES_NOT_EXIST

you have set wrong user authorization key in request

ERROR_ZERO_BALANCE

account has zero or negative balance

ERROR_NO_SLOT_AVAILABLE

no idle captcha workers are available at the moment, please try a bit later or try increasing your bid

ERROR_ZERO_CAPTCHA_FILESIZE

the size of the captcha you are uploading or pointing to is zero

ERROR_TOO_BIG_CAPTCHA_FILESIZE

your captcha size is exceeding 100kb limit

ERROR_WRONG_FILE_EXTENSION

your captcha file has wrong extension, the only allowed extensions are gif,jpg,jpeg,png

ERROR_IMAGE_TYPE_NOT_SUPPORTED

Could not determine captcha file type, only allowed formats are JPG, GIF, PNG

ERROR_IP_NOT_ALLOWED

Request with current account key is not allowed from your IP. Please refer to IP list section

ERROR_UNKNOWN String 

Instances

Functor ApiResult Source # 

Methods

fmap :: (a -> b) -> ApiResult a -> ApiResult b #

(<$) :: a -> ApiResult b -> ApiResult a #

Eq a => Eq (ApiResult a) Source # 

Methods

(==) :: ApiResult a -> ApiResult a -> Bool #

(/=) :: ApiResult a -> ApiResult a -> Bool #

Read a => Read (ApiResult a) Source # 
Show a => Show (ApiResult a) Source # 
NFData a => NFData (ApiResult a) Source # 

Methods

rnf :: ApiResult a -> () #

High level

data SolveConf Source #

Constructors

SolveConf 

Fields

  • api_upload_sleep :: [Int]

    how much to sleep while waiting for available slot; in microseconds.

    Default: [3000000]

  • api_check_sleep :: [Int]

    how much to sleep between captcha checks; in microseconds.

    Default: [6000000,2000000,3000000] -- sleep 6 seconds before checking, on first retry sleep 2 seconds, then always sleep 3 seconds. List can be infinite

  • api_counter :: Phase -> Int -> IO ()

    api_counter will be called at the start of each phase

    api_counter = \phase count -> do
        if count == 0
          then putStrLn $ show phase ++ " began"
          else putStrLn $ show phase ++ " retries: " ++ show count

    Default: _ _ -> return ()

  • api_upload_callback :: CaptchaID -> IO ()

    This will be called when upload phase finishes

solveCaptcha Source #

Arguments

:: (Failure HttpException m, MonadIO m, MonadThrow m) 
=> SolveConf 
-> ApiKey 
-> CaptchaConf 
-> FilePath

image filename (antigate guesses filetype by file extension)

-> ByteString

image contents

-> Manager

HTTP connection manager to use

-> m (CaptchaID, String) 

High level function to solve captcha, blocks until answer is provided (about 2-10 seconds).

throws SolveException or HttpException when something goes wrong.

Core functions

uploadCaptcha :: (Failure HttpException m, MonadIO m, MonadThrow m) => ApiKey -> CaptchaConf -> FilePath -> ByteString -> Manager -> m (ApiResult CaptchaID) Source #

upload captcha for recognition

throws HttpException on network errors.

checkCaptcha :: (Failure HttpException m, MonadIO m, MonadThrow m) => ApiKey -> CaptchaID -> Manager -> m (ApiResult String) Source #

retrieve captcha status

throws HttpException on network errors.

checkCaptchas :: (Failure HttpException m, MonadIO m, MonadThrow m) => ApiKey -> [CaptchaID] -> Manager -> m [ApiResult String] Source #

retrieve multiple captcha status

throws HttpException on network errors.

reportBad :: (Failure HttpException m, MonadIO m, MonadThrow m) => ApiKey -> CaptchaID -> Manager -> m Bool Source #

report bad captcha result

throws HttpException on network errors.

getBalance :: (Failure HttpException m, MonadIO m, MonadThrow m) => ApiKey -> Manager -> m Double Source #

retrieve your current account balance

throws HttpException on network errors.

Connection manager

data Manager :: * #

Keeps track of open connections for keep-alive.

If possible, you should share a single Manager between multiple threads and requests.

Since 0.1.0

newManager :: ManagerSettings -> IO Manager #

Create a Manager. The Manager will be shut down automatically via garbage collection.

Creating a new Manager is a relatively expensive operation, you are advised to share a single Manager between requests instead.

The first argument to this function is often defaultManagerSettings, though add-on libraries may provide a recommended replacement.

Since 0.1.0

closeManager :: Manager -> IO () #

Close all connections in a Manager.

Note that this doesn't affect currently in-flight connections, meaning you can safely use it without hurting any queries you may have concurrently running.

Since 0.1.0

Miscellaneous

parseUploadResponse :: String -> ApiResult CaptchaID Source #

Parse antigate's upload response

parseCheckResponse :: String -> ApiResult String Source #

Parse antigate's check response

parseMultiCheckResponse :: String -> ApiResult String Source #

Parse antigate's multi-check response

parseMultiCheckResponses :: String -> [ApiResult String] Source #

Parse antigate's multi-check response

renderApiResult :: ApiResult String -> String Source #

Marshal ApiResult back to its text form