{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
module GitHub.Types.Base.SimpleRepository 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.RepoOwner
data SimpleRepository = SimpleRepository
{ SimpleRepository -> Text
simpleRepositoryArchiveUrl :: Text
, SimpleRepository -> Text
simpleRepositoryAssigneesUrl :: Text
, SimpleRepository -> Text
simpleRepositoryBlobsUrl :: Text
, SimpleRepository -> Text
simpleRepositoryBranchesUrl :: Text
, SimpleRepository -> Text
simpleRepositoryCollaboratorsUrl :: Text
, :: Text
, SimpleRepository -> Text
simpleRepositoryCommitsUrl :: Text
, SimpleRepository -> Text
simpleRepositoryCompareUrl :: Text
, SimpleRepository -> Text
simpleRepositoryContentsUrl :: Text
, SimpleRepository -> Text
simpleRepositoryContributorsUrl :: Text
, SimpleRepository -> Text
simpleRepositoryDeploymentsUrl :: Text
, SimpleRepository -> Maybe Text
simpleRepositoryDescription :: Maybe Text
, SimpleRepository -> Text
simpleRepositoryDownloadsUrl :: Text
, SimpleRepository -> Text
simpleRepositoryEventsUrl :: Text
, SimpleRepository -> Bool
simpleRepositoryFork :: Bool
, SimpleRepository -> Text
simpleRepositoryForksUrl :: Text
, SimpleRepository -> Text
simpleRepositoryFullName :: Text
, SimpleRepository -> Text
simpleRepositoryGitCommitsUrl :: Text
, SimpleRepository -> Text
simpleRepositoryGitRefsUrl :: Text
, SimpleRepository -> Text
simpleRepositoryGitTagsUrl :: Text
, SimpleRepository -> Text
simpleRepositoryHooksUrl :: Text
, SimpleRepository -> Text
simpleRepositoryHtmlUrl :: Text
, SimpleRepository -> Int
simpleRepositoryId :: Int
, :: Text
, SimpleRepository -> Text
simpleRepositoryIssueEventsUrl :: Text
, SimpleRepository -> Text
simpleRepositoryIssuesUrl :: Text
, SimpleRepository -> Text
simpleRepositoryKeysUrl :: Text
, SimpleRepository -> Text
simpleRepositoryLabelsUrl :: Text
, SimpleRepository -> Text
simpleRepositoryLanguagesUrl :: Text
, SimpleRepository -> Text
simpleRepositoryMergesUrl :: Text
, SimpleRepository -> Text
simpleRepositoryMilestonesUrl :: Text
, SimpleRepository -> Text
simpleRepositoryName :: Text
, SimpleRepository -> Text
simpleRepositoryNodeId :: Text
, SimpleRepository -> Text
simpleRepositoryNotificationsUrl :: Text
, SimpleRepository -> RepoOwner
simpleRepositoryOwner :: RepoOwner
, SimpleRepository -> Bool
simpleRepositoryPrivate :: Bool
, SimpleRepository -> Text
simpleRepositoryPullsUrl :: Text
, SimpleRepository -> Text
simpleRepositoryReleasesUrl :: Text
, SimpleRepository -> Text
simpleRepositoryStargazersUrl :: Text
, SimpleRepository -> Text
simpleRepositoryStatusesUrl :: Text
, SimpleRepository -> Text
simpleRepositorySubscribersUrl :: Text
, SimpleRepository -> Text
simpleRepositorySubscriptionUrl :: Text
, SimpleRepository -> Text
simpleRepositoryTagsUrl :: Text
, SimpleRepository -> Text
simpleRepositoryTeamsUrl :: Text
, SimpleRepository -> Text
simpleRepositoryTreesUrl :: Text
, SimpleRepository -> Text
simpleRepositoryUrl :: Text
} deriving (SimpleRepository -> SimpleRepository -> Bool
(SimpleRepository -> SimpleRepository -> Bool)
-> (SimpleRepository -> SimpleRepository -> Bool)
-> Eq SimpleRepository
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SimpleRepository -> SimpleRepository -> Bool
$c/= :: SimpleRepository -> SimpleRepository -> Bool
== :: SimpleRepository -> SimpleRepository -> Bool
$c== :: SimpleRepository -> SimpleRepository -> Bool
Eq, Int -> SimpleRepository -> ShowS
[SimpleRepository] -> ShowS
SimpleRepository -> String
(Int -> SimpleRepository -> ShowS)
-> (SimpleRepository -> String)
-> ([SimpleRepository] -> ShowS)
-> Show SimpleRepository
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SimpleRepository] -> ShowS
$cshowList :: [SimpleRepository] -> ShowS
show :: SimpleRepository -> String
$cshow :: SimpleRepository -> String
showsPrec :: Int -> SimpleRepository -> ShowS
$cshowsPrec :: Int -> SimpleRepository -> ShowS
Show, ReadPrec [SimpleRepository]
ReadPrec SimpleRepository
Int -> ReadS SimpleRepository
ReadS [SimpleRepository]
(Int -> ReadS SimpleRepository)
-> ReadS [SimpleRepository]
-> ReadPrec SimpleRepository
-> ReadPrec [SimpleRepository]
-> Read SimpleRepository
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SimpleRepository]
$creadListPrec :: ReadPrec [SimpleRepository]
readPrec :: ReadPrec SimpleRepository
$creadPrec :: ReadPrec SimpleRepository
readList :: ReadS [SimpleRepository]
$creadList :: ReadS [SimpleRepository]
readsPrec :: Int -> ReadS SimpleRepository
$creadsPrec :: Int -> ReadS SimpleRepository
Read)
instance FromJSON SimpleRepository where
parseJSON :: Value -> Parser SimpleRepository
parseJSON (Object Object
x) = Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository
SimpleRepository
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"archive_url"
Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
(Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser (Maybe Text)
-> Parser
(Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
(Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Bool
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Int
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
(Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
(Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
(RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser RepoOwner
-> Parser
(Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Bool
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Parser Text
-> Parser
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> SimpleRepository)
-> Parser Text
-> Parser
(Text -> Text -> Text -> Text -> Text -> Text -> SimpleRepository)
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 -> SimpleRepository)
-> Parser Text
-> Parser
(Text -> Text -> Text -> Text -> Text -> SimpleRepository)
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 -> SimpleRepository)
-> Parser Text
-> Parser (Text -> Text -> Text -> Text -> SimpleRepository)
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 -> SimpleRepository)
-> Parser Text -> Parser (Text -> Text -> Text -> SimpleRepository)
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 -> SimpleRepository)
-> Parser Text -> Parser (Text -> Text -> SimpleRepository)
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 -> SimpleRepository)
-> Parser Text -> Parser (Text -> SimpleRepository)
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 (Text -> SimpleRepository)
-> Parser Text -> Parser SimpleRepository
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
x Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"url"
parseJSON Value
_ = String -> Parser SimpleRepository
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"SimpleRepository"
instance ToJSON SimpleRepository where
toJSON :: SimpleRepository -> Value
toJSON SimpleRepository{Bool
Int
Maybe Text
Text
RepoOwner
simpleRepositoryUrl :: Text
simpleRepositoryTreesUrl :: Text
simpleRepositoryTeamsUrl :: Text
simpleRepositoryTagsUrl :: Text
simpleRepositorySubscriptionUrl :: Text
simpleRepositorySubscribersUrl :: Text
simpleRepositoryStatusesUrl :: Text
simpleRepositoryStargazersUrl :: Text
simpleRepositoryReleasesUrl :: Text
simpleRepositoryPullsUrl :: Text
simpleRepositoryPrivate :: Bool
simpleRepositoryOwner :: RepoOwner
simpleRepositoryNotificationsUrl :: Text
simpleRepositoryNodeId :: Text
simpleRepositoryName :: Text
simpleRepositoryMilestonesUrl :: Text
simpleRepositoryMergesUrl :: Text
simpleRepositoryLanguagesUrl :: Text
simpleRepositoryLabelsUrl :: Text
simpleRepositoryKeysUrl :: Text
simpleRepositoryIssuesUrl :: Text
simpleRepositoryIssueEventsUrl :: Text
simpleRepositoryIssueCommentUrl :: Text
simpleRepositoryId :: Int
simpleRepositoryHtmlUrl :: Text
simpleRepositoryHooksUrl :: Text
simpleRepositoryGitTagsUrl :: Text
simpleRepositoryGitRefsUrl :: Text
simpleRepositoryGitCommitsUrl :: Text
simpleRepositoryFullName :: Text
simpleRepositoryForksUrl :: Text
simpleRepositoryFork :: Bool
simpleRepositoryEventsUrl :: Text
simpleRepositoryDownloadsUrl :: Text
simpleRepositoryDescription :: Maybe Text
simpleRepositoryDeploymentsUrl :: Text
simpleRepositoryContributorsUrl :: Text
simpleRepositoryContentsUrl :: Text
simpleRepositoryCompareUrl :: Text
simpleRepositoryCommitsUrl :: Text
simpleRepositoryCommentsUrl :: Text
simpleRepositoryCollaboratorsUrl :: Text
simpleRepositoryBranchesUrl :: Text
simpleRepositoryBlobsUrl :: Text
simpleRepositoryAssigneesUrl :: Text
simpleRepositoryArchiveUrl :: Text
simpleRepositoryUrl :: SimpleRepository -> Text
simpleRepositoryTreesUrl :: SimpleRepository -> Text
simpleRepositoryTeamsUrl :: SimpleRepository -> Text
simpleRepositoryTagsUrl :: SimpleRepository -> Text
simpleRepositorySubscriptionUrl :: SimpleRepository -> Text
simpleRepositorySubscribersUrl :: SimpleRepository -> Text
simpleRepositoryStatusesUrl :: SimpleRepository -> Text
simpleRepositoryStargazersUrl :: SimpleRepository -> Text
simpleRepositoryReleasesUrl :: SimpleRepository -> Text
simpleRepositoryPullsUrl :: SimpleRepository -> Text
simpleRepositoryPrivate :: SimpleRepository -> Bool
simpleRepositoryOwner :: SimpleRepository -> RepoOwner
simpleRepositoryNotificationsUrl :: SimpleRepository -> Text
simpleRepositoryNodeId :: SimpleRepository -> Text
simpleRepositoryName :: SimpleRepository -> Text
simpleRepositoryMilestonesUrl :: SimpleRepository -> Text
simpleRepositoryMergesUrl :: SimpleRepository -> Text
simpleRepositoryLanguagesUrl :: SimpleRepository -> Text
simpleRepositoryLabelsUrl :: SimpleRepository -> Text
simpleRepositoryKeysUrl :: SimpleRepository -> Text
simpleRepositoryIssuesUrl :: SimpleRepository -> Text
simpleRepositoryIssueEventsUrl :: SimpleRepository -> Text
simpleRepositoryIssueCommentUrl :: SimpleRepository -> Text
simpleRepositoryId :: SimpleRepository -> Int
simpleRepositoryHtmlUrl :: SimpleRepository -> Text
simpleRepositoryHooksUrl :: SimpleRepository -> Text
simpleRepositoryGitTagsUrl :: SimpleRepository -> Text
simpleRepositoryGitRefsUrl :: SimpleRepository -> Text
simpleRepositoryGitCommitsUrl :: SimpleRepository -> Text
simpleRepositoryFullName :: SimpleRepository -> Text
simpleRepositoryForksUrl :: SimpleRepository -> Text
simpleRepositoryFork :: SimpleRepository -> Bool
simpleRepositoryEventsUrl :: SimpleRepository -> Text
simpleRepositoryDownloadsUrl :: SimpleRepository -> Text
simpleRepositoryDescription :: SimpleRepository -> Maybe Text
simpleRepositoryDeploymentsUrl :: SimpleRepository -> Text
simpleRepositoryContributorsUrl :: SimpleRepository -> Text
simpleRepositoryContentsUrl :: SimpleRepository -> Text
simpleRepositoryCompareUrl :: SimpleRepository -> Text
simpleRepositoryCommitsUrl :: SimpleRepository -> Text
simpleRepositoryCommentsUrl :: SimpleRepository -> Text
simpleRepositoryCollaboratorsUrl :: SimpleRepository -> Text
simpleRepositoryBranchesUrl :: SimpleRepository -> Text
simpleRepositoryBlobsUrl :: SimpleRepository -> Text
simpleRepositoryAssigneesUrl :: SimpleRepository -> Text
simpleRepositoryArchiveUrl :: SimpleRepository -> Text
..} = [Pair] -> Value
object
[ Key
"archive_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryArchiveUrl
, Key
"assignees_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryAssigneesUrl
, Key
"blobs_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryBlobsUrl
, Key
"branches_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryBranchesUrl
, Key
"collaborators_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryCollaboratorsUrl
, Key
"comments_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryCommentsUrl
, Key
"commits_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryCommitsUrl
, Key
"compare_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryCompareUrl
, Key
"contents_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryContentsUrl
, Key
"contributors_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryContributorsUrl
, Key
"deployments_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryDeploymentsUrl
, Key
"description" Key -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
simpleRepositoryDescription
, Key
"downloads_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryDownloadsUrl
, Key
"events_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryEventsUrl
, Key
"fork" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
simpleRepositoryFork
, Key
"forks_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryForksUrl
, Key
"full_name" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryFullName
, Key
"git_commits_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryGitCommitsUrl
, Key
"git_refs_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryGitRefsUrl
, Key
"git_tags_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryGitTagsUrl
, Key
"hooks_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryHooksUrl
, Key
"html_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryHtmlUrl
, Key
"id" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
simpleRepositoryId
, Key
"issue_comment_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryIssueCommentUrl
, Key
"issue_events_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryIssueEventsUrl
, Key
"issues_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryIssuesUrl
, Key
"keys_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryKeysUrl
, Key
"labels_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryLabelsUrl
, Key
"languages_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryLanguagesUrl
, Key
"merges_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryMergesUrl
, Key
"milestones_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryMilestonesUrl
, Key
"name" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryName
, Key
"node_id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryNodeId
, Key
"notifications_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryNotificationsUrl
, Key
"owner" Key -> RepoOwner -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= RepoOwner
simpleRepositoryOwner
, Key
"private" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
simpleRepositoryPrivate
, Key
"pulls_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryPullsUrl
, Key
"releases_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryReleasesUrl
, Key
"stargazers_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryStargazersUrl
, Key
"statuses_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryStatusesUrl
, Key
"subscribers_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositorySubscribersUrl
, Key
"subscription_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositorySubscriptionUrl
, Key
"tags_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryTagsUrl
, Key
"teams_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryTeamsUrl
, Key
"trees_url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryTreesUrl
, Key
"url" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
simpleRepositoryUrl
]
instance Arbitrary SimpleRepository where
arbitrary :: Gen SimpleRepository
arbitrary = Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository
SimpleRepository
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
forall (f :: * -> *) a b. Functor 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
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Maybe Text
-> Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen (Maybe Text)
-> Gen
(Text
-> Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Bool
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Int
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Int
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Text
-> RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Text
-> Gen
(RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen
(RepoOwner
-> Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen RepoOwner
-> Gen
(Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen RepoOwner
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Bool
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
-> Gen Bool
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> SimpleRepository)
-> Gen Text
-> Gen
(Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> SimpleRepository)
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
-> SimpleRepository)
-> Gen Text
-> Gen
(Text -> Text -> Text -> Text -> Text -> Text -> SimpleRepository)
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 -> SimpleRepository)
-> Gen Text
-> Gen (Text -> Text -> Text -> Text -> Text -> SimpleRepository)
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 -> SimpleRepository)
-> Gen Text
-> Gen (Text -> Text -> Text -> Text -> SimpleRepository)
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 -> SimpleRepository)
-> Gen Text -> Gen (Text -> Text -> Text -> SimpleRepository)
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 -> SimpleRepository)
-> Gen Text -> Gen (Text -> Text -> SimpleRepository)
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 -> SimpleRepository)
-> Gen Text -> Gen (Text -> SimpleRepository)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary
Gen (Text -> SimpleRepository) -> Gen Text -> Gen SimpleRepository
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Text
forall a. Arbitrary a => Gen a
arbitrary