{-# LANGUAGE OverloadedStrings #-}
module Test.WebDriver.Commands.Logs.Selenium (
getSeleniumLogs
, getSeleniumLogTypes
) where
import Data.Aeson
import GHC.Stack
import Test.WebDriver.Commands.Logs.Common
import Test.WebDriver.Types
import Test.WebDriver.Util.Commands
getSeleniumLogs :: (HasCallStack, WebDriver wd) => LogType -> wd [LogEntry]
getSeleniumLogs :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
LogType -> wd [LogEntry]
getSeleniumLogs LogType
logType = Method -> Text -> Value -> wd [LogEntry]
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/log" (Value -> wd [LogEntry]) -> Value -> wd [LogEntry]
forall a b. (a -> b) -> a -> b
$ [Pair] -> Value
object [Key
"type" Key -> LogType -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= LogType
logType]
getSeleniumLogTypes :: (HasCallStack, WebDriver wd) => wd [LogType]
getSeleniumLogTypes :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd [LogType]
getSeleniumLogTypes = Method -> Text -> Value -> wd [LogType]
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/log/types" Value
Null