{-# LANGUAGE OverloadedStrings #-}
module Test.WebDriverWrapper.Helpers (download, decompressGecko, decompressZip, evalUntillSuccess) where
import Test.WebDriverWrapper.Constants (fileFormat, geckoDriverPath)
import Network.HTTP.Simple (setRequestHeader, setRequestMethod, httpLBS)
import Network.HTTP.Types (hUserAgent)
import Network.HTTP.Conduit (Response(..), parseRequest)
import qualified Data.ByteString.Lazy as BS
import Codec.Archive.Zip (toArchive, extractFilesFromArchive, ZipOption (OptDestination))
import qualified Codec.Compression.GZip as G
import qualified Codec.Archive.Tar as Tar
import System.Posix ( setFileMode, accessModes )
import Control.Exception (catch)
import Control.Exception.Base (SomeException)
download :: String -> FilePath -> IO()
download :: String -> String -> IO ()
download String
url String
output = do
Request
requestUrl <- String -> IO Request
forall (m :: * -> *). MonadThrow m => String -> m Request
parseRequest String
url
let
request :: Request
request
= ByteString -> Request -> Request
setRequestMethod ByteString
"GET"
(Request -> Request) -> Request -> Request
forall a b. (a -> b) -> a -> b
$ HeaderName -> [ByteString] -> Request -> Request
setRequestHeader HeaderName
hUserAgent [ByteString
"cli"]
Request
requestUrl
ByteString
response <- Response ByteString -> ByteString
forall body. Response body -> body
responseBody (Response ByteString -> ByteString)
-> IO (Response ByteString) -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Request -> IO (Response ByteString)
forall (m :: * -> *).
MonadIO m =>
Request -> m (Response ByteString)
httpLBS Request
request
String -> ByteString -> IO ()
BS.writeFile String
output ByteString
response
decompressGecko :: FilePath -> FilePath -> IO()
decompressGecko :: String -> String -> IO ()
decompressGecko String
file String
outputPath = do
case String
fileFormat of
String
".zip" -> String -> String -> IO ()
decompressZip String
file String
outputPath
String
".tar.gz" -> String -> String -> IO ()
decompressTarball String
file String
outputPath
String
_ -> String -> IO ()
forall a. HasCallStack => String -> a
error String
"unknown file"
decompressZip :: FilePath -> FilePath -> IO()
decompressZip :: String -> String -> IO ()
decompressZip String
file String
outputPath = do
Archive
archive <- ByteString -> Archive
toArchive (ByteString -> Archive) -> IO ByteString -> IO Archive
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO ByteString
BS.readFile String
file
[ZipOption] -> Archive -> IO ()
extractFilesFromArchive [String -> ZipOption
OptDestination String
outputPath] Archive
archive
decompressTarball :: FilePath -> FilePath -> IO()
decompressTarball :: String -> String -> IO ()
decompressTarball String
file String
outputPath = do
ByteString
tarball <- ByteString -> ByteString
G.decompress (ByteString -> ByteString) -> IO ByteString -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO ByteString
BS.readFile String
file
String -> Entries FormatError -> IO ()
forall e. Exception e => String -> Entries e -> IO ()
Tar.unpack String
outputPath (Entries FormatError -> IO ()) -> Entries FormatError -> IO ()
forall a b. (a -> b) -> a -> b
$ ByteString -> Entries FormatError
Tar.read ByteString
tarball
String
geckoDriver <- IO String
geckoDriverPath
String -> FileMode -> IO ()
setFileMode String
geckoDriver FileMode
accessModes
evalUntillSuccess :: [IO String] -> IO String
evalUntillSuccess :: [IO String] -> IO String
evalUntillSuccess [] = String -> IO String
forall a. HasCallStack => String -> a
error String
"None succeeded on evalUntillSuccess!"
evalUntillSuccess (IO String
x:[IO String]
xs) = IO String -> (SomeException -> IO String) -> IO String
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catch IO String
x (IO String -> SomeException -> IO String
forall a b. a -> b -> a
const (IO String -> SomeException -> IO String)
-> IO String -> SomeException -> IO String
forall a b. (a -> b) -> a -> b
$ [IO String] -> IO String
evalUntillSuccess [IO String]
xs :: SomeException -> IO String)