antigate-0.3: Haskell interface for antigate.com captcha recognition service, and other services which support its API.

Safe HaskellNone

Text.Recognition.Antigate

Contents

Description

Example:

 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"
 
 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.

Constructors

ApiKey 

Fields

api_host :: String

default: "antigate.com"

api_key :: String
 

data CaptchaConf Source

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

Constructors

CaptchaConf 

Fields

phrase :: Bool
  • False = default value (one word)
  • True = captcha has 2-4 words
regsense :: Bool
  • False = default value (case is not important)
  • True = captcha is case sensitive
numeric :: Maybe Bool
  • Nothing = default value
  • Just True = captcha consists from numbers only
  • Just False = captcha does not have numbers on it
calc :: Bool
  • False = default value
  • True = numbers on captcha must be summed
min_len :: Word
  • 0 = default value
  • >0 = minimum length of captcha text workers required to input
max_len :: Word
  • 0 = default value (unlimited)
  • >0 = maximum length of captcha text workers required to input
is_russian :: Bool
  • False = default value
  • True = captcha goes to Russian-speaking worker
max_bid :: Maybe Double

Default value is set on bids page. This parameter allows to control maximum bid without setting it on the bids page.

data UploadResult Source

Constructors

UPLOAD_OK CaptchaID

result is positive, your captcha is accepted for recognition and its ID follows. You may now attempt to retrieve captcha status with this ID.

ERROR_WRONG_USER_KEY

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

UPLOAD_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

UPLOAD_ERROR_UNKNOWN String 

data CheckResult Source

Constructors

CHECK_OK String

the captcha is recognized, the guessed text follows

CAPCHA_NOT_READY

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

CHECK_ERROR_KEY_DOES_NOT_EXIST

you have set wrong user authorization key in request

ERROR_WRONG_ID_FORMAT

the captcha ID you are sending is non-numeric

CHECK_ERROR_UNKNOWN String 

High level

data SolveConf Source

Constructors

SolveConf 

Fields

api_upload_sleep :: Int

how much to sleep while waiting for available slot. Microseconds.

api_check_sleep :: Int

how much to sleep between captcha checks. Microseconds.

api_counter :: Phase -> IO ()

This action will be executed before each sleep. e.g. print

solveCaptchaSource

Arguments

:: MonadResource 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 :: MonadResource m => ApiKey -> CaptchaConf -> FilePath -> ByteString -> Manager -> m UploadResultSource

upload captcha for recognition

throws HttpException on network errors.

checkCaptcha :: MonadResource m => ApiKey -> CaptchaID -> Manager -> m CheckResultSource

retrieve captcha status

throws HttpException on network errors.

checkCaptchas :: MonadResource m => ApiKey -> [CaptchaID] -> Manager -> m [CheckResult]Source

retrieve multiple captcha status

throws HttpException on network errors.

reportBad :: MonadResource m => ApiKey -> CaptchaID -> Manager -> m ()Source

report bad captcha result

throws HttpException on network errors.

getBalance :: MonadResource m => ApiKey -> Manager -> m DoubleSource

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.

newManager :: ManagerSettings -> IO Manager

Create a Manager. You must manually call closeManager to shut it down.

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

closeManager :: Manager -> IO ()

Close all connections in a Manager. Afterwards, the Manager can be reused if desired.

withManager :: (MonadIO m, MonadBaseControl IO m, MonadThrow m, MonadUnsafeIO m) => (Manager -> ResourceT m a) -> m a

Create a new manager, use it in the provided function, and then release it.

This function uses the default manager settings. For more control, use withManagerSettings.

Miscellaneous

parseUploadResult :: String -> UploadResultSource

Parse antigate's upload response

parseCheckResult :: String -> CheckResultSource

Parse antigate's check response

parseCheckResults :: String -> [CheckResult]Source

Parse antigate's multi-check response

parseCheckResultNoOK :: String -> CheckResultSource

Parse antigate's multi-check response

renderUploadResult :: UploadResult -> StringSource

Marshal UploadResult back to its text form

renderCheckResult :: CheckResult -> StringSource

Marshal CheckResult back to its text form