{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
module Test.WebDriver.Capabilities.ChromeOptions where
import Control.Monad.IO.Class
import Data.Aeson
import Data.Aeson as A
import Data.Aeson.TH
import Data.ByteString.Base64.Lazy as B64
import Data.ByteString.Lazy as LBS
import qualified Data.Text.Lazy as TL
import Data.Text.Lazy.Encoding (decodeLatin1)
import Lens.Micro.TH
import Test.WebDriver.Capabilities.Aeson
data ChromeDeviceMetrics = ChromeDeviceMetrics {
ChromeDeviceMetrics -> Maybe Int
_chromeDeviceMetricsWidth :: Maybe Int
, ChromeDeviceMetrics -> Maybe Int
_chromeDeviceMetricsHeight :: Maybe Int
, ChromeDeviceMetrics -> Maybe Double
_chromeDeviceMetricsPixelRatio :: Maybe Double
, ChromeDeviceMetrics -> Maybe Bool
_chromeDeviceMetricsTouch :: Maybe Bool
, ChromeDeviceMetrics -> Maybe Bool
_chromeDeviceMetricsMobile :: Maybe Bool
} deriving (Int -> ChromeDeviceMetrics -> ShowS
[ChromeDeviceMetrics] -> ShowS
ChromeDeviceMetrics -> String
(Int -> ChromeDeviceMetrics -> ShowS)
-> (ChromeDeviceMetrics -> String)
-> ([ChromeDeviceMetrics] -> ShowS)
-> Show ChromeDeviceMetrics
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChromeDeviceMetrics -> ShowS
showsPrec :: Int -> ChromeDeviceMetrics -> ShowS
$cshow :: ChromeDeviceMetrics -> String
show :: ChromeDeviceMetrics -> String
$cshowList :: [ChromeDeviceMetrics] -> ShowS
showList :: [ChromeDeviceMetrics] -> ShowS
Show, ChromeDeviceMetrics -> ChromeDeviceMetrics -> Bool
(ChromeDeviceMetrics -> ChromeDeviceMetrics -> Bool)
-> (ChromeDeviceMetrics -> ChromeDeviceMetrics -> Bool)
-> Eq ChromeDeviceMetrics
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChromeDeviceMetrics -> ChromeDeviceMetrics -> Bool
== :: ChromeDeviceMetrics -> ChromeDeviceMetrics -> Bool
$c/= :: ChromeDeviceMetrics -> ChromeDeviceMetrics -> Bool
/= :: ChromeDeviceMetrics -> ChromeDeviceMetrics -> Bool
Eq)
deriveJSON toCamel3 ''ChromeDeviceMetrics
makeLenses ''ChromeDeviceMetrics
data BrandAndVersion = BrandAndVersion {
BrandAndVersion -> String
brandAndVersionBrand :: String
, BrandAndVersion -> String
brandAndVersionVersion :: String
} deriving (Int -> BrandAndVersion -> ShowS
[BrandAndVersion] -> ShowS
BrandAndVersion -> String
(Int -> BrandAndVersion -> ShowS)
-> (BrandAndVersion -> String)
-> ([BrandAndVersion] -> ShowS)
-> Show BrandAndVersion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BrandAndVersion -> ShowS
showsPrec :: Int -> BrandAndVersion -> ShowS
$cshow :: BrandAndVersion -> String
show :: BrandAndVersion -> String
$cshowList :: [BrandAndVersion] -> ShowS
showList :: [BrandAndVersion] -> ShowS
Show, BrandAndVersion -> BrandAndVersion -> Bool
(BrandAndVersion -> BrandAndVersion -> Bool)
-> (BrandAndVersion -> BrandAndVersion -> Bool)
-> Eq BrandAndVersion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BrandAndVersion -> BrandAndVersion -> Bool
== :: BrandAndVersion -> BrandAndVersion -> Bool
$c/= :: BrandAndVersion -> BrandAndVersion -> Bool
/= :: BrandAndVersion -> BrandAndVersion -> Bool
Eq)
deriveJSON toCamel3 ''BrandAndVersion
makeLenses ''BrandAndVersion
data ChromeClientHints = ChromeClientHints {
ChromeClientHints -> String
_chromeClientHintsPlatform :: String
, ChromeClientHints -> Bool
_chromeClientHintsMobile :: Bool
, ChromeClientHints -> Maybe [BrandAndVersion]
_chromeClientHintsBrands :: Maybe [BrandAndVersion]
, ChromeClientHints -> Maybe [BrandAndVersion]
_chromeClientHintsFullVersionList :: Maybe [BrandAndVersion]
, ChromeClientHints -> Maybe String
_chromeClientHintsPlatformVersion :: Maybe String
, ChromeClientHints -> Maybe String
_chromeClientHintsModel :: Maybe String
, ChromeClientHints -> Maybe String
_chromeClientHintsArchitecture :: Maybe String
, ChromeClientHints -> Maybe String
_chromeClientHintsBitness :: Maybe String
, ChromeClientHints -> Maybe Bool
_chromeClientHintsWow64 :: Maybe Bool
} deriving (Int -> ChromeClientHints -> ShowS
[ChromeClientHints] -> ShowS
ChromeClientHints -> String
(Int -> ChromeClientHints -> ShowS)
-> (ChromeClientHints -> String)
-> ([ChromeClientHints] -> ShowS)
-> Show ChromeClientHints
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChromeClientHints -> ShowS
showsPrec :: Int -> ChromeClientHints -> ShowS
$cshow :: ChromeClientHints -> String
show :: ChromeClientHints -> String
$cshowList :: [ChromeClientHints] -> ShowS
showList :: [ChromeClientHints] -> ShowS
Show, ChromeClientHints -> ChromeClientHints -> Bool
(ChromeClientHints -> ChromeClientHints -> Bool)
-> (ChromeClientHints -> ChromeClientHints -> Bool)
-> Eq ChromeClientHints
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChromeClientHints -> ChromeClientHints -> Bool
== :: ChromeClientHints -> ChromeClientHints -> Bool
$c/= :: ChromeClientHints -> ChromeClientHints -> Bool
/= :: ChromeClientHints -> ChromeClientHints -> Bool
Eq)
deriveJSON toCamel3 ''ChromeClientHints
makeLenses ''ChromeClientHints
mkChromeClientHints :: String -> Bool -> ChromeClientHints
mkChromeClientHints :: String -> Bool -> ChromeClientHints
mkChromeClientHints String
platform Bool
mobile = ChromeClientHints {
_chromeClientHintsPlatform :: String
_chromeClientHintsPlatform = String
platform
, _chromeClientHintsMobile :: Bool
_chromeClientHintsMobile = Bool
mobile
, _chromeClientHintsBrands :: Maybe [BrandAndVersion]
_chromeClientHintsBrands = Maybe [BrandAndVersion]
forall a. Maybe a
Nothing
, _chromeClientHintsFullVersionList :: Maybe [BrandAndVersion]
_chromeClientHintsFullVersionList = Maybe [BrandAndVersion]
forall a. Maybe a
Nothing
, _chromeClientHintsPlatformVersion :: Maybe String
_chromeClientHintsPlatformVersion = Maybe String
forall a. Maybe a
Nothing
, _chromeClientHintsModel :: Maybe String
_chromeClientHintsModel = Maybe String
forall a. Maybe a
Nothing
, _chromeClientHintsArchitecture :: Maybe String
_chromeClientHintsArchitecture = Maybe String
forall a. Maybe a
Nothing
, _chromeClientHintsBitness :: Maybe String
_chromeClientHintsBitness = Maybe String
forall a. Maybe a
Nothing
, _chromeClientHintsWow64 :: Maybe Bool
_chromeClientHintsWow64 = Maybe Bool
forall a. Maybe a
Nothing
}
data ChromeMobileEmulation =
ChromeMobileEmulationSpecificDevice {
ChromeMobileEmulation -> String
_chromeMobileEmulationDeviceName :: String
}
| ChromeMobileEmulationIndividualAttributes {
ChromeMobileEmulation -> Maybe ChromeDeviceMetrics
_chromeMobileEmulationDeviceMetrics :: Maybe ChromeDeviceMetrics
, ChromeMobileEmulation -> Maybe ChromeClientHints
_chromeMobileEmulationClientHints :: Maybe ChromeClientHints
, ChromeMobileEmulation -> Maybe String
_chromeMobileEmulationUserAgent :: Maybe String
}
deriving (Int -> ChromeMobileEmulation -> ShowS
[ChromeMobileEmulation] -> ShowS
ChromeMobileEmulation -> String
(Int -> ChromeMobileEmulation -> ShowS)
-> (ChromeMobileEmulation -> String)
-> ([ChromeMobileEmulation] -> ShowS)
-> Show ChromeMobileEmulation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChromeMobileEmulation -> ShowS
showsPrec :: Int -> ChromeMobileEmulation -> ShowS
$cshow :: ChromeMobileEmulation -> String
show :: ChromeMobileEmulation -> String
$cshowList :: [ChromeMobileEmulation] -> ShowS
showList :: [ChromeMobileEmulation] -> ShowS
Show, ChromeMobileEmulation -> ChromeMobileEmulation -> Bool
(ChromeMobileEmulation -> ChromeMobileEmulation -> Bool)
-> (ChromeMobileEmulation -> ChromeMobileEmulation -> Bool)
-> Eq ChromeMobileEmulation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChromeMobileEmulation -> ChromeMobileEmulation -> Bool
== :: ChromeMobileEmulation -> ChromeMobileEmulation -> Bool
$c/= :: ChromeMobileEmulation -> ChromeMobileEmulation -> Bool
/= :: ChromeMobileEmulation -> ChromeMobileEmulation -> Bool
Eq)
deriveJSON (toCamel3 { sumEncoding = UntaggedValue }) ''ChromeMobileEmulation
makeLenses ''ChromeMobileEmulation
newtype ChromeExtension = ChromeExtension TL.Text
deriving (ChromeExtension -> ChromeExtension -> Bool
(ChromeExtension -> ChromeExtension -> Bool)
-> (ChromeExtension -> ChromeExtension -> Bool)
-> Eq ChromeExtension
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChromeExtension -> ChromeExtension -> Bool
== :: ChromeExtension -> ChromeExtension -> Bool
$c/= :: ChromeExtension -> ChromeExtension -> Bool
/= :: ChromeExtension -> ChromeExtension -> Bool
Eq, Int -> ChromeExtension -> ShowS
[ChromeExtension] -> ShowS
ChromeExtension -> String
(Int -> ChromeExtension -> ShowS)
-> (ChromeExtension -> String)
-> ([ChromeExtension] -> ShowS)
-> Show ChromeExtension
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChromeExtension -> ShowS
showsPrec :: Int -> ChromeExtension -> ShowS
$cshow :: ChromeExtension -> String
show :: ChromeExtension -> String
$cshowList :: [ChromeExtension] -> ShowS
showList :: [ChromeExtension] -> ShowS
Show, ReadPrec [ChromeExtension]
ReadPrec ChromeExtension
Int -> ReadS ChromeExtension
ReadS [ChromeExtension]
(Int -> ReadS ChromeExtension)
-> ReadS [ChromeExtension]
-> ReadPrec ChromeExtension
-> ReadPrec [ChromeExtension]
-> Read ChromeExtension
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ChromeExtension
readsPrec :: Int -> ReadS ChromeExtension
$creadList :: ReadS [ChromeExtension]
readList :: ReadS [ChromeExtension]
$creadPrec :: ReadPrec ChromeExtension
readPrec :: ReadPrec ChromeExtension
$creadListPrec :: ReadPrec [ChromeExtension]
readListPrec :: ReadPrec [ChromeExtension]
Read, [ChromeExtension] -> Value
[ChromeExtension] -> Encoding
ChromeExtension -> Bool
ChromeExtension -> Value
ChromeExtension -> Encoding
(ChromeExtension -> Value)
-> (ChromeExtension -> Encoding)
-> ([ChromeExtension] -> Value)
-> ([ChromeExtension] -> Encoding)
-> (ChromeExtension -> Bool)
-> ToJSON ChromeExtension
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ChromeExtension -> Value
toJSON :: ChromeExtension -> Value
$ctoEncoding :: ChromeExtension -> Encoding
toEncoding :: ChromeExtension -> Encoding
$ctoJSONList :: [ChromeExtension] -> Value
toJSONList :: [ChromeExtension] -> Value
$ctoEncodingList :: [ChromeExtension] -> Encoding
toEncodingList :: [ChromeExtension] -> Encoding
$comitField :: ChromeExtension -> Bool
omitField :: ChromeExtension -> Bool
ToJSON, Maybe ChromeExtension
Value -> Parser [ChromeExtension]
Value -> Parser ChromeExtension
(Value -> Parser ChromeExtension)
-> (Value -> Parser [ChromeExtension])
-> Maybe ChromeExtension
-> FromJSON ChromeExtension
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ChromeExtension
parseJSON :: Value -> Parser ChromeExtension
$cparseJSONList :: Value -> Parser [ChromeExtension]
parseJSONList :: Value -> Parser [ChromeExtension]
$comittedField :: Maybe ChromeExtension
omittedField :: Maybe ChromeExtension
FromJSON)
loadExtension :: MonadIO m => FilePath -> m ChromeExtension
loadExtension :: forall (m :: * -> *). MonadIO m => String -> m ChromeExtension
loadExtension String
path = IO ChromeExtension -> m ChromeExtension
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ChromeExtension -> m ChromeExtension)
-> IO ChromeExtension -> m ChromeExtension
forall a b. (a -> b) -> a -> b
$ ByteString -> ChromeExtension
loadRawExtension (ByteString -> ChromeExtension)
-> IO ByteString -> IO ChromeExtension
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO ByteString
LBS.readFile String
path
loadRawExtension :: ByteString -> ChromeExtension
loadRawExtension :: ByteString -> ChromeExtension
loadRawExtension = Text -> ChromeExtension
ChromeExtension (Text -> ChromeExtension)
-> (ByteString -> Text) -> ByteString -> ChromeExtension
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
decodeLatin1 (ByteString -> Text)
-> (ByteString -> ByteString) -> ByteString -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
B64.encode
data ChromeOptions = ChromeOptions {
ChromeOptions -> Maybe [String]
_chromeOptionsArgs :: Maybe [String]
, ChromeOptions -> Maybe String
_chromeOptionsBinary :: Maybe FilePath
, ChromeOptions -> Maybe [ChromeExtension]
_chromeOptionsExtensions :: Maybe [ChromeExtension]
, ChromeOptions -> Maybe Object
_chromeOptionsLocalState :: Maybe A.Object
, ChromeOptions -> Maybe Object
_chromeOptionsPrefs :: Maybe A.Object
, ChromeOptions -> Maybe Bool
_chromeOptionsDetach :: Maybe Bool
, ChromeOptions -> Maybe String
_chromeOptionsDebuggerAddress :: Maybe String
, ChromeOptions -> Maybe [String]
_chromeOptionsExcludeSwitches :: Maybe [String]
, ChromeOptions -> Maybe String
_chromeOptionsMinidumpPath :: Maybe FilePath
, ChromeOptions -> Maybe ChromeMobileEmulation
_chromeOptionsMobileEmulation :: Maybe ChromeMobileEmulation
, ChromeOptions -> Maybe Object
_chromeOptionsPerfLoggingPrefs :: Maybe A.Object
, ChromeOptions -> Maybe [String]
_chromeOptionsWindowTypes :: Maybe [String]
}
deriving (Int -> ChromeOptions -> ShowS
[ChromeOptions] -> ShowS
ChromeOptions -> String
(Int -> ChromeOptions -> ShowS)
-> (ChromeOptions -> String)
-> ([ChromeOptions] -> ShowS)
-> Show ChromeOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChromeOptions -> ShowS
showsPrec :: Int -> ChromeOptions -> ShowS
$cshow :: ChromeOptions -> String
show :: ChromeOptions -> String
$cshowList :: [ChromeOptions] -> ShowS
showList :: [ChromeOptions] -> ShowS
Show, ChromeOptions -> ChromeOptions -> Bool
(ChromeOptions -> ChromeOptions -> Bool)
-> (ChromeOptions -> ChromeOptions -> Bool) -> Eq ChromeOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChromeOptions -> ChromeOptions -> Bool
== :: ChromeOptions -> ChromeOptions -> Bool
$c/= :: ChromeOptions -> ChromeOptions -> Bool
/= :: ChromeOptions -> ChromeOptions -> Bool
Eq)
deriveJSON toCamel2 ''ChromeOptions
makeLenses ''ChromeOptions
defaultChromeOptions :: ChromeOptions
defaultChromeOptions :: ChromeOptions
defaultChromeOptions = ChromeOptions {
_chromeOptionsArgs :: Maybe [String]
_chromeOptionsArgs = Maybe [String]
forall a. Maybe a
Nothing
, _chromeOptionsBinary :: Maybe String
_chromeOptionsBinary = Maybe String
forall a. Maybe a
Nothing
, _chromeOptionsExtensions :: Maybe [ChromeExtension]
_chromeOptionsExtensions = Maybe [ChromeExtension]
forall a. Maybe a
Nothing
, _chromeOptionsLocalState :: Maybe Object
_chromeOptionsLocalState = Maybe Object
forall a. Maybe a
Nothing
, _chromeOptionsPrefs :: Maybe Object
_chromeOptionsPrefs = Maybe Object
forall a. Maybe a
Nothing
, _chromeOptionsDetach :: Maybe Bool
_chromeOptionsDetach = Maybe Bool
forall a. Maybe a
Nothing
, _chromeOptionsDebuggerAddress :: Maybe String
_chromeOptionsDebuggerAddress = Maybe String
forall a. Maybe a
Nothing
, _chromeOptionsExcludeSwitches :: Maybe [String]
_chromeOptionsExcludeSwitches = Maybe [String]
forall a. Maybe a
Nothing
, _chromeOptionsMinidumpPath :: Maybe String
_chromeOptionsMinidumpPath = Maybe String
forall a. Maybe a
Nothing
, _chromeOptionsMobileEmulation :: Maybe ChromeMobileEmulation
_chromeOptionsMobileEmulation = Maybe ChromeMobileEmulation
forall a. Maybe a
Nothing
, _chromeOptionsPerfLoggingPrefs :: Maybe Object
_chromeOptionsPerfLoggingPrefs = Maybe Object
forall a. Maybe a
Nothing
, _chromeOptionsWindowTypes :: Maybe [String]
_chromeOptionsWindowTypes = Maybe [String]
forall a. Maybe a
Nothing
}