{-# LANGUAGE DeriveGeneric #-}

module Test.WebDriver.Commands.Cookies (
  cookies
  , cookie
  , setCookie
  , deleteCookie
  , deleteCookies

  -- * Types
  , mkCookie
  , Cookie(..)
  ) where

import Data.Aeson as A
import Data.Aeson.Types
import qualified Data.Char as C
import Data.Text (Text)
import GHC.Generics
import GHC.Stack
import Test.WebDriver.JSON
import Test.WebDriver.Types
import Test.WebDriver.Util.Commands


-- | Retrieve all cookies.
cookies :: (HasCallStack, WebDriver wd) => wd [Cookie]
cookies :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd [Cookie]
cookies = Method -> Text -> Value -> wd [Cookie]
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet Text
"/cookie" Value
Null

-- | Retrieve a specific cookie by name.
cookie :: (HasCallStack, WebDriver wd) => Text -> wd Cookie
cookie :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Text -> wd Cookie
cookie Text
n = Method -> Text -> Value -> wd Cookie
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodGet (Text
"/cookie/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
n) Value
Null

-- | Set a cookie. If the cookie path is not specified, it will default to \"/\".
-- Likewise, if the domain is omitted, it will default to the current page's domain.
setCookie :: (HasCallStack, WebDriver wd) => Cookie -> wd ()
setCookie :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Cookie -> wd ()
setCookie = wd NoReturn -> wd ()
forall (m :: * -> *). WebDriver m => m NoReturn -> m ()
noReturn (wd NoReturn -> wd ())
-> (Cookie -> wd NoReturn) -> Cookie -> wd ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodPost Text
"/cookie" (Value -> wd NoReturn)
-> (Cookie -> Value) -> Cookie -> wd NoReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Cookie -> Value
forall a. ToJSON a => Text -> a -> Value
single Text
"cookie"

-- | Delete a cookie by name.
deleteCookie :: (HasCallStack, WebDriver wd) => Text -> wd ()
deleteCookie :: forall (wd :: * -> *).
(HasCallStack, WebDriver wd) =>
Text -> wd ()
deleteCookie Text
n = wd NoReturn -> wd ()
forall (m :: * -> *). WebDriver m => m NoReturn -> m ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodDelete (Text
"/cookie/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
urlEncode Text
n) Value
Null

-- | Delete all visible cookies on the current page.
deleteCookies :: (HasCallStack, WebDriver wd) => wd ()
deleteCookies :: forall (wd :: * -> *). (HasCallStack, WebDriver wd) => wd ()
deleteCookies = wd NoReturn -> wd ()
forall (m :: * -> *). WebDriver m => m NoReturn -> m ()
noReturn (wd NoReturn -> wd ()) -> wd NoReturn -> wd ()
forall a b. (a -> b) -> a -> b
$ Method -> Text -> Value -> wd NoReturn
forall (wd :: * -> *) a b.
(HasCallStack, WebDriver wd, ToJSON a, FromJSON b) =>
Method -> Text -> a -> wd b
doSessCommand Method
methodDelete Text
"/cookie" Value
Null

-- * Types

-- | Cookies are delicious delicacies. When sending cookies to the server, a value
-- of Nothing indicates that the server should use a default value. When receiving
-- cookies from the server, a value of Nothing indicates that the server is unable
-- to specify the value.
data Cookie = Cookie {
  Cookie -> Text
cookName   :: Text
  , Cookie -> Text
cookValue  :: Text
  -- | Path of this cookie. If Nothing, defaults to /
  , Cookie -> Maybe Text
cookPath   :: Maybe Text
  -- | Domain of this cookie. If Nothing, the current page's domain is used.
  , Cookie -> Maybe Text
cookDomain :: Maybe Text
  -- | Is this cookie secure?
  , Cookie -> Maybe Bool
cookSecure :: Maybe Bool
  -- | Expiry date expressed as seconds since the Unix epoch.
  -- 'Nothing' indicates that the cookie never expires.
  , Cookie -> Maybe Double
cookExpiry :: Maybe Double
  } deriving (Cookie -> Cookie -> Bool
(Cookie -> Cookie -> Bool)
-> (Cookie -> Cookie -> Bool) -> Eq Cookie
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Cookie -> Cookie -> Bool
== :: Cookie -> Cookie -> Bool
$c/= :: Cookie -> Cookie -> Bool
/= :: Cookie -> Cookie -> Bool
Eq, Int -> Cookie -> ShowS
[Cookie] -> ShowS
Cookie -> String
(Int -> Cookie -> ShowS)
-> (Cookie -> String) -> ([Cookie] -> ShowS) -> Show Cookie
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Cookie -> ShowS
showsPrec :: Int -> Cookie -> ShowS
$cshow :: Cookie -> String
show :: Cookie -> String
$cshowList :: [Cookie] -> ShowS
showList :: [Cookie] -> ShowS
Show, (forall x. Cookie -> Rep Cookie x)
-> (forall x. Rep Cookie x -> Cookie) -> Generic Cookie
forall x. Rep Cookie x -> Cookie
forall x. Cookie -> Rep Cookie x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Cookie -> Rep Cookie x
from :: forall x. Cookie -> Rep Cookie x
$cto :: forall x. Rep Cookie x -> Cookie
to :: forall x. Rep Cookie x -> Cookie
Generic)

aesonOptionsCookie :: Options
aesonOptionsCookie :: Options
aesonOptionsCookie = Options
defaultOptions {
  omitNothingFields = True
  , fieldLabelModifier = map C.toLower . drop 4
  }

-- | Creates a Cookie with only a name and value specified. All other
-- fields are set to Nothing, which tells the server to use default values.
mkCookie :: Text -> Text -> Cookie
mkCookie :: Text -> Text -> Cookie
mkCookie Text
name Text
value = Cookie {
  cookName :: Text
cookName = Text
name
  , cookValue :: Text
cookValue = Text
value
  , cookPath :: Maybe Text
cookPath = Maybe Text
forall a. Maybe a
Nothing
  , cookDomain :: Maybe Text
cookDomain = Maybe Text
forall a. Maybe a
Nothing
  , cookSecure :: Maybe Bool
cookSecure = Maybe Bool
forall a. Maybe a
Nothing
  , cookExpiry :: Maybe Double
cookExpiry = Maybe Double
forall a. Maybe a
Nothing
  }

instance ToJSON Cookie where
  toJSON :: Cookie -> Value
toJSON = Options -> Cookie -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptionsCookie
  toEncoding :: Cookie -> Encoding
toEncoding = Options -> Cookie -> Encoding
forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
genericToEncoding Options
aesonOptionsCookie
instance FromJSON Cookie where
  parseJSON :: Value -> Parser Cookie
parseJSON (Object Object
o) = Text
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe Double
-> Cookie
Cookie (Text
 -> Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Bool
 -> Maybe Double
 -> Cookie)
-> Parser Text
-> Parser
     (Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Double
      -> Cookie)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Parser Text
forall a. FromJSON a => Text -> Parser a
req Text
"name"
                                Parser
  (Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Double
   -> Cookie)
-> Parser Text
-> Parser
     (Maybe Text -> Maybe Text -> Maybe Bool -> Maybe Double -> Cookie)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Parser Text
forall a. FromJSON a => Text -> Parser a
req Text
"value"
                                Parser
  (Maybe Text -> Maybe Text -> Maybe Bool -> Maybe Double -> Cookie)
-> Parser (Maybe Text)
-> Parser (Maybe Text -> Maybe Bool -> Maybe Double -> Cookie)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Maybe Text -> Parser (Maybe Text)
forall a. FromJSON a => Text -> a -> Parser a
opt Text
"path" Maybe Text
forall a. Maybe a
Nothing
                                Parser (Maybe Text -> Maybe Bool -> Maybe Double -> Cookie)
-> Parser (Maybe Text)
-> Parser (Maybe Bool -> Maybe Double -> Cookie)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Maybe Text -> Parser (Maybe Text)
forall a. FromJSON a => Text -> a -> Parser a
opt Text
"domain" Maybe Text
forall a. Maybe a
Nothing
                                Parser (Maybe Bool -> Maybe Double -> Cookie)
-> Parser (Maybe Bool) -> Parser (Maybe Double -> Cookie)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Maybe Bool -> Parser (Maybe Bool)
forall a. FromJSON a => Text -> a -> Parser a
opt Text
"secure" Maybe Bool
forall a. Maybe a
Nothing
                                Parser (Maybe Double -> Cookie)
-> Parser (Maybe Double) -> Parser Cookie
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Maybe Double -> Parser (Maybe Double)
forall a. FromJSON a => Text -> a -> Parser a
opt Text
"expiry" Maybe Double
forall a. Maybe a
Nothing
    where
      req :: FromJSON a => Text -> Parser a
      req :: forall a. FromJSON a => Text -> Parser a
req = (Object
o Object -> Key -> Parser a
forall a. FromJSON a => Object -> Key -> Parser a
.:) (Key -> Parser a) -> (Text -> Key) -> Text -> Parser a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Key
aesonKeyFromText
      opt :: FromJSON a => Text -> a -> Parser a
      opt :: forall a. FromJSON a => Text -> a -> Parser a
opt Text
k a
d = Object
o Object -> Text -> Parser (Maybe a)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:?? Text
k Parser (Maybe a) -> a -> Parser a
forall a. Parser (Maybe a) -> a -> Parser a
.!= a
d
  parseJSON Value
v = String -> Value -> Parser Cookie
forall a. String -> Value -> Parser a
typeMismatch String
"Cookie" Value
v