Safe Haskell | None |
---|---|
Language | Haskell98 |
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"
- data ApiKey
- api_key :: ApiKey -> String
- api_host :: ApiKey -> String
- type CaptchaID = Int
- data CaptchaConf = CaptchaConf {}
- data ApiResult a
- = OK a
- | CAPCHA_NOT_READY
- | ERROR_WRONG_USER_KEY
- | ERROR_WRONG_ID_FORMAT
- | ERROR_KEY_DOES_NOT_EXIST
- | ERROR_ZERO_BALANCE
- | ERROR_NO_SLOT_AVAILABLE
- | ERROR_ZERO_CAPTCHA_FILESIZE
- | ERROR_TOO_BIG_CAPTCHA_FILESIZE
- | ERROR_WRONG_FILE_EXTENSION
- | ERROR_IMAGE_TYPE_NOT_SUPPORTED
- | ERROR_IP_NOT_ALLOWED
- | ERROR_UNKNOWN String
- data SolveException
- = SolveExceptionUpload (ApiResult ())
- | SolveExceptionCheck CaptchaID (ApiResult ())
- data SolveConf = SolveConf {
- api_upload_sleep :: [Int]
- api_check_sleep :: [Int]
- api_counter :: Phase -> Int -> IO ()
- api_upload_callback :: CaptchaID -> IO ()
- data Phase
- solveCaptcha :: (Failure HttpException m, MonadIO m, MonadThrow m) => SolveConf -> ApiKey -> CaptchaConf -> FilePath -> ByteString -> Manager -> m (CaptchaID, String)
- solveCaptchaFromFile :: (Failure HttpException m, MonadIO m, MonadThrow m) => SolveConf -> ApiKey -> CaptchaConf -> FilePath -> Manager -> m (CaptchaID, String)
- uploadCaptcha :: (Failure HttpException m, MonadIO m, MonadThrow m) => ApiKey -> CaptchaConf -> FilePath -> ByteString -> Manager -> m (ApiResult CaptchaID)
- uploadCaptchaFromFile :: (Failure HttpException m, MonadIO m, MonadThrow m) => ApiKey -> CaptchaConf -> FilePath -> Manager -> m (ApiResult CaptchaID)
- checkCaptcha :: (Failure HttpException m, MonadIO m, MonadThrow m) => ApiKey -> CaptchaID -> Manager -> m (ApiResult String)
- checkCaptchas :: (Failure HttpException m, MonadIO m, MonadThrow m) => ApiKey -> [CaptchaID] -> Manager -> m [ApiResult String]
- reportBad :: (Failure HttpException m, MonadIO m, MonadThrow m) => ApiKey -> CaptchaID -> Manager -> m Bool
- getBalance :: (Failure HttpException m, MonadIO m, MonadThrow m) => ApiKey -> Manager -> m Double
- data Manager :: *
- newManager :: ManagerSettings -> IO Manager
- closeManager :: Manager -> IO ()
- withManager :: (MonadIO m, MonadBaseControl IO m) => (Manager -> ResourceT m a) -> m a
- parseUploadResponse :: String -> ApiResult CaptchaID
- parseCheckResponse :: String -> ApiResult String
- parseMultiCheckResponse :: String -> ApiResult String
- parseMultiCheckResponses :: String -> [ApiResult String]
- renderApiResult :: ApiResult String -> String
Documentation
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.
data CaptchaConf Source #
Properties of the captcha to be solved. See http://antigate.com/panel.php?action=api
CaptchaConf | |
|
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 |
High level
data SolveException Source #
SolveConf | |
|
:: (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.
solveCaptchaFromFile :: (Failure HttpException m, MonadIO m, MonadThrow m) => SolveConf -> ApiKey -> CaptchaConf -> FilePath -> Manager -> m (CaptchaID, String) Source #
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.
uploadCaptchaFromFile :: (Failure HttpException m, MonadIO m, MonadThrow m) => ApiKey -> CaptchaConf -> FilePath -> Manager -> m (ApiResult CaptchaID) Source #
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
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
withManager :: (MonadIO m, MonadBaseControl IO m) => (Manager -> ResourceT m a) -> m a #