module Web.Api.WebDriver.Helpers (
writeDataFile
, readDataFile
, writeJsonFile
, readJsonFile
, stashCookies
, loadCookies
, press
, typeString
) where
import Control.Monad.Trans.Class
( MonadTrans(..) )
import qualified Data.Aeson as Aeson
( encode, ToJSON(..), Value )
import Data.ByteString.Lazy
( ByteString )
import qualified Data.ByteString.Lazy.Char8 as BS
( pack )
import qualified Data.Digest.Pure.SHA as SHA
( showDigest, sha1 )
import Web.Api.WebDriver.Endpoints
import Web.Api.WebDriver.Monad
import Web.Api.WebDriver.Types
import Web.Api.WebDriver.Types.Keyboard
stashCookies
:: (Monad eff, Monad (t eff), MonadTrans t)
=> String
-> WebDriverTT t eff ()
stashCookies string =
let file = SHA.showDigest $ SHA.sha1 $ BS.pack string in
getAllCookies >>= writeCookieFile file
loadCookies
:: (Monad eff, Monad (t eff), MonadTrans t)
=> String
-> WebDriverTT t eff Bool
loadCookies string = do
let file = SHA.showDigest $ SHA.sha1 $ BS.pack string
contents <- readCookieFile file
case contents of
Nothing -> return False
Just cs -> do
mapM_ addCookie cs
return True
writeCookieFile
:: (Monad eff, Monad (t eff), MonadTrans t)
=> FilePath
-> [Cookie]
-> WebDriverTT t eff ()
writeCookieFile file cookies = do
path <- fromEnv (_dataPath . _env)
let fullpath = path ++ "/secrets/cookies/" ++ file
writeFilePath fullpath (Aeson.encode cookies)
readCookieFile
:: (Monad eff, Monad (t eff), MonadTrans t)
=> FilePath
-> WebDriverTT t eff (Maybe [Cookie])
readCookieFile file = do
path <- fromEnv (_dataPath . _env)
let fullpath = path ++ "/secrets/cookies/" ++ file
cookieFileExists <- fileExists fullpath
if cookieFileExists
then readFilePath fullpath
>>= parseJson
>>= constructFromJson
>>= mapM constructFromJson
>>= (return . Just)
else return Nothing
writeDataFile
:: (Monad eff, Monad (t eff), MonadTrans t)
=> FilePath
-> ByteString
-> WebDriverTT t eff ()
writeDataFile file contents = do
path <- fromEnv (_dataPath . _env)
writeFilePath (path ++ file) contents
readDataFile
:: (Monad eff, Monad (t eff), MonadTrans t)
=> FilePath
-> WebDriverTT t eff ByteString
readDataFile file = do
path <- fromEnv (_dataPath . _env)
readFilePath $ path ++ file
writeJsonFile
:: (Monad eff, Monad (t eff), MonadTrans t, Aeson.ToJSON a)
=> FilePath
-> a
-> WebDriverTT t eff ()
writeJsonFile file a = do
path <- fromEnv (_dataPath . _env)
writeFilePath (path ++ file) (Aeson.encode $ Aeson.toJSON a)
readJsonFile
:: (Monad eff, Monad (t eff), MonadTrans t)
=> FilePath
-> WebDriverTT t eff Aeson.Value
readJsonFile file = do
path <- fromEnv (_dataPath . _env)
readFilePath (path ++ file) >>= parseJson
keypress :: Char -> ActionItem
keypress x = emptyActionItem
{ _actionType = Just KeyDownAction
, _actionValue = Just [x]
}
press :: Key -> Action
press key = emptyAction
{ _inputSourceType = Just KeyInputSource
, _inputSourceId = Just "kbd"
, _actionItems = [keypress (keyToChar key)]
}
typeString :: String -> Action
typeString x = emptyAction
{ _inputSourceType = Just KeyInputSource
, _inputSourceId = Just "kbd"
, _actionItems = map keypress x
}