github-data-0.18: Access to the GitHub API, v3.

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

GitHub.Data.GitData

Description

 

Synopsis

Documentation

data CommitQueryOption Source #

The options for querying commits.

Instances

Eq CommitQueryOption Source # 
Data CommitQueryOption Source # 

Methods

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

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

toConstr :: CommitQueryOption -> Constr #

dataTypeOf :: CommitQueryOption -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CommitQueryOption Source # 
Show CommitQueryOption Source # 
Generic CommitQueryOption Source # 
type Rep CommitQueryOption Source # 

data Stats Source #

Constructors

Stats 

Instances

Eq Stats Source # 

Methods

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

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

Data Stats Source # 

Methods

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

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

toConstr :: Stats -> Constr #

dataTypeOf :: Stats -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Stats Source # 

Methods

compare :: Stats -> Stats -> Ordering #

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

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

(>) :: Stats -> Stats -> Bool #

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

max :: Stats -> Stats -> Stats #

min :: Stats -> Stats -> Stats #

Show Stats Source # 

Methods

showsPrec :: Int -> Stats -> ShowS #

show :: Stats -> String #

showList :: [Stats] -> ShowS #

Generic Stats Source # 

Associated Types

type Rep Stats :: * -> * #

Methods

from :: Stats -> Rep Stats x #

to :: Rep Stats x -> Stats #

FromJSON Stats Source # 
Binary Stats Source # 

Methods

put :: Stats -> Put #

get :: Get Stats #

putList :: [Stats] -> Put #

NFData Stats Source # 

Methods

rnf :: Stats -> () #

type Rep Stats Source # 
type Rep Stats = D1 * (MetaData "Stats" "GitHub.Data.GitData" "github-data-0.18-CynTG9yKCcTHjYnDvzAzWG" False) (C1 * (MetaCons "Stats" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "statsAdditions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "statsTotal") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "statsDeletions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)))))

data Commit Source #

Instances

Eq Commit Source # 

Methods

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

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

Data Commit Source # 

Methods

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

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

toConstr :: Commit -> Constr #

dataTypeOf :: Commit -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Commit Source # 
Show Commit Source # 
Generic Commit Source # 

Associated Types

type Rep Commit :: * -> * #

Methods

from :: Commit -> Rep Commit x #

to :: Rep Commit x -> Commit #

FromJSON Commit Source # 
Binary Commit Source # 

Methods

put :: Commit -> Put #

get :: Get Commit #

putList :: [Commit] -> Put #

NFData Commit Source # 

Methods

rnf :: Commit -> () #

type Rep Commit Source # 

data Tree Source #

Constructors

Tree 

Instances

Eq Tree Source # 

Methods

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

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

Data Tree Source # 

Methods

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

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

toConstr :: Tree -> Constr #

dataTypeOf :: Tree -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Tree Source # 

Methods

compare :: Tree -> Tree -> Ordering #

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

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

(>) :: Tree -> Tree -> Bool #

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

max :: Tree -> Tree -> Tree #

min :: Tree -> Tree -> Tree #

Show Tree Source # 

Methods

showsPrec :: Int -> Tree -> ShowS #

show :: Tree -> String #

showList :: [Tree] -> ShowS #

Generic Tree Source # 

Associated Types

type Rep Tree :: * -> * #

Methods

from :: Tree -> Rep Tree x #

to :: Rep Tree x -> Tree #

FromJSON Tree Source # 
Binary Tree Source # 

Methods

put :: Tree -> Put #

get :: Get Tree #

putList :: [Tree] -> Put #

NFData Tree Source # 

Methods

rnf :: Tree -> () #

type Rep Tree Source # 
type Rep Tree = D1 * (MetaData "Tree" "GitHub.Data.GitData" "github-data-0.18-CynTG9yKCcTHjYnDvzAzWG" False) (C1 * (MetaCons "Tree" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "treeSha") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Name Tree))) ((:*:) * (S1 * (MetaSel (Just Symbol "treeUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * URL)) (S1 * (MetaSel (Just Symbol "treeGitTrees") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Vector GitTree))))))

data GitTree Source #

Instances

Eq GitTree Source # 

Methods

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

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

Data GitTree Source # 

Methods

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

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

toConstr :: GitTree -> Constr #

dataTypeOf :: GitTree -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord GitTree Source # 
Show GitTree Source # 
Generic GitTree Source # 

Associated Types

type Rep GitTree :: * -> * #

Methods

from :: GitTree -> Rep GitTree x #

to :: Rep GitTree x -> GitTree #

FromJSON GitTree Source # 
Binary GitTree Source # 

Methods

put :: GitTree -> Put #

get :: Get GitTree #

putList :: [GitTree] -> Put #

NFData GitTree Source # 

Methods

rnf :: GitTree -> () #

type Rep GitTree Source # 

data GitCommit Source #

Instances

Eq GitCommit Source # 
Data GitCommit Source # 

Methods

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

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

toConstr :: GitCommit -> Constr #

dataTypeOf :: GitCommit -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord GitCommit Source # 
Show GitCommit Source # 
Generic GitCommit Source # 

Associated Types

type Rep GitCommit :: * -> * #

FromJSON GitCommit Source # 
Binary GitCommit Source # 
NFData GitCommit Source # 

Methods

rnf :: GitCommit -> () #

type Rep GitCommit Source # 

data Blob Source #

Constructors

Blob 

Instances

Eq Blob Source # 

Methods

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

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

Data Blob Source # 

Methods

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

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

toConstr :: Blob -> Constr #

dataTypeOf :: Blob -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Blob Source # 

Methods

compare :: Blob -> Blob -> Ordering #

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

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

(>) :: Blob -> Blob -> Bool #

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

max :: Blob -> Blob -> Blob #

min :: Blob -> Blob -> Blob #

Show Blob Source # 

Methods

showsPrec :: Int -> Blob -> ShowS #

show :: Blob -> String #

showList :: [Blob] -> ShowS #

Generic Blob Source # 

Associated Types

type Rep Blob :: * -> * #

Methods

from :: Blob -> Rep Blob x #

to :: Rep Blob x -> Blob #

FromJSON Blob Source # 
Binary Blob Source # 

Methods

put :: Blob -> Put #

get :: Get Blob #

putList :: [Blob] -> Put #

NFData Blob Source # 

Methods

rnf :: Blob -> () #

type Rep Blob Source # 

data Tag Source #

Constructors

Tag 

Instances

Eq Tag Source # 

Methods

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

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

Data Tag Source # 

Methods

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

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

toConstr :: Tag -> Constr #

dataTypeOf :: Tag -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Tag Source # 

Methods

compare :: Tag -> Tag -> Ordering #

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

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

(>) :: Tag -> Tag -> Bool #

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

max :: Tag -> Tag -> Tag #

min :: Tag -> Tag -> Tag #

Show Tag Source # 

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag Source # 

Associated Types

type Rep Tag :: * -> * #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

FromJSON Tag Source # 
Binary Tag Source # 

Methods

put :: Tag -> Put #

get :: Get Tag #

putList :: [Tag] -> Put #

NFData Tag Source # 

Methods

rnf :: Tag -> () #

type Rep Tag Source # 

data Branch Source #

Constructors

Branch 

Instances

Eq Branch Source # 

Methods

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

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

Data Branch Source # 

Methods

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

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

toConstr :: Branch -> Constr #

dataTypeOf :: Branch -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Branch Source # 
Show Branch Source # 
Generic Branch Source # 

Associated Types

type Rep Branch :: * -> * #

Methods

from :: Branch -> Rep Branch x #

to :: Rep Branch x -> Branch #

FromJSON Branch Source # 
NFData Branch Source # 

Methods

rnf :: Branch -> () #

type Rep Branch Source # 
type Rep Branch = D1 * (MetaData "Branch" "GitHub.Data.GitData" "github-data-0.18-CynTG9yKCcTHjYnDvzAzWG" False) (C1 * (MetaCons "Branch" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "branchName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "branchCommit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * BranchCommit))))

data BranchCommit Source #

Constructors

BranchCommit 

Instances

Eq BranchCommit Source # 
Data BranchCommit Source # 

Methods

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

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

toConstr :: BranchCommit -> Constr #

dataTypeOf :: BranchCommit -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BranchCommit Source # 
Show BranchCommit Source # 
Generic BranchCommit Source # 

Associated Types

type Rep BranchCommit :: * -> * #

FromJSON BranchCommit Source # 
Binary BranchCommit Source # 
NFData BranchCommit Source # 

Methods

rnf :: BranchCommit -> () #

type Rep BranchCommit Source # 
type Rep BranchCommit = D1 * (MetaData "BranchCommit" "GitHub.Data.GitData" "github-data-0.18-CynTG9yKCcTHjYnDvzAzWG" False) (C1 * (MetaCons "BranchCommit" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "branchCommitSha") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "branchCommitUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * URL))))

data Diff Source #

Instances

Eq Diff Source # 

Methods

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

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

Data Diff Source # 

Methods

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

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

toConstr :: Diff -> Constr #

dataTypeOf :: Diff -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Diff Source # 

Methods

compare :: Diff -> Diff -> Ordering #

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

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

(>) :: Diff -> Diff -> Bool #

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

max :: Diff -> Diff -> Diff #

min :: Diff -> Diff -> Diff #

Show Diff Source # 

Methods

showsPrec :: Int -> Diff -> ShowS #

show :: Diff -> String #

showList :: [Diff] -> ShowS #

Generic Diff Source # 

Associated Types

type Rep Diff :: * -> * #

Methods

from :: Diff -> Rep Diff x #

to :: Rep Diff x -> Diff #

FromJSON Diff Source # 
Binary Diff Source # 

Methods

put :: Diff -> Put #

get :: Get Diff #

putList :: [Diff] -> Put #

NFData Diff Source # 

Methods

rnf :: Diff -> () #

type Rep Diff Source # 
type Rep Diff = D1 * (MetaData "Diff" "GitHub.Data.GitData" "github-data-0.18-CynTG9yKCcTHjYnDvzAzWG" False) (C1 * (MetaCons "Diff" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "diffStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "diffBehindBy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "diffPatchUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * URL)))) ((:*:) * (S1 * (MetaSel (Just Symbol "diffUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * URL)) ((:*:) * (S1 * (MetaSel (Just Symbol "diffBaseCommit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Commit)) (S1 * (MetaSel (Just Symbol "diffCommits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Vector Commit)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "diffTotalCommits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "diffHtmlUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * URL)) (S1 * (MetaSel (Just Symbol "diffFiles") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Vector File))))) ((:*:) * (S1 * (MetaSel (Just Symbol "diffAheadBy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "diffDiffUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * URL)) (S1 * (MetaSel (Just Symbol "diffPermalinkUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * URL)))))))

data NewGitReference Source #

Instances

Eq NewGitReference Source # 
Data NewGitReference Source # 

Methods

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

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

toConstr :: NewGitReference -> Constr #

dataTypeOf :: NewGitReference -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NewGitReference Source # 
Show NewGitReference Source # 
Generic NewGitReference Source # 
ToJSON NewGitReference Source # 
Binary NewGitReference Source # 
NFData NewGitReference Source # 

Methods

rnf :: NewGitReference -> () #

type Rep NewGitReference Source # 
type Rep NewGitReference = D1 * (MetaData "NewGitReference" "GitHub.Data.GitData" "github-data-0.18-CynTG9yKCcTHjYnDvzAzWG" False) (C1 * (MetaCons "NewGitReference" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "newGitReferenceRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "newGitReferenceSha") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))

data GitReference Source #

Instances

Eq GitReference Source # 
Data GitReference Source # 

Methods

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

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

toConstr :: GitReference -> Constr #

dataTypeOf :: GitReference -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord GitReference Source # 
Show GitReference Source # 
Generic GitReference Source # 

Associated Types

type Rep GitReference :: * -> * #

FromJSON GitReference Source # 
Binary GitReference Source # 
NFData GitReference Source # 

Methods

rnf :: GitReference -> () #

type Rep GitReference Source # 
type Rep GitReference = D1 * (MetaData "GitReference" "GitHub.Data.GitData" "github-data-0.18-CynTG9yKCcTHjYnDvzAzWG" False) (C1 * (MetaCons "GitReference" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "gitReferenceObject") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * GitObject)) ((:*:) * (S1 * (MetaSel (Just Symbol "gitReferenceUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * URL)) (S1 * (MetaSel (Just Symbol "gitReferenceRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))

data GitObject Source #

Constructors

GitObject 

Instances

Eq GitObject Source # 
Data GitObject Source # 

Methods

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

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

toConstr :: GitObject -> Constr #

dataTypeOf :: GitObject -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord GitObject Source # 
Show GitObject Source # 
Generic GitObject Source # 

Associated Types

type Rep GitObject :: * -> * #

FromJSON GitObject Source # 
Binary GitObject Source # 
NFData GitObject Source # 

Methods

rnf :: GitObject -> () #

type Rep GitObject Source # 
type Rep GitObject = D1 * (MetaData "GitObject" "GitHub.Data.GitData" "github-data-0.18-CynTG9yKCcTHjYnDvzAzWG" False) (C1 * (MetaCons "GitObject" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "gitObjectType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "gitObjectSha") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "gitObjectUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * URL)))))

data GitUser Source #

Constructors

GitUser 

Instances

Eq GitUser Source # 

Methods

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

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

Data GitUser Source # 

Methods

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

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

toConstr :: GitUser -> Constr #

dataTypeOf :: GitUser -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord GitUser Source # 
Show GitUser Source # 
Generic GitUser Source # 

Associated Types

type Rep GitUser :: * -> * #

Methods

from :: GitUser -> Rep GitUser x #

to :: Rep GitUser x -> GitUser #

FromJSON GitUser Source # 
Binary GitUser Source # 

Methods

put :: GitUser -> Put #

get :: Get GitUser #

putList :: [GitUser] -> Put #

NFData GitUser Source # 

Methods

rnf :: GitUser -> () #

type Rep GitUser Source # 
type Rep GitUser = D1 * (MetaData "GitUser" "GitHub.Data.GitData" "github-data-0.18-CynTG9yKCcTHjYnDvzAzWG" False) (C1 * (MetaCons "GitUser" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "gitUserName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "gitUserEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "gitUserDate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * UTCTime)))))

data File Source #

Instances

Eq File Source # 

Methods

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

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

Data File Source # 

Methods

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

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

toConstr :: File -> Constr #

dataTypeOf :: File -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord File Source # 

Methods

compare :: File -> File -> Ordering #

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

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

(>) :: File -> File -> Bool #

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

max :: File -> File -> File #

min :: File -> File -> File #

Show File Source # 

Methods

showsPrec :: Int -> File -> ShowS #

show :: File -> String #

showList :: [File] -> ShowS #

Generic File Source # 

Associated Types

type Rep File :: * -> * #

Methods

from :: File -> Rep File x #

to :: Rep File x -> File #

FromJSON File Source # 
Binary File Source # 

Methods

put :: File -> Put #

get :: Get File #

putList :: [File] -> Put #

NFData File Source # 

Methods

rnf :: File -> () #

type Rep File Source #