{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards   #-}
{-# LANGUAGE StrictData        #-}
module GitHub.Types.Events.GollumEvent 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 GollumEvent = GollumEvent
    { GollumEvent -> Maybe Installation
gollumEventInstallation :: Maybe Installation
    , GollumEvent -> Organization
gollumEventOrganization :: Organization
    , GollumEvent -> Repository
gollumEventRepository   :: Repository
    , GollumEvent -> User
gollumEventSender       :: User

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

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

instance FromJSON GollumEvent where
    parseJSON :: Value -> Parser GollumEvent
parseJSON (Object Object
x) = Maybe Installation
-> Organization -> Repository -> User -> Text -> GollumEvent
GollumEvent
        (Maybe Installation
 -> Organization -> Repository -> User -> Text -> GollumEvent)
-> Parser (Maybe Installation)
-> Parser
     (Organization -> Repository -> User -> Text -> GollumEvent)
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 -> GollumEvent)
-> Parser Organization
-> Parser (Repository -> User -> Text -> GollumEvent)
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 -> GollumEvent)
-> Parser Repository -> Parser (User -> Text -> GollumEvent)
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 -> GollumEvent)
-> Parser User -> Parser (Text -> GollumEvent)
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 -> GollumEvent) -> Parser Text -> Parser GollumEvent
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
"pages"

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

instance ToJSON GollumEvent where
    toJSON :: GollumEvent -> Value
toJSON GollumEvent{Maybe Installation
Text
Organization
User
Repository
gollumEventPages :: Text
gollumEventSender :: User
gollumEventRepository :: Repository
gollumEventOrganization :: Organization
gollumEventInstallation :: Maybe Installation
gollumEventPages :: GollumEvent -> Text
gollumEventSender :: GollumEvent -> User
gollumEventRepository :: GollumEvent -> Repository
gollumEventOrganization :: GollumEvent -> Organization
gollumEventInstallation :: GollumEvent -> Maybe Installation
..} = [Pair] -> Value
object
        [ Key
"installation" Key -> Maybe Installation -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Installation
gollumEventInstallation
        , Key
"organization" Key -> Organization -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Organization
gollumEventOrganization
        , Key
"repository"   Key -> Repository -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Repository
gollumEventRepository
        , Key
"sender"       Key -> User -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= User
gollumEventSender

        , Key
"pages"      Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
gollumEventPages
        ]


instance Arbitrary GollumEvent where
    arbitrary :: Gen GollumEvent
arbitrary = Maybe Installation
-> Organization -> Repository -> User -> Text -> GollumEvent
GollumEvent
        (Maybe Installation
 -> Organization -> Repository -> User -> Text -> GollumEvent)
-> Gen (Maybe Installation)
-> Gen (Organization -> Repository -> User -> Text -> GollumEvent)
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 -> GollumEvent)
-> Gen Organization
-> Gen (Repository -> User -> Text -> GollumEvent)
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 -> GollumEvent)
-> Gen Repository -> Gen (User -> Text -> GollumEvent)
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 -> GollumEvent)
-> Gen User -> Gen (Text -> GollumEvent)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen User
forall a. Arbitrary a => Gen a
arbitrary

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