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

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

GitHub.Data.Content

Description

 

Synopsis

Documentation

data Content Source #

Instances

Eq Content Source # 

Methods

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

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

Data Content Source # 

Methods

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

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

toConstr :: Content -> Constr #

dataTypeOf :: Content -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Content Source # 
Show Content Source # 
Generic Content Source # 

Associated Types

type Rep Content :: * -> * #

Methods

from :: Content -> Rep Content x #

to :: Rep Content x -> Content #

FromJSON Content Source # 
Binary Content Source # 

Methods

put :: Content -> Put #

get :: Get Content #

putList :: [Content] -> Put #

NFData Content Source # 

Methods

rnf :: Content -> () #

type Rep Content Source # 
type Rep Content = D1 * (MetaData "Content" "GitHub.Data.Content" "github-0.19-HK5gGFVL8du3RBT4q9vA87" False) ((:+:) * (C1 * (MetaCons "ContentFile" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ContentFileData))) (C1 * (MetaCons "ContentDirectory" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Vector ContentItem)))))

data ContentFileData Source #

Instances

Eq ContentFileData Source # 
Data ContentFileData Source # 

Methods

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

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

toConstr :: ContentFileData -> Constr #

dataTypeOf :: ContentFileData -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ContentFileData Source # 
Show ContentFileData Source # 
Generic ContentFileData Source # 
FromJSON ContentFileData Source # 
Binary ContentFileData Source # 
NFData ContentFileData Source # 

Methods

rnf :: ContentFileData -> () #

type Rep ContentFileData Source # 
type Rep ContentFileData = D1 * (MetaData "ContentFileData" "GitHub.Data.Content" "github-0.19-HK5gGFVL8du3RBT4q9vA87" False) (C1 * (MetaCons "ContentFileData" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "contentFileInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ContentInfo)) (S1 * (MetaSel (Just Symbol "contentFileEncoding") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "contentFileSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "contentFileContent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))

data ContentItem Source #

An item in a directory listing.

Instances

Eq ContentItem Source # 
Data ContentItem Source # 

Methods

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

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

toConstr :: ContentItem -> Constr #

dataTypeOf :: ContentItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ContentItem Source # 
Show ContentItem Source # 
Generic ContentItem Source # 

Associated Types

type Rep ContentItem :: * -> * #

FromJSON ContentItem Source # 
Binary ContentItem Source # 
NFData ContentItem Source # 

Methods

rnf :: ContentItem -> () #

type Rep ContentItem Source # 
type Rep ContentItem = D1 * (MetaData "ContentItem" "GitHub.Data.Content" "github-0.19-HK5gGFVL8du3RBT4q9vA87" False) (C1 * (MetaCons "ContentItem" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "contentItemType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ContentItemType)) (S1 * (MetaSel (Just Symbol "contentItemInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ContentInfo))))

data ContentItemType Source #

Constructors

ItemFile 
ItemDir 

Instances

Eq ContentItemType Source # 
Data ContentItemType Source # 

Methods

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

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

toConstr :: ContentItemType -> Constr #

dataTypeOf :: ContentItemType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ContentItemType Source # 
Show ContentItemType Source # 
Generic ContentItemType Source # 
FromJSON ContentItemType Source # 
Binary ContentItemType Source # 
NFData ContentItemType Source # 

Methods

rnf :: ContentItemType -> () #

type Rep ContentItemType Source # 
type Rep ContentItemType = D1 * (MetaData "ContentItemType" "GitHub.Data.Content" "github-0.19-HK5gGFVL8du3RBT4q9vA87" False) ((:+:) * (C1 * (MetaCons "ItemFile" PrefixI False) (U1 *)) (C1 * (MetaCons "ItemDir" PrefixI False) (U1 *)))

data ContentInfo Source #

Information common to both kinds of Content: files and directories.

Instances

Eq ContentInfo Source # 
Data ContentInfo Source # 

Methods

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

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

toConstr :: ContentInfo -> Constr #

dataTypeOf :: ContentInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ContentInfo Source # 
Show ContentInfo Source # 
Generic ContentInfo Source # 

Associated Types

type Rep ContentInfo :: * -> * #

FromJSON ContentInfo Source # 
Binary ContentInfo Source # 
NFData ContentInfo Source # 

Methods

rnf :: ContentInfo -> () #

type Rep ContentInfo Source # 

data ContentResultInfo Source #

Instances

Eq ContentResultInfo Source # 
Data ContentResultInfo Source # 

Methods

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

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

toConstr :: ContentResultInfo -> Constr #

dataTypeOf :: ContentResultInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ContentResultInfo Source # 
Show ContentResultInfo Source # 
Generic ContentResultInfo Source # 
FromJSON ContentResultInfo Source # 
Binary ContentResultInfo Source # 
NFData ContentResultInfo Source # 

Methods

rnf :: ContentResultInfo -> () #

type Rep ContentResultInfo Source # 
type Rep ContentResultInfo = D1 * (MetaData "ContentResultInfo" "GitHub.Data.Content" "github-0.19-HK5gGFVL8du3RBT4q9vA87" False) (C1 * (MetaCons "ContentResultInfo" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "contentResultInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ContentInfo)) (S1 * (MetaSel (Just Symbol "contentResultSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int))))

data ContentResult Source #

Instances

Eq ContentResult Source # 
Data ContentResult Source # 

Methods

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

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

toConstr :: ContentResult -> Constr #

dataTypeOf :: ContentResult -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ContentResult Source # 
Show ContentResult Source # 
Generic ContentResult Source # 

Associated Types

type Rep ContentResult :: * -> * #

FromJSON ContentResult Source # 
Binary ContentResult Source # 
NFData ContentResult Source # 

Methods

rnf :: ContentResult -> () #

type Rep ContentResult Source # 
type Rep ContentResult = D1 * (MetaData "ContentResult" "GitHub.Data.Content" "github-0.19-HK5gGFVL8du3RBT4q9vA87" False) (C1 * (MetaCons "ContentResult" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "contentResultContent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ContentResultInfo)) (S1 * (MetaSel (Just Symbol "contentResultCommit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * GitCommit))))

data Author Source #

Constructors

Author 

Fields

Instances

Eq Author Source # 

Methods

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

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

Data Author Source # 

Methods

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

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

toConstr :: Author -> Constr #

dataTypeOf :: Author -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Author Source # 
Show Author Source # 
Generic Author Source # 

Associated Types

type Rep Author :: * -> * #

Methods

from :: Author -> Rep Author x #

to :: Rep Author x -> Author #

ToJSON Author Source # 
Binary Author Source # 

Methods

put :: Author -> Put #

get :: Get Author #

putList :: [Author] -> Put #

NFData Author Source # 

Methods

rnf :: Author -> () #

type Rep Author Source # 
type Rep Author = D1 * (MetaData "Author" "GitHub.Data.Content" "github-0.19-HK5gGFVL8du3RBT4q9vA87" False) (C1 * (MetaCons "Author" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "authorName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "authorEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))

data CreateFile Source #

Instances

Eq CreateFile Source # 
Data CreateFile Source # 

Methods

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

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

toConstr :: CreateFile -> Constr #

dataTypeOf :: CreateFile -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CreateFile Source # 
Show CreateFile Source # 
Generic CreateFile Source # 

Associated Types

type Rep CreateFile :: * -> * #

ToJSON CreateFile Source # 
Binary CreateFile Source # 
NFData CreateFile Source # 

Methods

rnf :: CreateFile -> () #

type Rep CreateFile Source # 
type Rep CreateFile = D1 * (MetaData "CreateFile" "GitHub.Data.Content" "github-0.19-HK5gGFVL8du3RBT4q9vA87" False) (C1 * (MetaCons "CreateFile" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "createFilePath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "createFileMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "createFileContent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "createFileBranch") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "createFileAuthor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Author))) (S1 * (MetaSel (Just Symbol "createFileCommitter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Author)))))))

data UpdateFile Source #

Instances

Eq UpdateFile Source # 
Data UpdateFile Source # 

Methods

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

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

toConstr :: UpdateFile -> Constr #

dataTypeOf :: UpdateFile -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord UpdateFile Source # 
Show UpdateFile Source # 
Generic UpdateFile Source # 

Associated Types

type Rep UpdateFile :: * -> * #

ToJSON UpdateFile Source # 
Binary UpdateFile Source # 
NFData UpdateFile Source # 

Methods

rnf :: UpdateFile -> () #

type Rep UpdateFile Source # 

data DeleteFile Source #

Instances

Eq DeleteFile Source # 
Data DeleteFile Source # 

Methods

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

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

toConstr :: DeleteFile -> Constr #

dataTypeOf :: DeleteFile -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DeleteFile Source # 
Show DeleteFile Source # 
Generic DeleteFile Source # 

Associated Types

type Rep DeleteFile :: * -> * #

ToJSON DeleteFile Source # 
Binary DeleteFile Source # 
NFData DeleteFile Source # 

Methods

rnf :: DeleteFile -> () #

type Rep DeleteFile Source # 
type Rep DeleteFile = D1 * (MetaData "DeleteFile" "GitHub.Data.Content" "github-0.19-HK5gGFVL8du3RBT4q9vA87" False) (C1 * (MetaCons "DeleteFile" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "deleteFilePath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "deleteFileMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "deleteFileSHA") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "deleteFileBranch") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "deleteFileAuthor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Author))) (S1 * (MetaSel (Just Symbol "deleteFileCommitter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Author)))))))

(.=?) :: ToJSON v => Text -> Maybe v -> [Pair] Source #