Skip to content

Instantly share code, notes, and snippets.

Show Gist options
  • Save SergeyStretovich/0c054c24da622ee0b99b45f7fd09cc2e to your computer and use it in GitHub Desktop.
Save SergeyStretovich/0c054c24da622ee0b99b45f7fd09cc2e to your computer and use it in GitHub Desktop.
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
import Network.HTTP.Conduit
import Network.HTTP.Simple
import Control.Monad
import qualified Data.ByteString.Lazy.Char8 as L8
import qualified Data.ByteString.Char8 as C
import Control.Exception (try)
import Control.Concurrent.Async
import Data.Time.Clock (diffUTCTime, getCurrentTime)
import Control.Monad.IO.Class (liftIO)
import Data.Function
import Data.Sort
{-
getProxList = [(Proxy "180.210.204.53" 3128),(Proxy "181.177.250.221" 8080),(Proxy "190.214.9.34" 4153),(Proxy "200.54.78.178" 4153)]
-}
main = do
totalTimeStart <- liftIO getCurrentTime
proxies <- (getProxyListFromFile "C:\\HASKELL_PROJECTS\\proxylist.txt")
listUnsorted <- mapConcurrently runProxyTest proxies
{-
xs <- mapM (async . getProxyTest1) proxies
lstS <- mapM wait xs
-}
let sorted = sortBy (compare `on` snd) $ catEither listUnsorted
let leftList = catEitherLeft listUnsorted
forM_ sorted (\(i,j)-> do
Prelude.putStrLn (i ++" time "++(show j))
Prelude.putStrLn "---------------------")
Prelude.putStrLn "%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%"
forM_ leftList (\(i,j)-> do
Prelude.putStrLn (i ++" error "++ j)
Prelude.putStrLn "---------------------")
totalTimeEnd <- liftIO getCurrentTime
let timeTruncated = truncate' (realToFrac (diffUTCTime totalTimeEnd totalTimeStart) :: Double) 3
putStrLn ("total time : " ++ (show timeTruncated))
getProxyListFromFile::String->IO[Proxy]
getProxyListFromFile st = do
proxyTextContent <- Prelude.readFile st
let txLines = map (\xc -> words xc) $ lines proxyTextContent
let proxies = map (\[xa,xb] -> Proxy (C.pack $ xa) (read $ xb::Int)) txLines
return proxies
truncate' :: Double -> Int -> Double
truncate' x n = (fromIntegral (floor (x * t))) / t
where t = 10^n
catEither :: [Either a b] -> [b]
catEither ls = [x | Right x <- ls]
catEitherLeft :: [Either a b] -> [a]
catEitherLeft ls = [x | Left x <- ls]
runProxyTest:: Proxy -> IO( Either (String,String) (String,Double))
runProxyTest proxyItem = do
let strProxy = "proxy host: " ++(C.unpack (proxyHost proxyItem))++" port: "++(show $ proxyPort proxyItem )
timeStart <- liftIO getCurrentTime
let request = setRequestProxy (Just proxyItem)
$ "https://httpbin.org/get"
eResponse::(Either HttpException (Response L8.ByteString)) <- try $ httpLBS request
timeEnd <- liftIO getCurrentTime
let timeTruncated = truncate' (realToFrac (diffUTCTime timeEnd timeStart) :: Double) 3
let funcGetResp eR = case eR of
Left error -> Left (strProxy,(show error))
Right response -> Right (strProxy,timeTruncated )
let resultOfHttpReq = funcGetResp eResponse
return resultOfHttpReq
{-
180.210.204.53 3128
181.177.250.221 8080
190.214.9.34 4153
200.54.78.178 4153
-}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment