module GitHub.Data.Releases where

import GitHub.Data.Definitions
import GitHub.Data.Id          (Id)
import GitHub.Data.URL         (URL)
import GitHub.Internal.Prelude
import Prelude ()

data Release = Release
    { Release -> URL
releaseUrl             :: !URL
    , Release -> URL
releaseHtmlUrl         :: !URL
    , Release -> URL
releaseAssetsurl       :: !URL
    , Release -> URL
releaseUploadUrl       :: !URL
    , Release -> URL
releaseTarballUrl      :: !URL
    , Release -> URL
releaseZipballUrl      :: !URL
    , Release -> Id Release
releaseId              :: !(Id Release)
    , Release -> Text
releaseTagName         :: !Text
    , Release -> Text
releaseTargetCommitish :: !Text
    , Release -> Text
releaseName            :: !Text
    , Release -> Text
releaseBody            :: !Text
    , Release -> Bool
releaseDraft           :: !Bool
    , Release -> Bool
releasePrerelease      :: !Bool
    , Release -> UTCTime
releaseCreatedAt       :: !UTCTime
    , Release -> Maybe UTCTime
releasePublishedAt     :: !(Maybe UTCTime)
    , Release -> SimpleUser
releaseAuthor          :: !SimpleUser
    , Release -> Vector ReleaseAsset
releaseAssets          :: !(Vector ReleaseAsset)
    }
    deriving (Int -> Release -> ShowS
[Release] -> ShowS
Release -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Release] -> ShowS
$cshowList :: [Release] -> ShowS
show :: Release -> String
$cshow :: Release -> String
showsPrec :: Int -> Release -> ShowS
$cshowsPrec :: Int -> Release -> ShowS
Show, Typeable Release
Release -> DataType
Release -> Constr
(forall b. Data b => b -> b) -> Release -> Release
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Release -> u
forall u. (forall d. Data d => d -> u) -> Release -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Release -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Release -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Release -> m Release
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Release -> m Release
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Release
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Release -> c Release
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Release)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Release)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Release -> m Release
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Release -> m Release
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Release -> m Release
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Release -> m Release
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Release -> m Release
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Release -> m Release
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Release -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Release -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Release -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Release -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Release -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Release -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Release -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Release -> r
gmapT :: (forall b. Data b => b -> b) -> Release -> Release
$cgmapT :: (forall b. Data b => b -> b) -> Release -> Release
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Release)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Release)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Release)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Release)
dataTypeOf :: Release -> DataType
$cdataTypeOf :: Release -> DataType
toConstr :: Release -> Constr
$ctoConstr :: Release -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Release
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Release
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Release -> c Release
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Release -> c Release
Data, Typeable, Release -> Release -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Release -> Release -> Bool
$c/= :: Release -> Release -> Bool
== :: Release -> Release -> Bool
$c== :: Release -> Release -> Bool
Eq, Eq Release
Release -> Release -> Bool
Release -> Release -> Ordering
Release -> Release -> Release
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Release -> Release -> Release
$cmin :: Release -> Release -> Release
max :: Release -> Release -> Release
$cmax :: Release -> Release -> Release
>= :: Release -> Release -> Bool
$c>= :: Release -> Release -> Bool
> :: Release -> Release -> Bool
$c> :: Release -> Release -> Bool
<= :: Release -> Release -> Bool
$c<= :: Release -> Release -> Bool
< :: Release -> Release -> Bool
$c< :: Release -> Release -> Bool
compare :: Release -> Release -> Ordering
$ccompare :: Release -> Release -> Ordering
Ord, forall x. Rep Release x -> Release
forall x. Release -> Rep Release x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Release x -> Release
$cfrom :: forall x. Release -> Rep Release x
Generic)

instance FromJSON Release where
    parseJSON :: Value -> Parser Release
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Event" forall a b. (a -> b) -> a -> b
$ \Object
o -> URL
-> URL
-> URL
-> URL
-> URL
-> URL
-> Id Release
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Bool
-> UTCTime
-> Maybe UTCTime
-> SimpleUser
-> Vector ReleaseAsset
-> Release
Release
        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"url"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"html_url"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"assets_url"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"upload_url"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"tarball_url"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"zipball_url"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"tag_name"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"target_commitish"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"body"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"draft"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"prerelease"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"created_at"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"published_at"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"author"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"assets"

instance NFData Release where rnf :: Release -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary Release

data ReleaseAsset = ReleaseAsset
    { ReleaseAsset -> URL
releaseAssetUrl                :: !URL
    , ReleaseAsset -> Text
releaseAssetBrowserDownloadUrl :: !Text
    , ReleaseAsset -> Id ReleaseAsset
releaseAssetId                 :: !(Id ReleaseAsset)
    , ReleaseAsset -> Text
releaseAssetName               :: !Text
    , ReleaseAsset -> Maybe Text
releaseAssetLabel              :: !(Maybe Text)
    , ReleaseAsset -> Text
releaseAssetState              :: !Text
    , ReleaseAsset -> Text
releaseAssetContentType        :: !Text
    , ReleaseAsset -> Int
releaseAssetSize               :: !Int
    , ReleaseAsset -> Int
releaseAssetDownloadCount      :: !Int
    , ReleaseAsset -> UTCTime
releaseAssetCreatedAt          :: !UTCTime
    , ReleaseAsset -> UTCTime
releaseAssetUpdatedAt          :: !UTCTime
    , ReleaseAsset -> SimpleUser
releaseAssetUploader           :: !SimpleUser
    }
    deriving (Int -> ReleaseAsset -> ShowS
[ReleaseAsset] -> ShowS
ReleaseAsset -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReleaseAsset] -> ShowS
$cshowList :: [ReleaseAsset] -> ShowS
show :: ReleaseAsset -> String
$cshow :: ReleaseAsset -> String
showsPrec :: Int -> ReleaseAsset -> ShowS
$cshowsPrec :: Int -> ReleaseAsset -> ShowS
Show, Typeable ReleaseAsset
ReleaseAsset -> DataType
ReleaseAsset -> Constr
(forall b. Data b => b -> b) -> ReleaseAsset -> ReleaseAsset
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ReleaseAsset -> u
forall u. (forall d. Data d => d -> u) -> ReleaseAsset -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReleaseAsset -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReleaseAsset -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ReleaseAsset -> m ReleaseAsset
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ReleaseAsset -> m ReleaseAsset
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReleaseAsset
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReleaseAsset -> c ReleaseAsset
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReleaseAsset)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReleaseAsset)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ReleaseAsset -> m ReleaseAsset
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ReleaseAsset -> m ReleaseAsset
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ReleaseAsset -> m ReleaseAsset
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ReleaseAsset -> m ReleaseAsset
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ReleaseAsset -> m ReleaseAsset
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ReleaseAsset -> m ReleaseAsset
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ReleaseAsset -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ReleaseAsset -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ReleaseAsset -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ReleaseAsset -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReleaseAsset -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReleaseAsset -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReleaseAsset -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReleaseAsset -> r
gmapT :: (forall b. Data b => b -> b) -> ReleaseAsset -> ReleaseAsset
$cgmapT :: (forall b. Data b => b -> b) -> ReleaseAsset -> ReleaseAsset
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReleaseAsset)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReleaseAsset)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReleaseAsset)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReleaseAsset)
dataTypeOf :: ReleaseAsset -> DataType
$cdataTypeOf :: ReleaseAsset -> DataType
toConstr :: ReleaseAsset -> Constr
$ctoConstr :: ReleaseAsset -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReleaseAsset
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReleaseAsset
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReleaseAsset -> c ReleaseAsset
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReleaseAsset -> c ReleaseAsset
Data, Typeable, ReleaseAsset -> ReleaseAsset -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReleaseAsset -> ReleaseAsset -> Bool
$c/= :: ReleaseAsset -> ReleaseAsset -> Bool
== :: ReleaseAsset -> ReleaseAsset -> Bool
$c== :: ReleaseAsset -> ReleaseAsset -> Bool
Eq, Eq ReleaseAsset
ReleaseAsset -> ReleaseAsset -> Bool
ReleaseAsset -> ReleaseAsset -> Ordering
ReleaseAsset -> ReleaseAsset -> ReleaseAsset
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ReleaseAsset -> ReleaseAsset -> ReleaseAsset
$cmin :: ReleaseAsset -> ReleaseAsset -> ReleaseAsset
max :: ReleaseAsset -> ReleaseAsset -> ReleaseAsset
$cmax :: ReleaseAsset -> ReleaseAsset -> ReleaseAsset
>= :: ReleaseAsset -> ReleaseAsset -> Bool
$c>= :: ReleaseAsset -> ReleaseAsset -> Bool
> :: ReleaseAsset -> ReleaseAsset -> Bool
$c> :: ReleaseAsset -> ReleaseAsset -> Bool
<= :: ReleaseAsset -> ReleaseAsset -> Bool
$c<= :: ReleaseAsset -> ReleaseAsset -> Bool
< :: ReleaseAsset -> ReleaseAsset -> Bool
$c< :: ReleaseAsset -> ReleaseAsset -> Bool
compare :: ReleaseAsset -> ReleaseAsset -> Ordering
$ccompare :: ReleaseAsset -> ReleaseAsset -> Ordering
Ord, forall x. Rep ReleaseAsset x -> ReleaseAsset
forall x. ReleaseAsset -> Rep ReleaseAsset x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReleaseAsset x -> ReleaseAsset
$cfrom :: forall x. ReleaseAsset -> Rep ReleaseAsset x
Generic)

instance FromJSON ReleaseAsset where
    parseJSON :: Value -> Parser ReleaseAsset
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Event" forall a b. (a -> b) -> a -> b
$ \Object
o -> URL
-> Text
-> Id ReleaseAsset
-> Text
-> Maybe Text
-> Text
-> Text
-> Int
-> Int
-> UTCTime
-> UTCTime
-> SimpleUser
-> ReleaseAsset
ReleaseAsset
        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"url"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"browser_download_url"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"label"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"state"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"content_type"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"size"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"download_count"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"created_at"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"updated_at"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"uploader"

instance NFData ReleaseAsset where rnf :: ReleaseAsset -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary ReleaseAsset