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