{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
module GitHub.Types.Base.Team where
import Data.Aeson (FromJSON (..), ToJSON (..), object)
import Data.Aeson.Types (Value (..), (.:), (.:?), (.=))
import Data.Text (Text)
import Data.Text.Arbitrary ()
import Test.QuickCheck.Arbitrary (Arbitrary (..))
data Team = Team
{ Team -> Text
teamDescription :: Text
, Team -> Int
teamId :: Int
, Team -> Text
teamHtmlUrl :: Text
, Team -> Text
teamMembersUrl :: Text
, Team -> Text
teamName :: Text
, Team -> Text
teamNodeId :: Text
, Team -> Maybe Team
teamParent :: Maybe Team
, Team -> Text
teamPermission :: Text
, Team -> Text
teamPrivacy :: Text
, Team -> Text
teamRepositoriesUrl :: Text
, Team -> Text
teamSlug :: Text
, Team -> Text
teamUrl :: Text
} deriving (Team -> Team -> Bool
(Team -> Team -> Bool) -> (Team -> Team -> Bool) -> Eq Team
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Team -> Team -> Bool
$c/= :: Team -> Team -> Bool
== :: Team -> Team -> Bool
$c== :: Team -> Team -> Bool
Eq, Int -> Team -> ShowS
[Team] -> ShowS
Team -> String
(Int -> Team -> ShowS)
-> (Team -> String) -> ([Team] -> ShowS) -> Show Team
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Team] -> ShowS
$cshowList :: [Team] -> ShowS
show :: Team -> String
$cshow :: Team -> String
showsPrec :: Int -> Team -> ShowS
$cshowsPrec :: Int -> Team -> ShowS
Show, ReadPrec [Team]
ReadPrec Team
Int -> ReadS Team
ReadS [Team]
(Int -> ReadS Team)
-> ReadS [Team] -> ReadPrec Team -> ReadPrec [Team] -> Read Team
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Team]
$creadListPrec :: ReadPrec [Team]
readPrec :: ReadPrec Team
$creadPrec :: ReadPrec Team
readList :: ReadS [Team]
$creadList :: ReadS [Team]
readsPrec :: Int -> ReadS Team
$creadsPrec :: Int -> ReadS Team
Read)
instance FromJSON Team where
parseJSON :: Value -> Parser Team
parseJSON (Object Object
x) = Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Maybe Team
-> Text
-> Text
-> Text
-> Text
-> Text
-> Team
Team
(Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Maybe Team
-> Text
-> Text
-> Text
-> Text
-> Text
-> Team)
-> Parser Text
-> Parser
(Int
-> Text
-> Text
-> Text
-> Text
-> Maybe Team
-> Text
-> Text
-> Text
-> Text
-> Text
-> Team)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"description"
Parser
(Int
-> Text
-> Text
-> Text
-> Text
-> Maybe Team
-> Text
-> Text
-> Text
-> Text
-> Text
-> Team)
-> Parser Int
-> Parser
(Text
-> Text
-> Text
-> Text
-> Maybe Team
-> Text
-> Text
-> Text
-> Text
-> Text
-> Team)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
Parser
(Text
-> Text
-> Text
-> Text
-> Maybe Team
-> Text
-> Text
-> Text
-> Text
-> Text
-> Team)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Maybe Team
-> Text
-> Text
-> Text
-> Text
-> Text
-> Team)
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
"html_url"
Parser
(Text
-> Text
-> Text
-> Maybe Team
-> Text
-> Text
-> Text
-> Text
-> Text
-> Team)
-> Parser Text
-> Parser
(Text
-> Text
-> Maybe Team
-> Text
-> Text
-> Text
-> Text
-> Text
-> Team)
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
"members_url"
Parser
(Text
-> Text
-> Maybe Team
-> Text
-> Text
-> Text
-> Text
-> Text
-> Team)
-> Parser Text
-> Parser
(Text
-> Maybe Team -> Text -> Text -> Text -> Text -> Text -> Team)
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
"name"
Parser
(Text
-> Maybe Team -> Text -> Text -> Text -> Text -> Text -> Team)
-> Parser Text
-> Parser
(Maybe Team -> Text -> Text -> Text -> Text -> Text -> Team)
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
"node_id"
Parser (Maybe Team -> Text -> Text -> Text -> Text -> Text -> Team)
-> Parser (Maybe Team)
-> Parser (Text -> Text -> Text -> Text -> Text -> Team)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe Team)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"parent"
Parser (Text -> Text -> Text -> Text -> Text -> Team)
-> Parser Text -> Parser (Text -> Text -> Text -> Text -> Team)
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
"permission"
Parser (Text -> Text -> Text -> Text -> Team)
-> Parser Text -> Parser (Text -> Text -> Text -> Team)
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
"privacy"
Parser (Text -> Text -> Text -> Team)
-> Parser Text -> Parser (Text -> Text -> Team)
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
"repositories_url"
Parser (Text -> Text -> Team)
-> Parser Text -> Parser (Text -> Team)
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
"slug"
Parser (Text -> Team) -> Parser Text -> Parser Team
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
"url"
parseJSON Value
_ = String -> Parser Team
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Team"
instance ToJSON Team where
toJSON :: Team -> Value
toJSON Team{Int
Maybe Team
Text
teamUrl :: Text
teamSlug :: Text
teamRepositoriesUrl :: Text
teamPrivacy :: Text
teamPermission :: Text
teamParent :: Maybe Team
teamNodeId :: Text
teamName :: Text
teamMembersUrl :: Text
teamHtmlUrl :: Text
teamId :: Int
teamDescription :: Text
teamUrl :: Team -> Text
teamSlug :: Team -> Text
teamRepositoriesUrl :: Team -> Text
teamPrivacy :: Team -> Text
teamPermission :: Team -> Text
teamParent :: Team -> Maybe Team
teamNodeId :: Team -> Text
teamName :: Team -> Text
teamMembersUrl :: Team -> Text
teamHtmlUrl :: Team -> Text
teamId :: Team -> Int
teamDescription :: Team -> Text
..} = [Pair] -> Value
object
[ Key
"description" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
teamDescription
, Key
"id" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
teamId
, Key
"html_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
teamHtmlUrl
, Key
"members_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
teamMembersUrl
, Key
"name" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
teamName
, Key
"node_id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
teamNodeId
, Key
"parent" Key -> Maybe Team -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Team
teamParent
, Key
"permission" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
teamPermission
, Key
"privacy" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
teamPrivacy
, Key
"repositories_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
teamRepositoriesUrl
, Key
"slug" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
teamSlug
, Key
"url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
teamUrl
]
instance Arbitrary Team where
arbitrary :: Gen Team
arbitrary = Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Maybe Team
-> Text
-> Text
-> Text
-> Text
-> Text
-> Team
Team
(Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Maybe Team
-> Text
-> Text
-> Text
-> Text
-> Text
-> Team)
-> Gen Text
-> Gen
(Int
-> Text
-> Text
-> Text
-> Text
-> Maybe Team
-> Text
-> Text
-> Text
-> Text
-> Text
-> Team)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Int
-> Text
-> Text
-> Text
-> Text
-> Maybe Team
-> Text
-> Text
-> Text
-> Text
-> Text
-> Team)
-> Gen Int
-> Gen
(Text
-> Text
-> Text
-> Text
-> Maybe Team
-> Text
-> Text
-> Text
-> Text
-> Text
-> Team)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Text
-> Text
-> Text
-> Maybe Team
-> Text
-> Text
-> Text
-> Text
-> Text
-> Team)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Maybe Team
-> Text
-> Text
-> Text
-> Text
-> Text
-> Team)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Text
-> Text
-> Maybe Team
-> Text
-> Text
-> Text
-> Text
-> Text
-> Team)
-> Gen Text
-> Gen
(Text
-> Text
-> Maybe Team
-> Text
-> Text
-> Text
-> Text
-> Text
-> Team)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Text
-> Maybe Team
-> Text
-> Text
-> Text
-> Text
-> Text
-> Team)
-> Gen Text
-> Gen
(Text
-> Maybe Team -> Text -> Text -> Text -> Text -> Text -> Team)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Maybe Team -> Text -> Text -> Text -> Text -> Text -> Team)
-> Gen Text
-> Gen (Maybe Team -> Text -> Text -> Text -> Text -> Text -> Team)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Maybe Team -> Text -> Text -> Text -> Text -> Text -> Team)
-> Gen (Maybe Team)
-> Gen (Text -> Text -> Text -> Text -> Text -> Team)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Team)
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> Text -> Text -> Text -> Text -> Team)
-> Gen Text -> Gen (Text -> Text -> Text -> Text -> Team)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> Text -> Text -> Text -> Team)
-> Gen Text -> Gen (Text -> Text -> Text -> Team)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> Text -> Text -> Team)
-> Gen Text -> Gen (Text -> Text -> Team)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> Text -> Team) -> Gen Text -> Gen (Text -> Team)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> Team) -> Gen Text -> Gen Team
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary