| Safe Haskell | None |
|---|
Text.Recognition.Antigate
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"
- data ApiKey = ApiKey {}
- type CaptchaID = Int
- data CaptchaConf = CaptchaConf {}
- data UploadResult
- = UPLOAD_OK CaptchaID
- | ERROR_WRONG_USER_KEY
- | UPLOAD_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
- | UPLOAD_ERROR_UNKNOWN String
- data CheckResult
- data SolveException
- data SolveConf = SolveConf {
- api_upload_sleep :: Int
- api_check_sleep :: Int
- api_counter :: Phase -> IO ()
- data Phase
- solveCaptcha :: MonadResource m => SolveConf -> ApiKey -> CaptchaConf -> FilePath -> ByteString -> Manager -> m (CaptchaID, String)
- solveCaptchaFromFile :: (MonadBaseControl IO m, MonadResource m) => SolveConf -> ApiKey -> CaptchaConf -> FilePath -> Manager -> m (CaptchaID, String)
- uploadCaptcha :: MonadResource m => ApiKey -> CaptchaConf -> FilePath -> ByteString -> Manager -> m UploadResult
- uploadCaptchaFromFile :: MonadResource m => ApiKey -> CaptchaConf -> FilePath -> Manager -> m UploadResult
- checkCaptcha :: MonadResource m => ApiKey -> CaptchaID -> Manager -> m CheckResult
- checkCaptchas :: MonadResource m => ApiKey -> [CaptchaID] -> Manager -> m [CheckResult]
- reportBad :: MonadResource m => ApiKey -> CaptchaID -> Manager -> m ()
- getBalance :: MonadResource m => ApiKey -> Manager -> m Double
- data Manager
- newManager :: ManagerSettings -> IO Manager
- closeManager :: Manager -> IO ()
- withManager :: (MonadIO m, MonadBaseControl IO m, MonadThrow m, MonadUnsafeIO m) => (Manager -> ResourceT m a) -> m a
- parseUploadResult :: String -> UploadResult
- parseCheckResult :: String -> CheckResult
- parseCheckResults :: String -> [CheckResult]
- parseCheckResultNoOK :: String -> CheckResult
- renderUploadResult :: UploadResult -> String
- renderCheckResult :: CheckResult -> 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
Constructors
| CaptchaConf | |
Fields
| |
Instances
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 |
Instances
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 |
Instances
High level
data SolveException Source
Constructors
| SolveConf | |
Fields
| |
Constructors
| UploadPhase | |
| CheckPhase |
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.
solveCaptchaFromFile :: (MonadBaseControl IO m, MonadResource m) => SolveConf -> ApiKey -> CaptchaConf -> FilePath -> Manager -> m (CaptchaID, String)Source
Core functions
uploadCaptcha :: MonadResource m => ApiKey -> CaptchaConf -> FilePath -> ByteString -> Manager -> m UploadResultSource
upload captcha for recognition
throws HttpException on network errors.
uploadCaptchaFromFile :: MonadResource m => ApiKey -> CaptchaConf -> FilePath -> Manager -> m UploadResultSource
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 ()
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