{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
module GitHub.Types.Base.Label 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 Label = Label
{ Label -> Text
labelColor :: Text
, Label -> Bool
labelDefault :: Bool
, Label -> Text
labelDescription :: Text
, Label -> Text
labelUrl :: Text
, Label -> Text
labelName :: Text
, Label -> Int
labelId :: Int
, Label -> Text
labelNodeId :: Text
} deriving (Label -> Label -> Bool
(Label -> Label -> Bool) -> (Label -> Label -> Bool) -> Eq Label
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Label -> Label -> Bool
$c/= :: Label -> Label -> Bool
== :: Label -> Label -> Bool
$c== :: Label -> Label -> Bool
Eq, Int -> Label -> ShowS
[Label] -> ShowS
Label -> String
(Int -> Label -> ShowS)
-> (Label -> String) -> ([Label] -> ShowS) -> Show Label
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Label] -> ShowS
$cshowList :: [Label] -> ShowS
show :: Label -> String
$cshow :: Label -> String
showsPrec :: Int -> Label -> ShowS
$cshowsPrec :: Int -> Label -> ShowS
Show, ReadPrec [Label]
ReadPrec Label
Int -> ReadS Label
ReadS [Label]
(Int -> ReadS Label)
-> ReadS [Label]
-> ReadPrec Label
-> ReadPrec [Label]
-> Read Label
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Label]
$creadListPrec :: ReadPrec [Label]
readPrec :: ReadPrec Label
$creadPrec :: ReadPrec Label
readList :: ReadS [Label]
$creadList :: ReadS [Label]
readsPrec :: Int -> ReadS Label
$creadsPrec :: Int -> ReadS Label
Read)
instance FromJSON Label where
parseJSON :: Value -> Parser Label
parseJSON (Object Object
x) = Text -> Bool -> Text -> Text -> Text -> Int -> Text -> Label
Label
(Text -> Bool -> Text -> Text -> Text -> Int -> Text -> Label)
-> Parser Text
-> Parser (Bool -> Text -> Text -> Text -> Int -> Text -> Label)
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
"color"
Parser (Bool -> Text -> Text -> Text -> Int -> Text -> Label)
-> Parser Bool
-> Parser (Text -> Text -> Text -> Int -> Text -> Label)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"default"
Parser (Text -> Text -> Text -> Int -> Text -> Label)
-> Parser Text -> Parser (Text -> Text -> Int -> Text -> Label)
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
"description"
Parser (Text -> Text -> Int -> Text -> Label)
-> Parser Text -> Parser (Text -> Int -> Text -> Label)
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"
Parser (Text -> Int -> Text -> Label)
-> Parser Text -> Parser (Int -> Text -> Label)
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 (Int -> Text -> Label)
-> Parser Int -> Parser (Text -> Label)
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 -> Label) -> Parser Text -> Parser Label
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"
parseJSON Value
_ = String -> Parser Label
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Label"
instance ToJSON Label where
toJSON :: Label -> Value
toJSON Label{Bool
Int
Text
labelNodeId :: Text
labelId :: Int
labelName :: Text
labelUrl :: Text
labelDescription :: Text
labelDefault :: Bool
labelColor :: Text
labelNodeId :: Label -> Text
labelId :: Label -> Int
labelName :: Label -> Text
labelUrl :: Label -> Text
labelDescription :: Label -> Text
labelDefault :: Label -> Bool
labelColor :: Label -> Text
..} = [Pair] -> Value
object
[ Key
"color" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
labelColor
, Key
"default" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
labelDefault
, Key
"description" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
labelDescription
, Key
"url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
labelUrl
, Key
"name" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
labelName
, Key
"id" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
labelId
, Key
"node_id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
labelNodeId
]
instance Arbitrary Label where
arbitrary :: Gen Label
arbitrary = Text -> Bool -> Text -> Text -> Text -> Int -> Text -> Label
Label
(Text -> Bool -> Text -> Text -> Text -> Int -> Text -> Label)
-> Gen Text
-> Gen (Bool -> Text -> Text -> Text -> Int -> Text -> Label)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Bool -> Text -> Text -> Text -> Int -> Text -> Label)
-> Gen Bool -> Gen (Text -> Text -> Text -> Int -> Text -> Label)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Bool
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> Text -> Text -> Int -> Text -> Label)
-> Gen Text -> Gen (Text -> Text -> Int -> Text -> Label)
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 -> Int -> Text -> Label)
-> Gen Text -> Gen (Text -> Int -> Text -> Label)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> Int -> Text -> Label)
-> Gen Text -> Gen (Int -> Text -> Label)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Int -> Text -> Label) -> Gen Int -> Gen (Text -> Label)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> Label) -> Gen Text -> Gen Label
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary