github-0.19: Access to the GitHub API, v3.

LicenseBSD-3-Clause
MaintainerOleg Grenrus <oleg.grenrus@iki.fi>
Safe HaskellNone
LanguageHaskell2010

GitHub.Data.Repos

Description

This module also exports FromJSON a => FromJSON (HashMap Language a) orphan-ish instance for aeson < 1

Synopsis

Documentation

data Repo Source #

Instances

Eq Repo Source # 

Methods

(==) :: Repo -> Repo -> Bool #

(/=) :: Repo -> Repo -> Bool #

Data Repo Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Repo -> c Repo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Repo #

toConstr :: Repo -> Constr #

dataTypeOf :: Repo -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Repo) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Repo) #

gmapT :: (forall b. Data b => b -> b) -> Repo -> Repo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Repo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Repo -> r #

gmapQ :: (forall d. Data d => d -> u) -> Repo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Repo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Repo -> m Repo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Repo -> m Repo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Repo -> m Repo #

Ord Repo Source # 

Methods

compare :: Repo -> Repo -> Ordering #

(<) :: Repo -> Repo -> Bool #

(<=) :: Repo -> Repo -> Bool #

(>) :: Repo -> Repo -> Bool #

(>=) :: Repo -> Repo -> Bool #

max :: Repo -> Repo -> Repo #

min :: Repo -> Repo -> Repo #

Show Repo Source # 

Methods

showsPrec :: Int -> Repo -> ShowS #

show :: Repo -> String #

showList :: [Repo] -> ShowS #

Generic Repo Source # 

Associated Types

type Rep Repo :: * -> * #

Methods

from :: Repo -> Rep Repo x #

to :: Rep Repo x -> Repo #

FromJSON Repo Source # 
Binary Repo Source # 

Methods

put :: Repo -> Put #

get :: Get Repo #

putList :: [Repo] -> Put #

NFData Repo Source # 

Methods

rnf :: Repo -> () #

type Rep Repo Source # 
type Rep Repo = D1 * (MetaData "Repo" "GitHub.Data.Repos" "github-0.19-HK5gGFVL8du3RBT4q9vA87" False) (C1 * (MetaCons "Repo" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "repoSshUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe URL))) ((:*:) * (S1 * (MetaSel (Just Symbol "repoDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "repoCreatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe UTCTime))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "repoHtmlUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * URL)) (S1 * (MetaSel (Just Symbol "repoSvnUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe URL)))) ((:*:) * (S1 * (MetaSel (Just Symbol "repoForks") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "repoHomepage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "repoFork") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "repoGitUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe URL)))) ((:*:) * (S1 * (MetaSel (Just Symbol "repoPrivate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "repoArchived") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bool)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "repoCloneUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe URL))) (S1 * (MetaSel (Just Symbol "repoSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "repoUpdatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe UTCTime))) (S1 * (MetaSel (Just Symbol "repoWatchers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "repoOwner") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SimpleOwner)) ((:*:) * (S1 * (MetaSel (Just Symbol "repoName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Name Repo))) (S1 * (MetaSel (Just Symbol "repoLanguage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Language))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "repoDefaultBranch") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "repoPushedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe UTCTime)))) ((:*:) * (S1 * (MetaSel (Just Symbol "repoId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Id Repo))) (S1 * (MetaSel (Just Symbol "repoUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * URL))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "repoOpenIssues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "repoHasWiki") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "repoHasIssues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "repoHasDownloads") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "repoParent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe RepoRef))) (S1 * (MetaSel (Just Symbol "repoSource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe RepoRef)))) ((:*:) * (S1 * (MetaSel (Just Symbol "repoHooksUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * URL)) (S1 * (MetaSel (Just Symbol "repoStargazersCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int))))))))

data RepoRef Source #

Constructors

RepoRef 

Instances

Eq RepoRef Source # 

Methods

(==) :: RepoRef -> RepoRef -> Bool #

(/=) :: RepoRef -> RepoRef -> Bool #

Data RepoRef Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RepoRef -> c RepoRef #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RepoRef #

toConstr :: RepoRef -> Constr #

dataTypeOf :: RepoRef -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RepoRef) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoRef) #

gmapT :: (forall b. Data b => b -> b) -> RepoRef -> RepoRef #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RepoRef -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RepoRef -> r #

gmapQ :: (forall d. Data d => d -> u) -> RepoRef -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RepoRef -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RepoRef -> m RepoRef #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoRef -> m RepoRef #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoRef -> m RepoRef #

Ord RepoRef Source # 
Show RepoRef Source # 
Generic RepoRef Source # 

Associated Types

type Rep RepoRef :: * -> * #

Methods

from :: RepoRef -> Rep RepoRef x #

to :: Rep RepoRef x -> RepoRef #

FromJSON RepoRef Source # 
Binary RepoRef Source # 

Methods

put :: RepoRef -> Put #

get :: Get RepoRef #

putList :: [RepoRef] -> Put #

NFData RepoRef Source # 

Methods

rnf :: RepoRef -> () #

type Rep RepoRef Source # 
type Rep RepoRef = D1 * (MetaData "RepoRef" "GitHub.Data.Repos" "github-0.19-HK5gGFVL8du3RBT4q9vA87" False) (C1 * (MetaCons "RepoRef" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "repoRefOwner") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * SimpleOwner)) (S1 * (MetaSel (Just Symbol "repoRefRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Name Repo)))))

data NewRepo Source #

Instances

Eq NewRepo Source # 

Methods

(==) :: NewRepo -> NewRepo -> Bool #

(/=) :: NewRepo -> NewRepo -> Bool #

Data NewRepo Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NewRepo -> c NewRepo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NewRepo #

toConstr :: NewRepo -> Constr #

dataTypeOf :: NewRepo -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NewRepo) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewRepo) #

gmapT :: (forall b. Data b => b -> b) -> NewRepo -> NewRepo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NewRepo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NewRepo -> r #

gmapQ :: (forall d. Data d => d -> u) -> NewRepo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NewRepo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NewRepo -> m NewRepo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NewRepo -> m NewRepo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NewRepo -> m NewRepo #

Ord NewRepo Source # 
Show NewRepo Source # 
Generic NewRepo Source # 

Associated Types

type Rep NewRepo :: * -> * #

Methods

from :: NewRepo -> Rep NewRepo x #

to :: Rep NewRepo x -> NewRepo #

ToJSON NewRepo Source # 
Binary NewRepo Source # 

Methods

put :: NewRepo -> Put #

get :: Get NewRepo #

putList :: [NewRepo] -> Put #

NFData NewRepo Source # 

Methods

rnf :: NewRepo -> () #

type Rep NewRepo Source # 

data EditRepo Source #

Instances

Eq EditRepo Source # 
Data EditRepo Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EditRepo -> c EditRepo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EditRepo #

toConstr :: EditRepo -> Constr #

dataTypeOf :: EditRepo -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EditRepo) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EditRepo) #

gmapT :: (forall b. Data b => b -> b) -> EditRepo -> EditRepo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EditRepo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EditRepo -> r #

gmapQ :: (forall d. Data d => d -> u) -> EditRepo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EditRepo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EditRepo -> m EditRepo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EditRepo -> m EditRepo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EditRepo -> m EditRepo #

Ord EditRepo Source # 
Show EditRepo Source # 
Generic EditRepo Source # 

Associated Types

type Rep EditRepo :: * -> * #

Methods

from :: EditRepo -> Rep EditRepo x #

to :: Rep EditRepo x -> EditRepo #

ToJSON EditRepo Source # 
Binary EditRepo Source # 

Methods

put :: EditRepo -> Put #

get :: Get EditRepo #

putList :: [EditRepo] -> Put #

NFData EditRepo Source # 

Methods

rnf :: EditRepo -> () #

type Rep EditRepo Source # 

data RepoPublicity Source #

Filter the list of the user's repos using any of these constructors.

Constructors

RepoPublicityAll

All repos accessible to the user.

RepoPublicityOwner

Only repos owned by the user.

RepoPublicityPublic

Only public repos.

RepoPublicityPrivate

Only private repos.

RepoPublicityMember

Only repos to which the user is a member but not an owner.

Instances

Bounded RepoPublicity Source # 
Enum RepoPublicity Source # 
Eq RepoPublicity Source # 
Data RepoPublicity Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RepoPublicity -> c RepoPublicity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RepoPublicity #

toConstr :: RepoPublicity -> Constr #

dataTypeOf :: RepoPublicity -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RepoPublicity) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoPublicity) #

gmapT :: (forall b. Data b => b -> b) -> RepoPublicity -> RepoPublicity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RepoPublicity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RepoPublicity -> r #

gmapQ :: (forall d. Data d => d -> u) -> RepoPublicity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RepoPublicity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RepoPublicity -> m RepoPublicity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoPublicity -> m RepoPublicity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoPublicity -> m RepoPublicity #

Ord RepoPublicity Source # 
Show RepoPublicity Source # 
Generic RepoPublicity Source # 

Associated Types

type Rep RepoPublicity :: * -> * #

type Rep RepoPublicity Source # 
type Rep RepoPublicity = D1 * (MetaData "RepoPublicity" "GitHub.Data.Repos" "github-0.19-HK5gGFVL8du3RBT4q9vA87" False) ((:+:) * ((:+:) * (C1 * (MetaCons "RepoPublicityAll" PrefixI False) (U1 *)) (C1 * (MetaCons "RepoPublicityOwner" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "RepoPublicityPublic" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "RepoPublicityPrivate" PrefixI False) (U1 *)) (C1 * (MetaCons "RepoPublicityMember" PrefixI False) (U1 *)))))

type Languages = HashMap Language Int Source #

The value is the number of bytes of code written in that language.

newtype Language Source #

A programming language.

Constructors

Language Text 

Instances

Eq Language Source # 
Data Language Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Language -> c Language #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Language #

toConstr :: Language -> Constr #

dataTypeOf :: Language -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Language) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Language) #

gmapT :: (forall b. Data b => b -> b) -> Language -> Language #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Language -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Language -> r #

gmapQ :: (forall d. Data d => d -> u) -> Language -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Language -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Language -> m Language #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Language -> m Language #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Language -> m Language #

Ord Language Source # 
Show Language Source # 
IsString Language Source # 
Generic Language Source # 

Associated Types

type Rep Language :: * -> * #

Methods

from :: Language -> Rep Language x #

to :: Rep Language x -> Language #

Hashable Language Source # 

Methods

hashWithSalt :: Int -> Language -> Int #

hash :: Language -> Int #

ToJSON Language Source # 
FromJSON Language Source # 
FromJSONKey Language Source # 
Binary Language Source # 

Methods

put :: Language -> Put #

get :: Get Language #

putList :: [Language] -> Put #

NFData Language Source # 

Methods

rnf :: Language -> () #

type Rep Language Source # 
type Rep Language = D1 * (MetaData "Language" "GitHub.Data.Repos" "github-0.19-HK5gGFVL8du3RBT4q9vA87" True) (C1 * (MetaCons "Language" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

data Contributor Source #

Constructors

KnownContributor !Int !URL !(Name User) !URL !(Id User) !Text

An existing Github user, with their number of contributions, avatar URL, login, URL, ID, and Gravatar ID.

AnonymousContributor !Int !Text

An unknown Github user with their number of contributions and recorded name.

Instances

Eq Contributor Source # 
Data Contributor Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Contributor -> c Contributor #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Contributor #

toConstr :: Contributor -> Constr #

dataTypeOf :: Contributor -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Contributor) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Contributor) #

gmapT :: (forall b. Data b => b -> b) -> Contributor -> Contributor #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Contributor -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Contributor -> r #

gmapQ :: (forall d. Data d => d -> u) -> Contributor -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Contributor -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Contributor -> m Contributor #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Contributor -> m Contributor #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Contributor -> m Contributor #

Ord Contributor Source # 
Show Contributor Source # 
Generic Contributor Source # 

Associated Types

type Rep Contributor :: * -> * #

FromJSON Contributor Source # 
Binary Contributor Source # 
NFData Contributor Source # 

Methods

rnf :: Contributor -> () #

type Rep Contributor Source # 

data ArchiveFormat Source #

Constructors

ArchiveFormatTarball

".tar.gz" format

ArchiveFormatZipball

".zip" format

Instances

Bounded ArchiveFormat Source # 
Enum ArchiveFormat Source # 
Eq ArchiveFormat Source # 
Data ArchiveFormat Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArchiveFormat -> c ArchiveFormat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ArchiveFormat #

toConstr :: ArchiveFormat -> Constr #

dataTypeOf :: ArchiveFormat -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ArchiveFormat) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArchiveFormat) #

gmapT :: (forall b. Data b => b -> b) -> ArchiveFormat -> ArchiveFormat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArchiveFormat -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArchiveFormat -> r #

gmapQ :: (forall d. Data d => d -> u) -> ArchiveFormat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArchiveFormat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArchiveFormat -> m ArchiveFormat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArchiveFormat -> m ArchiveFormat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArchiveFormat -> m ArchiveFormat #

Ord ArchiveFormat Source # 
Show ArchiveFormat Source # 
Generic ArchiveFormat Source # 

Associated Types

type Rep ArchiveFormat :: * -> * #

IsPathPart ArchiveFormat Source # 
type Rep ArchiveFormat Source # 
type Rep ArchiveFormat = D1 * (MetaData "ArchiveFormat" "GitHub.Data.Repos" "github-0.19-HK5gGFVL8du3RBT4q9vA87" False) ((:+:) * (C1 * (MetaCons "ArchiveFormatTarball" PrefixI False) (U1 *)) (C1 * (MetaCons "ArchiveFormatZipball" PrefixI False) (U1 *)))