{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards   #-}
{-# LANGUAGE StrictData        #-}
module GitHub.Types.Events.DeploymentEvent where

import           Data.Aeson                (FromJSON (..), ToJSON (..), object)
import           Data.Aeson.Types          (Value (..), (.:), (.:?), (.=))
import           Data.Text                 (Text)
import           Test.QuickCheck.Arbitrary (Arbitrary (..))

import           GitHub.Types.Base
import           GitHub.Types.Event


data DeploymentEvent = DeploymentEvent
    { DeploymentEvent -> Maybe Installation
deploymentEventInstallation :: Maybe Installation
    , DeploymentEvent -> Organization
deploymentEventOrganization :: Organization
    , DeploymentEvent -> Repository
deploymentEventRepository   :: Repository
    , DeploymentEvent -> User
deploymentEventSender       :: User

    , DeploymentEvent -> Text
deploymentEventAction       :: Text
    , DeploymentEvent -> Deployment
deploymentEventDeployment   :: Deployment
    } deriving (DeploymentEvent -> DeploymentEvent -> Bool
(DeploymentEvent -> DeploymentEvent -> Bool)
-> (DeploymentEvent -> DeploymentEvent -> Bool)
-> Eq DeploymentEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeploymentEvent -> DeploymentEvent -> Bool
$c/= :: DeploymentEvent -> DeploymentEvent -> Bool
== :: DeploymentEvent -> DeploymentEvent -> Bool
$c== :: DeploymentEvent -> DeploymentEvent -> Bool
Eq, Int -> DeploymentEvent -> ShowS
[DeploymentEvent] -> ShowS
DeploymentEvent -> String
(Int -> DeploymentEvent -> ShowS)
-> (DeploymentEvent -> String)
-> ([DeploymentEvent] -> ShowS)
-> Show DeploymentEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeploymentEvent] -> ShowS
$cshowList :: [DeploymentEvent] -> ShowS
show :: DeploymentEvent -> String
$cshow :: DeploymentEvent -> String
showsPrec :: Int -> DeploymentEvent -> ShowS
$cshowsPrec :: Int -> DeploymentEvent -> ShowS
Show, ReadPrec [DeploymentEvent]
ReadPrec DeploymentEvent
Int -> ReadS DeploymentEvent
ReadS [DeploymentEvent]
(Int -> ReadS DeploymentEvent)
-> ReadS [DeploymentEvent]
-> ReadPrec DeploymentEvent
-> ReadPrec [DeploymentEvent]
-> Read DeploymentEvent
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeploymentEvent]
$creadListPrec :: ReadPrec [DeploymentEvent]
readPrec :: ReadPrec DeploymentEvent
$creadPrec :: ReadPrec DeploymentEvent
readList :: ReadS [DeploymentEvent]
$creadList :: ReadS [DeploymentEvent]
readsPrec :: Int -> ReadS DeploymentEvent
$creadsPrec :: Int -> ReadS DeploymentEvent
Read)

instance Event DeploymentEvent where
    typeName :: TypeName DeploymentEvent
typeName = Text -> TypeName DeploymentEvent
forall a. Text -> TypeName a
TypeName Text
"DeploymentEvent"
    eventName :: EventName DeploymentEvent
eventName = Text -> EventName DeploymentEvent
forall a. Text -> EventName a
EventName Text
"deployment"

instance FromJSON DeploymentEvent where
    parseJSON :: Value -> Parser DeploymentEvent
parseJSON (Object Object
x) = Maybe Installation
-> Organization
-> Repository
-> User
-> Text
-> Deployment
-> DeploymentEvent
DeploymentEvent
        (Maybe Installation
 -> Organization
 -> Repository
 -> User
 -> Text
 -> Deployment
 -> DeploymentEvent)
-> Parser (Maybe Installation)
-> Parser
     (Organization
      -> Repository -> User -> Text -> Deployment -> DeploymentEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
x Object -> Key -> Parser (Maybe Installation)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"installation"
        Parser
  (Organization
   -> Repository -> User -> Text -> Deployment -> DeploymentEvent)
-> Parser Organization
-> Parser
     (Repository -> User -> Text -> Deployment -> DeploymentEvent)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Organization
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"organization"
        Parser
  (Repository -> User -> Text -> Deployment -> DeploymentEvent)
-> Parser Repository
-> Parser (User -> Text -> Deployment -> DeploymentEvent)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Repository
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"repository"
        Parser (User -> Text -> Deployment -> DeploymentEvent)
-> Parser User -> Parser (Text -> Deployment -> DeploymentEvent)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser User
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"sender"

        Parser (Text -> Deployment -> DeploymentEvent)
-> Parser Text -> Parser (Deployment -> DeploymentEvent)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"action"
        Parser (Deployment -> DeploymentEvent)
-> Parser Deployment -> Parser DeploymentEvent
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Deployment
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"deployment"

    parseJSON Value
_ = String -> Parser DeploymentEvent
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"DeploymentEvent"

instance ToJSON DeploymentEvent where
    toJSON :: DeploymentEvent -> Value
toJSON DeploymentEvent{Maybe Installation
Text
Organization
User
Deployment
Repository
deploymentEventDeployment :: Deployment
deploymentEventAction :: Text
deploymentEventSender :: User
deploymentEventRepository :: Repository
deploymentEventOrganization :: Organization
deploymentEventInstallation :: Maybe Installation
deploymentEventDeployment :: DeploymentEvent -> Deployment
deploymentEventAction :: DeploymentEvent -> Text
deploymentEventSender :: DeploymentEvent -> User
deploymentEventRepository :: DeploymentEvent -> Repository
deploymentEventOrganization :: DeploymentEvent -> Organization
deploymentEventInstallation :: DeploymentEvent -> Maybe Installation
..} = [Pair] -> Value
object
        [ Key
"installation" Key -> Maybe Installation -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Installation
deploymentEventInstallation
        , Key
"organization" Key -> Organization -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Organization
deploymentEventOrganization
        , Key
"repository"   Key -> Repository -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Repository
deploymentEventRepository
        , Key
"sender"       Key -> User -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= User
deploymentEventSender

        , Key
"action"       Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
deploymentEventAction
        , Key
"deployment"   Key -> Deployment -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Deployment
deploymentEventDeployment
        ]


instance Arbitrary DeploymentEvent where
    arbitrary :: Gen DeploymentEvent
arbitrary = Maybe Installation
-> Organization
-> Repository
-> User
-> Text
-> Deployment
-> DeploymentEvent
DeploymentEvent
        (Maybe Installation
 -> Organization
 -> Repository
 -> User
 -> Text
 -> Deployment
 -> DeploymentEvent)
-> Gen (Maybe Installation)
-> Gen
     (Organization
      -> Repository -> User -> Text -> Deployment -> DeploymentEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Maybe Installation)
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Organization
   -> Repository -> User -> Text -> Deployment -> DeploymentEvent)
-> Gen Organization
-> Gen
     (Repository -> User -> Text -> Deployment -> DeploymentEvent)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Organization
forall a. Arbitrary a => Gen a
arbitrary
        Gen (Repository -> User -> Text -> Deployment -> DeploymentEvent)
-> Gen Repository
-> Gen (User -> Text -> Deployment -> DeploymentEvent)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Repository
forall a. Arbitrary a => Gen a
arbitrary
        Gen (User -> Text -> Deployment -> DeploymentEvent)
-> Gen User -> Gen (Text -> Deployment -> DeploymentEvent)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen User
forall a. Arbitrary a => Gen a
arbitrary

        Gen (Text -> Deployment -> DeploymentEvent)
-> Gen Text -> Gen (Deployment -> DeploymentEvent)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
        Gen (Deployment -> DeploymentEvent)
-> Gen Deployment -> Gen DeploymentEvent
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Deployment
forall a. Arbitrary a => Gen a
arbitrary