{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards   #-}
{-# LANGUAGE StrictData        #-}
module GitHub.Types.Base.Repository 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.DateTime
import           GitHub.Types.Base.License
import           GitHub.Types.Base.RepoOwner

------------------------------------------------------------------------------
-- Repository

data Repository = Repository
    { Repository -> Maybe Bool
repositoryAllowAutoMerge           :: Maybe Bool
    , Repository -> Bool
repositoryAllowForking             :: Bool
    , Repository -> Maybe Bool
repositoryAllowMergeCommit         :: Maybe Bool
    , Repository -> Maybe Bool
repositoryAllowRebaseMerge         :: Maybe Bool
    , Repository -> Maybe Bool
repositoryAllowSquashMerge         :: Maybe Bool
    , Repository -> Maybe Bool
repositoryAllowUpdateBranch        :: Maybe Bool
    , Repository -> Bool
repositoryArchived                 :: Bool
    , Repository -> Text
repositoryArchiveUrl               :: Text
    , Repository -> Text
repositoryAssigneesUrl             :: Text
    , Repository -> Text
repositoryBlobsUrl                 :: Text
    , Repository -> Text
repositoryBranchesUrl              :: Text
    , Repository -> Text
repositoryCloneUrl                 :: Text
    , Repository -> Text
repositoryCollaboratorsUrl         :: Text
    , Repository -> Text
repositoryCommentsUrl              :: Text
    , Repository -> Text
repositoryCommitsUrl               :: Text
    , Repository -> Text
repositoryCompareUrl               :: Text
    , Repository -> Text
repositoryContentsUrl              :: Text
    , Repository -> Text
repositoryContributorsUrl          :: Text
    , Repository -> DateTime
repositoryCreatedAt                :: DateTime
    , Repository -> Value
repositoryCustomProperties         :: Value  -- TODO(iphydf): Figure out what this actually is.
    , Repository -> Text
repositoryDefaultBranch            :: Text
    , Repository -> Maybe Bool
repositoryDeleteBranchOnMerge      :: Maybe Bool
    , Repository -> Text
repositoryDeploymentsUrl           :: Text
    , Repository -> Maybe Text
repositoryDescription              :: Maybe Text
    , Repository -> Bool
repositoryDisabled                 :: Bool
    , Repository -> Text
repositoryDownloadsUrl             :: Text
    , Repository -> Text
repositoryEventsUrl                :: Text
    , Repository -> Bool
repositoryFork                     :: Bool
    , Repository -> Int
repositoryForks                    :: Int
    , Repository -> Int
repositoryForksCount               :: Int
    , Repository -> Text
repositoryForksUrl                 :: Text
    , Repository -> Text
repositoryFullName                 :: Text
    , Repository -> Text
repositoryGitCommitsUrl            :: Text
    , Repository -> Text
repositoryGitRefsUrl               :: Text
    , Repository -> Text
repositoryGitTagsUrl               :: Text
    , Repository -> Text
repositoryGitUrl                   :: Text
    , Repository -> Bool
repositoryIsTemplate               :: Bool
    , Repository -> Bool
repositoryHasDiscussions           :: Bool
    , Repository -> Bool
repositoryHasDownloads             :: Bool
    , Repository -> Bool
repositoryHasIssues                :: Bool
    , Repository -> Bool
repositoryHasPages                 :: Bool
    , Repository -> Bool
repositoryHasProjects              :: Bool
    , Repository -> Bool
repositoryHasWiki                  :: Bool
    , Repository -> Maybe Text
repositoryHomepage                 :: Maybe Text
    , Repository -> Text
repositoryHooksUrl                 :: Text
    , Repository -> Text
repositoryHtmlUrl                  :: Text
    , Repository -> Int
repositoryId                       :: Int
    , Repository -> Text
repositoryIssueCommentUrl          :: Text
    , Repository -> Text
repositoryIssueEventsUrl           :: Text
    , Repository -> Text
repositoryIssuesUrl                :: Text
    , Repository -> Text
repositoryKeysUrl                  :: Text
    , Repository -> Text
repositoryLabelsUrl                :: Text
    , Repository -> Maybe Text
repositoryLanguage                 :: Maybe Text
    , Repository -> Text
repositoryLanguagesUrl             :: Text
    , Repository -> Maybe License
repositoryLicense                  :: Maybe License
    , Repository -> Maybe Text
repositoryMasterBranch             :: Maybe Text
    , Repository -> Text
repositoryMergesUrl                :: Text
    , Repository -> Text
repositoryMilestonesUrl            :: Text
    , Repository -> Maybe Text
repositoryMirrorUrl                :: Maybe Text
    , Repository -> Text
repositoryName                     :: Text
    , Repository -> Text
repositoryNodeId                   :: Text
    , Repository -> Text
repositoryNotificationsUrl         :: Text
    , Repository -> Int
repositoryOpenIssues               :: Int
    , Repository -> Int
repositoryOpenIssuesCount          :: Int
    , Repository -> Maybe Text
repositoryOrganization             :: Maybe Text
    , Repository -> RepoOwner
repositoryOwner                    :: RepoOwner
    , Repository -> Bool
repositoryPrivate                  :: Bool
    , Repository -> Maybe Bool
repositoryPublic                   :: Maybe Bool
    , Repository -> Text
repositoryPullsUrl                 :: Text
    , Repository -> Maybe DateTime
repositoryPushedAt                 :: Maybe DateTime
    , Repository -> Text
repositoryReleasesUrl              :: Text
    , Repository -> Int
repositorySize                     :: Int
    , Repository -> Text
repositorySshUrl                   :: Text
    , Repository -> Maybe Int
repositoryStargazers               :: Maybe Int
    , Repository -> Int
repositoryStargazersCount          :: Int
    , Repository -> Text
repositoryStargazersUrl            :: Text
    , Repository -> Text
repositoryStatusesUrl              :: Text
    , Repository -> Text
repositorySubscribersUrl           :: Text
    , Repository -> Text
repositorySubscriptionUrl          :: Text
    , Repository -> Text
repositorySvnUrl                   :: Text
    , Repository -> Text
repositoryTagsUrl                  :: Text
    , Repository -> Text
repositoryTeamsUrl                 :: Text
    , Repository -> [Text]
repositoryTopics                   :: [Text]
    , Repository -> Text
repositoryTreesUrl                 :: Text
    , Repository -> DateTime
repositoryUpdatedAt                :: DateTime
    , Repository -> Text
repositoryUrl                      :: Text
    , Repository -> Text
repositoryVisibility               :: Text
    , Repository -> Int
repositoryWatchers                 :: Int
    , Repository -> Int
repositoryWatchersCount            :: Int
    , Repository -> Bool
repositoryWebCommitSignoffRequired :: Bool
    } deriving (Repository -> Repository -> Bool
(Repository -> Repository -> Bool)
-> (Repository -> Repository -> Bool) -> Eq Repository
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Repository -> Repository -> Bool
$c/= :: Repository -> Repository -> Bool
== :: Repository -> Repository -> Bool
$c== :: Repository -> Repository -> Bool
Eq, Int -> Repository -> ShowS
[Repository] -> ShowS
Repository -> String
(Int -> Repository -> ShowS)
-> (Repository -> String)
-> ([Repository] -> ShowS)
-> Show Repository
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Repository] -> ShowS
$cshowList :: [Repository] -> ShowS
show :: Repository -> String
$cshow :: Repository -> String
showsPrec :: Int -> Repository -> ShowS
$cshowsPrec :: Int -> Repository -> ShowS
Show, ReadPrec [Repository]
ReadPrec Repository
Int -> ReadS Repository
ReadS [Repository]
(Int -> ReadS Repository)
-> ReadS [Repository]
-> ReadPrec Repository
-> ReadPrec [Repository]
-> Read Repository
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Repository]
$creadListPrec :: ReadPrec [Repository]
readPrec :: ReadPrec Repository
$creadPrec :: ReadPrec Repository
readList :: ReadS [Repository]
$creadList :: ReadS [Repository]
readsPrec :: Int -> ReadS Repository
$creadsPrec :: Int -> ReadS Repository
Read)


instance FromJSON Repository where
    parseJSON :: Value -> Parser Repository
parseJSON (Object Object
x) = Maybe Bool
-> Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> DateTime
-> Value
-> Text
-> Maybe Bool
-> Text
-> Maybe Text
-> Bool
-> Text
-> Text
-> Bool
-> Int
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Maybe Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Maybe License
-> Maybe Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Int
-> Int
-> Maybe Text
-> RepoOwner
-> Bool
-> Maybe Bool
-> Text
-> Maybe DateTime
-> Text
-> Int
-> Text
-> Maybe Int
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> DateTime
-> Text
-> Text
-> Int
-> Int
-> Bool
-> Repository
Repository
        (Maybe Bool
 -> Bool
 -> Maybe Bool
 -> Maybe Bool
 -> Maybe Bool
 -> Maybe Bool
 -> Bool
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> DateTime
 -> Value
 -> Text
 -> Maybe Bool
 -> Text
 -> Maybe Text
 -> Bool
 -> Text
 -> Text
 -> Bool
 -> Int
 -> Int
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Bool
 -> Bool
 -> Bool
 -> Bool
 -> Bool
 -> Bool
 -> Bool
 -> Maybe Text
 -> Text
 -> Text
 -> Int
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Maybe Text
 -> Text
 -> Maybe License
 -> Maybe Text
 -> Text
 -> Text
 -> Maybe Text
 -> Text
 -> Text
 -> Text
 -> Int
 -> Int
 -> Maybe Text
 -> RepoOwner
 -> Bool
 -> Maybe Bool
 -> Text
 -> Maybe DateTime
 -> Text
 -> Int
 -> Text
 -> Maybe Int
 -> Int
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> [Text]
 -> Text
 -> DateTime
 -> Text
 -> Text
 -> Int
 -> Int
 -> Bool
 -> Repository)
-> Parser (Maybe Bool)
-> Parser
     (Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Bool
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
x Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"allow_auto_merge"
        Parser
  (Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Bool
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Bool
-> Parser
     (Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Bool
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"allow_forking"
        Parser
  (Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Bool
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser (Maybe Bool)
-> Parser
     (Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Bool
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"allow_merge_commit"
        Parser
  (Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Bool
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser (Maybe Bool)
-> Parser
     (Maybe Bool
      -> Maybe Bool
      -> Bool
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"allow_rebase_merge"
        Parser
  (Maybe Bool
   -> Maybe Bool
   -> Bool
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser (Maybe Bool)
-> Parser
     (Maybe Bool
      -> Bool
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"allow_squash_merge"
        Parser
  (Maybe Bool
   -> Bool
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser (Maybe Bool)
-> Parser
     (Bool
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"allow_update_branch"
        Parser
  (Bool
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Bool
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"archived"
        Parser
  (Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"archive_url"
        Parser
  (Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"assignees_url"
        Parser
  (Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"blobs_url"
        Parser
  (Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"branches_url"
        Parser
  (Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"clone_url"
        Parser
  (Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"collaborators_url"
        Parser
  (Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"comments_url"
        Parser
  (Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"commits_url"
        Parser
  (Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"compare_url"
        Parser
  (Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"contents_url"
        Parser
  (Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"contributors_url"
        Parser
  (DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser DateTime
-> Parser
     (Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser DateTime
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"created_at"
        Parser
  (Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Value
-> Parser
     (Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"custom_properties"
        Parser
  (Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"default_branch"
        Parser
  (Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser (Maybe Bool)
-> Parser
     (Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"delete_branch_on_merge"
        Parser
  (Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"deployments_url"
        Parser
  (Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser (Maybe Text)
-> Parser
     (Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"description"
        Parser
  (Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Bool
-> Parser
     (Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"disabled"
        Parser
  (Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"downloads_url"
        Parser
  (Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"events_url"
        Parser
  (Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Bool
-> Parser
     (Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"fork"
        Parser
  (Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Int
-> Parser
     (Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"forks"
        Parser
  (Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Int
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"forks_count"
        Parser
  (Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"forks_url"
        Parser
  (Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"full_name"
        Parser
  (Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"git_commits_url"
        Parser
  (Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"git_refs_url"
        Parser
  (Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"git_tags_url"
        Parser
  (Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"git_url"
        Parser
  (Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Bool
-> Parser
     (Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"is_template"
        Parser
  (Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Bool
-> Parser
     (Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"has_discussions"
        Parser
  (Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Bool
-> Parser
     (Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"has_downloads"
        Parser
  (Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Bool
-> Parser
     (Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"has_issues"
        Parser
  (Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Bool
-> Parser
     (Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"has_pages"
        Parser
  (Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Bool
-> Parser
     (Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"has_projects"
        Parser
  (Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Bool
-> Parser
     (Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"has_wiki"
        Parser
  (Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser (Maybe Text)
-> Parser
     (Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"homepage"
        Parser
  (Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"hooks_url"
        Parser
  (Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
  (Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Int
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"issue_comment_url"
        Parser
  (Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"issue_events_url"
        Parser
  (Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"issues_url"
        Parser
  (Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"keys_url"
        Parser
  (Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"labels_url"
        Parser
  (Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser (Maybe Text)
-> Parser
     (Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"language"
        Parser
  (Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"languages_url"
        Parser
  (Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser (Maybe License)
-> Parser
     (Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe License)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"license"
        Parser
  (Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser (Maybe Text)
-> Parser
     (Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"master_branch"
        Parser
  (Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"merges_url"
        Parser
  (Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"milestones_url"
        Parser
  (Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser (Maybe Text)
-> Parser
     (Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"mirror_url"
        Parser
  (Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
  (Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"notifications_url"
        Parser
  (Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Int
-> Parser
     (Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"open_issues"
        Parser
  (Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Int
-> Parser
     (Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"open_issues_count"
        Parser
  (Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser (Maybe Text)
-> Parser
     (RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"organization"
        Parser
  (RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser RepoOwner
-> Parser
     (Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser RepoOwner
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"owner"
        Parser
  (Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Bool
-> Parser
     (Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"private"
        Parser
  (Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser (Maybe Bool)
-> Parser
     (Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"public"
        Parser
  (Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"pulls_url"
        Parser
  (Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser (Maybe DateTime)
-> Parser
     (Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe DateTime)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"pushed_at"
        Parser
  (Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"releases_url"
        Parser
  (Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Int
-> Parser
     (Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"size"
        Parser
  (Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"ssh_url"
        Parser
  (Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser (Maybe Int)
-> Parser
     (Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"stargazers"
        Parser
  (Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Int
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"stargazers_count"
        Parser
  (Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"stargazers_url"
        Parser
  (Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"statuses_url"
        Parser
  (Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"subscribers_url"
        Parser
  (Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"subscription_url"
        Parser
  (Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"svn_url"
        Parser
  (Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     (Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"tags_url"
        Parser
  (Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser Text
-> Parser
     ([Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
"teams_url"
        Parser
  ([Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Parser [Text]
-> Parser
     (Text
      -> DateTime -> Text -> Text -> Int -> Int -> Bool -> Repository)
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
"topics"
        Parser
  (Text
   -> DateTime -> Text -> Text -> Int -> Int -> Bool -> Repository)
-> Parser Text
-> Parser
     (DateTime -> Text -> Text -> Int -> Int -> Bool -> Repository)
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
"trees_url"
        Parser
  (DateTime -> Text -> Text -> Int -> Int -> Bool -> Repository)
-> Parser DateTime
-> Parser (Text -> Text -> Int -> Int -> Bool -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser DateTime
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"updated_at"
        Parser (Text -> Text -> Int -> Int -> Bool -> Repository)
-> Parser Text -> Parser (Text -> Int -> Int -> Bool -> Repository)
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 -> Int -> Bool -> Repository)
-> Parser Text -> Parser (Int -> Int -> Bool -> Repository)
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
"visibility"
        Parser (Int -> Int -> Bool -> Repository)
-> Parser Int -> Parser (Int -> Bool -> Repository)
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
"watchers"
        Parser (Int -> Bool -> Repository)
-> Parser Int -> Parser (Bool -> Repository)
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
"watchers_count"
        Parser (Bool -> Repository) -> Parser Bool -> Parser Repository
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
"web_commit_signoff_required"

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

instance ToJSON Repository where
    toJSON :: Repository -> Value
toJSON Repository{Bool
Int
[Text]
Maybe Bool
Maybe Int
Maybe Text
Maybe DateTime
Maybe License
Text
Value
DateTime
RepoOwner
repositoryWebCommitSignoffRequired :: Bool
repositoryWatchersCount :: Int
repositoryWatchers :: Int
repositoryVisibility :: Text
repositoryUrl :: Text
repositoryUpdatedAt :: DateTime
repositoryTreesUrl :: Text
repositoryTopics :: [Text]
repositoryTeamsUrl :: Text
repositoryTagsUrl :: Text
repositorySvnUrl :: Text
repositorySubscriptionUrl :: Text
repositorySubscribersUrl :: Text
repositoryStatusesUrl :: Text
repositoryStargazersUrl :: Text
repositoryStargazersCount :: Int
repositoryStargazers :: Maybe Int
repositorySshUrl :: Text
repositorySize :: Int
repositoryReleasesUrl :: Text
repositoryPushedAt :: Maybe DateTime
repositoryPullsUrl :: Text
repositoryPublic :: Maybe Bool
repositoryPrivate :: Bool
repositoryOwner :: RepoOwner
repositoryOrganization :: Maybe Text
repositoryOpenIssuesCount :: Int
repositoryOpenIssues :: Int
repositoryNotificationsUrl :: Text
repositoryNodeId :: Text
repositoryName :: Text
repositoryMirrorUrl :: Maybe Text
repositoryMilestonesUrl :: Text
repositoryMergesUrl :: Text
repositoryMasterBranch :: Maybe Text
repositoryLicense :: Maybe License
repositoryLanguagesUrl :: Text
repositoryLanguage :: Maybe Text
repositoryLabelsUrl :: Text
repositoryKeysUrl :: Text
repositoryIssuesUrl :: Text
repositoryIssueEventsUrl :: Text
repositoryIssueCommentUrl :: Text
repositoryId :: Int
repositoryHtmlUrl :: Text
repositoryHooksUrl :: Text
repositoryHomepage :: Maybe Text
repositoryHasWiki :: Bool
repositoryHasProjects :: Bool
repositoryHasPages :: Bool
repositoryHasIssues :: Bool
repositoryHasDownloads :: Bool
repositoryHasDiscussions :: Bool
repositoryIsTemplate :: Bool
repositoryGitUrl :: Text
repositoryGitTagsUrl :: Text
repositoryGitRefsUrl :: Text
repositoryGitCommitsUrl :: Text
repositoryFullName :: Text
repositoryForksUrl :: Text
repositoryForksCount :: Int
repositoryForks :: Int
repositoryFork :: Bool
repositoryEventsUrl :: Text
repositoryDownloadsUrl :: Text
repositoryDisabled :: Bool
repositoryDescription :: Maybe Text
repositoryDeploymentsUrl :: Text
repositoryDeleteBranchOnMerge :: Maybe Bool
repositoryDefaultBranch :: Text
repositoryCustomProperties :: Value
repositoryCreatedAt :: DateTime
repositoryContributorsUrl :: Text
repositoryContentsUrl :: Text
repositoryCompareUrl :: Text
repositoryCommitsUrl :: Text
repositoryCommentsUrl :: Text
repositoryCollaboratorsUrl :: Text
repositoryCloneUrl :: Text
repositoryBranchesUrl :: Text
repositoryBlobsUrl :: Text
repositoryAssigneesUrl :: Text
repositoryArchiveUrl :: Text
repositoryArchived :: Bool
repositoryAllowUpdateBranch :: Maybe Bool
repositoryAllowSquashMerge :: Maybe Bool
repositoryAllowRebaseMerge :: Maybe Bool
repositoryAllowMergeCommit :: Maybe Bool
repositoryAllowForking :: Bool
repositoryAllowAutoMerge :: Maybe Bool
repositoryWebCommitSignoffRequired :: Repository -> Bool
repositoryWatchersCount :: Repository -> Int
repositoryWatchers :: Repository -> Int
repositoryVisibility :: Repository -> Text
repositoryUrl :: Repository -> Text
repositoryUpdatedAt :: Repository -> DateTime
repositoryTreesUrl :: Repository -> Text
repositoryTopics :: Repository -> [Text]
repositoryTeamsUrl :: Repository -> Text
repositoryTagsUrl :: Repository -> Text
repositorySvnUrl :: Repository -> Text
repositorySubscriptionUrl :: Repository -> Text
repositorySubscribersUrl :: Repository -> Text
repositoryStatusesUrl :: Repository -> Text
repositoryStargazersUrl :: Repository -> Text
repositoryStargazersCount :: Repository -> Int
repositoryStargazers :: Repository -> Maybe Int
repositorySshUrl :: Repository -> Text
repositorySize :: Repository -> Int
repositoryReleasesUrl :: Repository -> Text
repositoryPushedAt :: Repository -> Maybe DateTime
repositoryPullsUrl :: Repository -> Text
repositoryPublic :: Repository -> Maybe Bool
repositoryPrivate :: Repository -> Bool
repositoryOwner :: Repository -> RepoOwner
repositoryOrganization :: Repository -> Maybe Text
repositoryOpenIssuesCount :: Repository -> Int
repositoryOpenIssues :: Repository -> Int
repositoryNotificationsUrl :: Repository -> Text
repositoryNodeId :: Repository -> Text
repositoryName :: Repository -> Text
repositoryMirrorUrl :: Repository -> Maybe Text
repositoryMilestonesUrl :: Repository -> Text
repositoryMergesUrl :: Repository -> Text
repositoryMasterBranch :: Repository -> Maybe Text
repositoryLicense :: Repository -> Maybe License
repositoryLanguagesUrl :: Repository -> Text
repositoryLanguage :: Repository -> Maybe Text
repositoryLabelsUrl :: Repository -> Text
repositoryKeysUrl :: Repository -> Text
repositoryIssuesUrl :: Repository -> Text
repositoryIssueEventsUrl :: Repository -> Text
repositoryIssueCommentUrl :: Repository -> Text
repositoryId :: Repository -> Int
repositoryHtmlUrl :: Repository -> Text
repositoryHooksUrl :: Repository -> Text
repositoryHomepage :: Repository -> Maybe Text
repositoryHasWiki :: Repository -> Bool
repositoryHasProjects :: Repository -> Bool
repositoryHasPages :: Repository -> Bool
repositoryHasIssues :: Repository -> Bool
repositoryHasDownloads :: Repository -> Bool
repositoryHasDiscussions :: Repository -> Bool
repositoryIsTemplate :: Repository -> Bool
repositoryGitUrl :: Repository -> Text
repositoryGitTagsUrl :: Repository -> Text
repositoryGitRefsUrl :: Repository -> Text
repositoryGitCommitsUrl :: Repository -> Text
repositoryFullName :: Repository -> Text
repositoryForksUrl :: Repository -> Text
repositoryForksCount :: Repository -> Int
repositoryForks :: Repository -> Int
repositoryFork :: Repository -> Bool
repositoryEventsUrl :: Repository -> Text
repositoryDownloadsUrl :: Repository -> Text
repositoryDisabled :: Repository -> Bool
repositoryDescription :: Repository -> Maybe Text
repositoryDeploymentsUrl :: Repository -> Text
repositoryDeleteBranchOnMerge :: Repository -> Maybe Bool
repositoryDefaultBranch :: Repository -> Text
repositoryCustomProperties :: Repository -> Value
repositoryCreatedAt :: Repository -> DateTime
repositoryContributorsUrl :: Repository -> Text
repositoryContentsUrl :: Repository -> Text
repositoryCompareUrl :: Repository -> Text
repositoryCommitsUrl :: Repository -> Text
repositoryCommentsUrl :: Repository -> Text
repositoryCollaboratorsUrl :: Repository -> Text
repositoryCloneUrl :: Repository -> Text
repositoryBranchesUrl :: Repository -> Text
repositoryBlobsUrl :: Repository -> Text
repositoryAssigneesUrl :: Repository -> Text
repositoryArchiveUrl :: Repository -> Text
repositoryArchived :: Repository -> Bool
repositoryAllowUpdateBranch :: Repository -> Maybe Bool
repositoryAllowSquashMerge :: Repository -> Maybe Bool
repositoryAllowRebaseMerge :: Repository -> Maybe Bool
repositoryAllowMergeCommit :: Repository -> Maybe Bool
repositoryAllowForking :: Repository -> Bool
repositoryAllowAutoMerge :: Repository -> Maybe Bool
..} = [Pair] -> Value
object
        [ Key
"allow_auto_merge"            Key -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
repositoryAllowAutoMerge
        , Key
"allow_forking"               Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
repositoryAllowForking
        , Key
"allow_merge_commit"          Key -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
repositoryAllowMergeCommit
        , Key
"allow_rebase_merge"          Key -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
repositoryAllowRebaseMerge
        , Key
"allow_squash_merge"          Key -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
repositoryAllowSquashMerge
        , Key
"allow_update_branch"         Key -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
repositoryAllowUpdateBranch
        , Key
"archived"                    Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
repositoryArchived
        , Key
"archive_url"                 Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryArchiveUrl
        , Key
"assignees_url"               Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryAssigneesUrl
        , Key
"blobs_url"                   Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryBlobsUrl
        , Key
"branches_url"                Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryBranchesUrl
        , Key
"clone_url"                   Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryCloneUrl
        , Key
"collaborators_url"           Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryCollaboratorsUrl
        , Key
"comments_url"                Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryCommentsUrl
        , Key
"commits_url"                 Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryCommitsUrl
        , Key
"compare_url"                 Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryCompareUrl
        , Key
"contents_url"                Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryContentsUrl
        , Key
"contributors_url"            Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryContributorsUrl
        , Key
"created_at"                  Key -> DateTime -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= DateTime
repositoryCreatedAt
        , Key
"custom_properties"           Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Value
repositoryCustomProperties
        , Key
"default_branch"              Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryDefaultBranch
        , Key
"delete_branch_on_merge"      Key -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
repositoryDeleteBranchOnMerge
        , Key
"deployments_url"             Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryDeploymentsUrl
        , Key
"description"                 Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
repositoryDescription
        , Key
"disabled"                    Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
repositoryDisabled
        , Key
"downloads_url"               Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryDownloadsUrl
        , Key
"events_url"                  Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryEventsUrl
        , Key
"fork"                        Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
repositoryFork
        , Key
"forks"                       Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
repositoryForks
        , Key
"forks_count"                 Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
repositoryForksCount
        , Key
"forks_url"                   Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryForksUrl
        , Key
"full_name"                   Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryFullName
        , Key
"git_commits_url"             Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryGitCommitsUrl
        , Key
"git_refs_url"                Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryGitRefsUrl
        , Key
"git_tags_url"                Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryGitTagsUrl
        , Key
"git_url"                     Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryGitUrl
        , Key
"is_template"                 Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
repositoryIsTemplate
        , Key
"has_discussions"             Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
repositoryHasDiscussions
        , Key
"has_downloads"               Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
repositoryHasDownloads
        , Key
"has_issues"                  Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
repositoryHasIssues
        , Key
"has_pages"                   Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
repositoryHasPages
        , Key
"has_projects"                Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
repositoryHasProjects
        , Key
"has_wiki"                    Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
repositoryHasWiki
        , Key
"homepage"                    Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
repositoryHomepage
        , Key
"hooks_url"                   Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryHooksUrl
        , Key
"html_url"                    Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryHtmlUrl
        , Key
"id"                          Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
repositoryId
        , Key
"issue_comment_url"           Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryIssueCommentUrl
        , Key
"issue_events_url"            Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryIssueEventsUrl
        , Key
"issues_url"                  Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryIssuesUrl
        , Key
"keys_url"                    Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryKeysUrl
        , Key
"labels_url"                  Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryLabelsUrl
        , Key
"language"                    Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
repositoryLanguage
        , Key
"languages_url"               Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryLanguagesUrl
        , Key
"license"                     Key -> Maybe License -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe License
repositoryLicense
        , Key
"master_branch"               Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
repositoryMasterBranch
        , Key
"merges_url"                  Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryMergesUrl
        , Key
"milestones_url"              Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryMilestonesUrl
        , Key
"mirror_url"                  Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
repositoryMirrorUrl
        , Key
"name"                        Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryName
        , Key
"node_id"                     Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryNodeId
        , Key
"notifications_url"           Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryNotificationsUrl
        , Key
"open_issues"                 Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
repositoryOpenIssues
        , Key
"open_issues_count"           Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
repositoryOpenIssuesCount
        , Key
"organization"                Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
repositoryOrganization
        , Key
"owner"                       Key -> RepoOwner -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= RepoOwner
repositoryOwner
        , Key
"private"                     Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
repositoryPrivate
        , Key
"public"                      Key -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
repositoryPublic
        , Key
"pulls_url"                   Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryPullsUrl
        , Key
"pushed_at"                   Key -> Maybe DateTime -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe DateTime
repositoryPushedAt
        , Key
"releases_url"                Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryReleasesUrl
        , Key
"size"                        Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
repositorySize
        , Key
"ssh_url"                     Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositorySshUrl
        , Key
"stargazers"                  Key -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Int
repositoryStargazers
        , Key
"stargazers_count"            Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
repositoryStargazersCount
        , Key
"stargazers_url"              Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryStargazersUrl
        , Key
"statuses_url"                Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryStatusesUrl
        , Key
"subscribers_url"             Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositorySubscribersUrl
        , Key
"subscription_url"            Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositorySubscriptionUrl
        , Key
"svn_url"                     Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositorySvnUrl
        , Key
"tags_url"                    Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryTagsUrl
        , Key
"teams_url"                   Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryTeamsUrl
        , Key
"topics"                      Key -> [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [Text]
repositoryTopics
        , Key
"trees_url"                   Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryTreesUrl
        , Key
"updated_at"                  Key -> DateTime -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= DateTime
repositoryUpdatedAt
        , Key
"url"                         Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryUrl
        , Key
"visibility"                  Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
repositoryVisibility
        , Key
"watchers"                    Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
repositoryWatchers
        , Key
"watchers_count"              Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
repositoryWatchersCount
        , Key
"web_commit_signoff_required" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
repositoryWebCommitSignoffRequired
        ]


instance Arbitrary Repository where
    arbitrary :: Gen Repository
arbitrary = Maybe Bool
-> Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> DateTime
-> Value
-> Text
-> Maybe Bool
-> Text
-> Maybe Text
-> Bool
-> Text
-> Text
-> Bool
-> Int
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Maybe Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Maybe License
-> Maybe Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Text
-> Int
-> Int
-> Maybe Text
-> RepoOwner
-> Bool
-> Maybe Bool
-> Text
-> Maybe DateTime
-> Text
-> Int
-> Text
-> Maybe Int
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> [Text]
-> Text
-> DateTime
-> Text
-> Text
-> Int
-> Int
-> Bool
-> Repository
Repository
        (Maybe Bool
 -> Bool
 -> Maybe Bool
 -> Maybe Bool
 -> Maybe Bool
 -> Maybe Bool
 -> Bool
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> DateTime
 -> Value
 -> Text
 -> Maybe Bool
 -> Text
 -> Maybe Text
 -> Bool
 -> Text
 -> Text
 -> Bool
 -> Int
 -> Int
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Bool
 -> Bool
 -> Bool
 -> Bool
 -> Bool
 -> Bool
 -> Bool
 -> Maybe Text
 -> Text
 -> Text
 -> Int
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Maybe Text
 -> Text
 -> Maybe License
 -> Maybe Text
 -> Text
 -> Text
 -> Maybe Text
 -> Text
 -> Text
 -> Text
 -> Int
 -> Int
 -> Maybe Text
 -> RepoOwner
 -> Bool
 -> Maybe Bool
 -> Text
 -> Maybe DateTime
 -> Text
 -> Int
 -> Text
 -> Maybe Int
 -> Int
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> Text
 -> [Text]
 -> Text
 -> DateTime
 -> Text
 -> Text
 -> Int
 -> Int
 -> Bool
 -> Repository)
-> Gen (Maybe Bool)
-> Gen
     (Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Bool
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Maybe Bool)
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Bool
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Bool
-> Gen
     (Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Bool
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Bool
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Bool
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen (Maybe Bool)
-> Gen
     (Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Bool
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Bool)
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Bool
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen (Maybe Bool)
-> Gen
     (Maybe Bool
      -> Maybe Bool
      -> Bool
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Bool)
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Maybe Bool
   -> Maybe Bool
   -> Bool
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen (Maybe Bool)
-> Gen
     (Maybe Bool
      -> Bool
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Bool)
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Maybe Bool
   -> Bool
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen (Maybe Bool)
-> Gen
     (Bool
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Bool)
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Bool
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Bool
-> Gen
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Text
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Text
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Text
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Text
   -> DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (DateTime
      -> Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (DateTime
   -> Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen DateTime
-> Gen
     (Value
      -> Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen DateTime
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Value
   -> Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Value
-> Gen
     (Text
      -> Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Value
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Text
   -> Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Maybe Bool
      -> Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Maybe Bool
   -> Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen (Maybe Bool)
-> Gen
     (Text
      -> Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Bool)
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Text
   -> Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Maybe Text
      -> Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Maybe Text
   -> Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen (Maybe Text)
-> Gen
     (Bool
      -> Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Text)
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Bool
   -> Text
   -> Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Bool
-> Gen
     (Text
      -> Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Text
   -> Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Bool
      -> Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Bool
   -> Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Bool
-> Gen
     (Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Bool
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Int
-> Gen
     (Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Int
-> Gen
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Text
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Text
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Bool
-> Gen
     (Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Bool
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Bool
-> Gen
     (Bool
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Bool
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Bool
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Bool
-> Gen
     (Bool
      -> Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Bool
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Bool
   -> Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Bool
-> Gen
     (Bool
      -> Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Bool
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Bool
   -> Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Bool
-> Gen
     (Bool
      -> Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Bool
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Bool
   -> Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Bool
-> Gen
     (Bool
      -> Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Bool
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Bool
   -> Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Bool
-> Gen
     (Maybe Text
      -> Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Bool
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Maybe Text
   -> Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen (Maybe Text)
-> Gen
     (Text
      -> Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Text)
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Text
   -> Text
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Text
   -> Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Int
-> Gen
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Text
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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 Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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 Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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 Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Maybe Text
      -> Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Maybe Text
   -> Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen (Maybe Text)
-> Gen
     (Text
      -> Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Text)
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Text
   -> Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Maybe License
      -> Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Maybe License
   -> Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen (Maybe License)
-> Gen
     (Maybe Text
      -> Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe License)
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Maybe Text
   -> Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen (Maybe Text)
-> Gen
     (Text
      -> Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Text)
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Text
   -> Text
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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 Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Maybe Text
      -> Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Maybe Text
   -> Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen (Maybe Text)
-> Gen
     (Text
      -> Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Text)
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Text
   -> Text
   -> Text
   -> Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Int
      -> Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Int
   -> Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Int
-> Gen
     (Int
      -> Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Int
   -> Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Int
-> Gen
     (Maybe Text
      -> RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Maybe Text
   -> RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen (Maybe Text)
-> Gen
     (RepoOwner
      -> Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Text)
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (RepoOwner
   -> Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen RepoOwner
-> Gen
     (Bool
      -> Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen RepoOwner
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Bool
   -> Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Bool
-> Gen
     (Maybe Bool
      -> Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Bool
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Maybe Bool
   -> Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen (Maybe Bool)
-> Gen
     (Text
      -> Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Bool)
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Text
   -> Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Maybe DateTime
      -> Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Maybe DateTime
   -> Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen (Maybe DateTime)
-> Gen
     (Text
      -> Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe DateTime)
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Text
   -> Int
   -> Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Int
      -> Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Int
-> Gen
     (Text
      -> Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Text
   -> Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Maybe Int
      -> Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Maybe Int
   -> Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen (Maybe Int)
-> Gen
     (Int
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Maybe Int)
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Int
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Int
-> Gen
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Text
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Text
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> Text
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> [Text]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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]
   -> Text
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     (Text
      -> [Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen Text
-> Gen
     ([Text]
      -> Text
      -> DateTime
      -> Text
      -> Text
      -> Int
      -> Int
      -> Bool
      -> Repository)
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
   -> DateTime
   -> Text
   -> Text
   -> Int
   -> Int
   -> Bool
   -> Repository)
-> Gen [Text]
-> Gen
     (Text
      -> DateTime -> Text -> Text -> Int -> Int -> Bool -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen [Text]
forall a. Arbitrary a => Gen a
arbitrary
        Gen
  (Text
   -> DateTime -> Text -> Text -> Int -> Int -> Bool -> Repository)
-> Gen Text
-> Gen
     (DateTime -> Text -> Text -> Int -> Int -> Bool -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
        Gen (DateTime -> Text -> Text -> Int -> Int -> Bool -> Repository)
-> Gen DateTime
-> Gen (Text -> Text -> Int -> Int -> Bool -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen DateTime
forall a. Arbitrary a => Gen a
arbitrary
        Gen (Text -> Text -> Int -> Int -> Bool -> Repository)
-> Gen Text -> Gen (Text -> Int -> Int -> Bool -> Repository)
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 -> Int -> Bool -> Repository)
-> Gen Text -> Gen (Int -> Int -> Bool -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
        Gen (Int -> Int -> Bool -> Repository)
-> Gen Int -> Gen (Int -> Bool -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
        Gen (Int -> Bool -> Repository)
-> Gen Int -> Gen (Bool -> Repository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
        Gen (Bool -> Repository) -> Gen Bool -> Gen Repository
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Bool
forall a. Arbitrary a => Gen a
arbitrary