Safe Haskell | None |
---|---|
Language | Haskell2010 |
GitHub.Data.Content
Synopsis
- data Content
- data ContentFileData = ContentFileData {}
- data ContentItem = ContentItem {}
- data ContentItemType
- data ContentInfo = ContentInfo {
- contentName :: !Text
- contentPath :: !Text
- contentSha :: !Text
- contentUrl :: !URL
- contentGitUrl :: !URL
- contentHtmlUrl :: !URL
- data ContentResultInfo = ContentResultInfo {}
- data ContentResult = ContentResult {}
- data Author = Author {
- authorName :: !Text
- authorEmail :: !Text
- data CreateFile = CreateFile {
- createFilePath :: !Text
- createFileMessage :: !Text
- createFileContent :: !Text
- createFileBranch :: !(Maybe Text)
- createFileAuthor :: !(Maybe Author)
- createFileCommitter :: !(Maybe Author)
- data UpdateFile = UpdateFile {
- updateFilePath :: !Text
- updateFileMessage :: !Text
- updateFileContent :: !Text
- updateFileSHA :: !Text
- updateFileBranch :: !(Maybe Text)
- updateFileAuthor :: !(Maybe Author)
- updateFileCommitter :: !(Maybe Author)
- data DeleteFile = DeleteFile {
- deleteFilePath :: !Text
- deleteFileMessage :: !Text
- deleteFileSHA :: !Text
- deleteFileBranch :: !(Maybe Text)
- deleteFileAuthor :: !(Maybe Author)
- deleteFileCommitter :: !(Maybe Author)
- (.=?) :: ToJSON v => Key -> Maybe v -> [Pair]
Documentation
Constructors
ContentFile !ContentFileData | |
ContentDirectory !(Vector ContentItem) |
Instances
FromJSON Content Source # | |||||
Defined in GitHub.Data.Content | |||||
Data Content Source # | |||||
Defined in GitHub.Data.Content 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 :: forall r r'. (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 # | |||||
Generic Content Source # | |||||
Defined in GitHub.Data.Content Associated Types
| |||||
Show Content Source # | |||||
Binary Content Source # | |||||
NFData Content Source # | |||||
Defined in GitHub.Data.Content | |||||
Eq Content Source # | |||||
Ord Content Source # | |||||
type Rep Content Source # | |||||
Defined in GitHub.Data.Content type Rep Content = D1 ('MetaData "Content" "GitHub.Data.Content" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" 'False) (C1 ('MetaCons "ContentFile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ContentFileData)) :+: C1 ('MetaCons "ContentDirectory" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Vector ContentItem)))) |
data ContentFileData Source #
Constructors
ContentFileData | |
Fields
|
Instances
data ContentItem Source #
An item in a directory listing.
Constructors
ContentItem | |
Fields |
Instances
FromJSON ContentItem Source # | |||||
Defined in GitHub.Data.Content | |||||
Data ContentItem Source # | |||||
Defined in GitHub.Data.Content 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 :: forall r r'. (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 # | |||||
Generic ContentItem Source # | |||||
Defined in GitHub.Data.Content Associated Types
| |||||
Show ContentItem Source # | |||||
Defined in GitHub.Data.Content Methods showsPrec :: Int -> ContentItem -> ShowS # show :: ContentItem -> String # showList :: [ContentItem] -> ShowS # | |||||
Binary ContentItem Source # | |||||
Defined in GitHub.Data.Content | |||||
NFData ContentItem Source # | |||||
Defined in GitHub.Data.Content Methods rnf :: ContentItem -> () # | |||||
Eq ContentItem Source # | |||||
Defined in GitHub.Data.Content | |||||
Ord ContentItem Source # | |||||
Defined in GitHub.Data.Content Methods compare :: ContentItem -> ContentItem -> Ordering # (<) :: ContentItem -> ContentItem -> Bool # (<=) :: ContentItem -> ContentItem -> Bool # (>) :: ContentItem -> ContentItem -> Bool # (>=) :: ContentItem -> ContentItem -> Bool # max :: ContentItem -> ContentItem -> ContentItem # min :: ContentItem -> ContentItem -> ContentItem # | |||||
type Rep ContentItem Source # | |||||
Defined in GitHub.Data.Content type Rep ContentItem = D1 ('MetaData "ContentItem" "GitHub.Data.Content" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" 'False) (C1 ('MetaCons "ContentItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "contentItemType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ContentItemType) :*: S1 ('MetaSel ('Just "contentItemInfo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ContentInfo))) |
data ContentItemType Source #
Instances
FromJSON ContentItemType Source # | |||||
Defined in GitHub.Data.Content Methods parseJSON :: Value -> Parser ContentItemType # parseJSONList :: Value -> Parser [ContentItemType] # | |||||
Data ContentItemType Source # | |||||
Defined in GitHub.Data.Content 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 :: forall r r'. (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 # | |||||
Generic ContentItemType Source # | |||||
Defined in GitHub.Data.Content Associated Types
Methods from :: ContentItemType -> Rep ContentItemType x # to :: Rep ContentItemType x -> ContentItemType # | |||||
Show ContentItemType Source # | |||||
Defined in GitHub.Data.Content Methods showsPrec :: Int -> ContentItemType -> ShowS # show :: ContentItemType -> String # showList :: [ContentItemType] -> ShowS # | |||||
Binary ContentItemType Source # | |||||
Defined in GitHub.Data.Content Methods put :: ContentItemType -> Put # get :: Get ContentItemType # putList :: [ContentItemType] -> Put # | |||||
NFData ContentItemType Source # | |||||
Defined in GitHub.Data.Content Methods rnf :: ContentItemType -> () # | |||||
Eq ContentItemType Source # | |||||
Defined in GitHub.Data.Content Methods (==) :: ContentItemType -> ContentItemType -> Bool # (/=) :: ContentItemType -> ContentItemType -> Bool # | |||||
Ord ContentItemType Source # | |||||
Defined in GitHub.Data.Content Methods compare :: ContentItemType -> ContentItemType -> Ordering # (<) :: ContentItemType -> ContentItemType -> Bool # (<=) :: ContentItemType -> ContentItemType -> Bool # (>) :: ContentItemType -> ContentItemType -> Bool # (>=) :: ContentItemType -> ContentItemType -> Bool # max :: ContentItemType -> ContentItemType -> ContentItemType # min :: ContentItemType -> ContentItemType -> ContentItemType # | |||||
type Rep ContentItemType Source # | |||||
data ContentInfo Source #
Information common to both kinds of Content: files and directories.
Constructors
ContentInfo | |
Fields
|
Instances
FromJSON ContentInfo Source # | |||||
Defined in GitHub.Data.Content | |||||
Data ContentInfo Source # | |||||
Defined in GitHub.Data.Content 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 :: forall r r'. (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 # | |||||
Generic ContentInfo Source # | |||||
Defined in GitHub.Data.Content Associated Types
| |||||
Show ContentInfo Source # | |||||
Defined in GitHub.Data.Content Methods showsPrec :: Int -> ContentInfo -> ShowS # show :: ContentInfo -> String # showList :: [ContentInfo] -> ShowS # | |||||
Binary ContentInfo Source # | |||||
Defined in GitHub.Data.Content | |||||
NFData ContentInfo Source # | |||||
Defined in GitHub.Data.Content Methods rnf :: ContentInfo -> () # | |||||
Eq ContentInfo Source # | |||||
Defined in GitHub.Data.Content | |||||
Ord ContentInfo Source # | |||||
Defined in GitHub.Data.Content Methods compare :: ContentInfo -> ContentInfo -> Ordering # (<) :: ContentInfo -> ContentInfo -> Bool # (<=) :: ContentInfo -> ContentInfo -> Bool # (>) :: ContentInfo -> ContentInfo -> Bool # (>=) :: ContentInfo -> ContentInfo -> Bool # max :: ContentInfo -> ContentInfo -> ContentInfo # min :: ContentInfo -> ContentInfo -> ContentInfo # | |||||
type Rep ContentInfo Source # | |||||
Defined in GitHub.Data.Content type Rep ContentInfo = D1 ('MetaData "ContentInfo" "GitHub.Data.Content" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" 'False) (C1 ('MetaCons "ContentInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "contentName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "contentPath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "contentSha") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) :*: (S1 ('MetaSel ('Just "contentUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: (S1 ('MetaSel ('Just "contentGitUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "contentHtmlUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))))) |
data ContentResultInfo Source #
Constructors
ContentResultInfo | |
Fields |
Instances
FromJSON ContentResultInfo Source # | |||||
Defined in GitHub.Data.Content Methods parseJSON :: Value -> Parser ContentResultInfo # parseJSONList :: Value -> Parser [ContentResultInfo] # | |||||
Data ContentResultInfo Source # | |||||
Defined in GitHub.Data.Content 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 :: forall r r'. (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 # | |||||
Generic ContentResultInfo Source # | |||||
Defined in GitHub.Data.Content Associated Types
Methods from :: ContentResultInfo -> Rep ContentResultInfo x # to :: Rep ContentResultInfo x -> ContentResultInfo # | |||||
Show ContentResultInfo Source # | |||||
Defined in GitHub.Data.Content Methods showsPrec :: Int -> ContentResultInfo -> ShowS # show :: ContentResultInfo -> String # showList :: [ContentResultInfo] -> ShowS # | |||||
Binary ContentResultInfo Source # | |||||
Defined in GitHub.Data.Content Methods put :: ContentResultInfo -> Put # get :: Get ContentResultInfo # putList :: [ContentResultInfo] -> Put # | |||||
NFData ContentResultInfo Source # | |||||
Defined in GitHub.Data.Content Methods rnf :: ContentResultInfo -> () # | |||||
Eq ContentResultInfo Source # | |||||
Defined in GitHub.Data.Content Methods (==) :: ContentResultInfo -> ContentResultInfo -> Bool # (/=) :: ContentResultInfo -> ContentResultInfo -> Bool # | |||||
Ord ContentResultInfo Source # | |||||
Defined in GitHub.Data.Content Methods compare :: ContentResultInfo -> ContentResultInfo -> Ordering # (<) :: ContentResultInfo -> ContentResultInfo -> Bool # (<=) :: ContentResultInfo -> ContentResultInfo -> Bool # (>) :: ContentResultInfo -> ContentResultInfo -> Bool # (>=) :: ContentResultInfo -> ContentResultInfo -> Bool # max :: ContentResultInfo -> ContentResultInfo -> ContentResultInfo # min :: ContentResultInfo -> ContentResultInfo -> ContentResultInfo # | |||||
type Rep ContentResultInfo Source # | |||||
Defined in GitHub.Data.Content type Rep ContentResultInfo = D1 ('MetaData "ContentResultInfo" "GitHub.Data.Content" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" 'False) (C1 ('MetaCons "ContentResultInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "contentResultInfo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ContentInfo) :*: S1 ('MetaSel ('Just "contentResultSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))) |
data ContentResult Source #
Constructors
ContentResult | |
Fields |
Instances
FromJSON ContentResult Source # | |||||
Defined in GitHub.Data.Content Methods parseJSON :: Value -> Parser ContentResult # parseJSONList :: Value -> Parser [ContentResult] # | |||||
Data ContentResult Source # | |||||
Defined in GitHub.Data.Content 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 :: forall r r'. (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 # | |||||
Generic ContentResult Source # | |||||
Defined in GitHub.Data.Content Associated Types
| |||||
Show ContentResult Source # | |||||
Defined in GitHub.Data.Content Methods showsPrec :: Int -> ContentResult -> ShowS # show :: ContentResult -> String # showList :: [ContentResult] -> ShowS # | |||||
Binary ContentResult Source # | |||||
Defined in GitHub.Data.Content | |||||
NFData ContentResult Source # | |||||
Defined in GitHub.Data.Content Methods rnf :: ContentResult -> () # | |||||
Eq ContentResult Source # | |||||
Defined in GitHub.Data.Content Methods (==) :: ContentResult -> ContentResult -> Bool # (/=) :: ContentResult -> ContentResult -> Bool # | |||||
Ord ContentResult Source # | |||||
Defined in GitHub.Data.Content Methods compare :: ContentResult -> ContentResult -> Ordering # (<) :: ContentResult -> ContentResult -> Bool # (<=) :: ContentResult -> ContentResult -> Bool # (>) :: ContentResult -> ContentResult -> Bool # (>=) :: ContentResult -> ContentResult -> Bool # max :: ContentResult -> ContentResult -> ContentResult # min :: ContentResult -> ContentResult -> ContentResult # | |||||
type Rep ContentResult Source # | |||||
Defined in GitHub.Data.Content type Rep ContentResult = D1 ('MetaData "ContentResult" "GitHub.Data.Content" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" 'False) (C1 ('MetaCons "ContentResult" 'PrefixI 'True) (S1 ('MetaSel ('Just "contentResultContent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ContentResultInfo) :*: S1 ('MetaSel ('Just "contentResultCommit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 GitCommit))) |
Constructors
Author | |
Fields
|
Instances
ToJSON Author Source # | |||||
Data Author Source # | |||||
Defined in GitHub.Data.Content 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 :: forall r r'. (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 # | |||||
Generic Author Source # | |||||
Defined in GitHub.Data.Content Associated Types
| |||||
Show Author Source # | |||||
Binary Author Source # | |||||
NFData Author Source # | |||||
Defined in GitHub.Data.Content | |||||
Eq Author Source # | |||||
Ord Author Source # | |||||
type Rep Author Source # | |||||
Defined in GitHub.Data.Content type Rep Author = D1 ('MetaData "Author" "GitHub.Data.Content" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" 'False) (C1 ('MetaCons "Author" 'PrefixI 'True) (S1 ('MetaSel ('Just "authorName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "authorEmail") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) |
data CreateFile Source #
Constructors
CreateFile | |
Fields
|
Instances
ToJSON CreateFile Source # | |||||
Defined in GitHub.Data.Content Methods toJSON :: CreateFile -> Value # toEncoding :: CreateFile -> Encoding # toJSONList :: [CreateFile] -> Value # toEncodingList :: [CreateFile] -> Encoding # omitField :: CreateFile -> Bool # | |||||
Data CreateFile Source # | |||||
Defined in GitHub.Data.Content 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 :: forall r r'. (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 # | |||||
Generic CreateFile Source # | |||||
Defined in GitHub.Data.Content Associated Types
| |||||
Show CreateFile Source # | |||||
Defined in GitHub.Data.Content Methods showsPrec :: Int -> CreateFile -> ShowS # show :: CreateFile -> String # showList :: [CreateFile] -> ShowS # | |||||
Binary CreateFile Source # | |||||
Defined in GitHub.Data.Content | |||||
NFData CreateFile Source # | |||||
Defined in GitHub.Data.Content Methods rnf :: CreateFile -> () # | |||||
Eq CreateFile Source # | |||||
Defined in GitHub.Data.Content | |||||
Ord CreateFile Source # | |||||
Defined in GitHub.Data.Content Methods compare :: CreateFile -> CreateFile -> Ordering # (<) :: CreateFile -> CreateFile -> Bool # (<=) :: CreateFile -> CreateFile -> Bool # (>) :: CreateFile -> CreateFile -> Bool # (>=) :: CreateFile -> CreateFile -> Bool # max :: CreateFile -> CreateFile -> CreateFile # min :: CreateFile -> CreateFile -> CreateFile # | |||||
type Rep CreateFile Source # | |||||
Defined in GitHub.Data.Content type Rep CreateFile = D1 ('MetaData "CreateFile" "GitHub.Data.Content" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" 'False) (C1 ('MetaCons "CreateFile" 'PrefixI 'True) ((S1 ('MetaSel ('Just "createFilePath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "createFileMessage") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "createFileContent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) :*: (S1 ('MetaSel ('Just "createFileBranch") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "createFileAuthor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Author)) :*: S1 ('MetaSel ('Just "createFileCommitter") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Author)))))) |
data UpdateFile Source #
Constructors
UpdateFile | |
Fields
|
Instances
ToJSON UpdateFile Source # | |||||
Defined in GitHub.Data.Content Methods toJSON :: UpdateFile -> Value # toEncoding :: UpdateFile -> Encoding # toJSONList :: [UpdateFile] -> Value # toEncodingList :: [UpdateFile] -> Encoding # omitField :: UpdateFile -> Bool # | |||||
Data UpdateFile Source # | |||||
Defined in GitHub.Data.Content 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 :: forall r r'. (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 # | |||||
Generic UpdateFile Source # | |||||
Defined in GitHub.Data.Content Associated Types
| |||||
Show UpdateFile Source # | |||||
Defined in GitHub.Data.Content Methods showsPrec :: Int -> UpdateFile -> ShowS # show :: UpdateFile -> String # showList :: [UpdateFile] -> ShowS # | |||||
Binary UpdateFile Source # | |||||
Defined in GitHub.Data.Content | |||||
NFData UpdateFile Source # | |||||
Defined in GitHub.Data.Content Methods rnf :: UpdateFile -> () # | |||||
Eq UpdateFile Source # | |||||
Defined in GitHub.Data.Content | |||||
Ord UpdateFile Source # | |||||
Defined in GitHub.Data.Content Methods compare :: UpdateFile -> UpdateFile -> Ordering # (<) :: UpdateFile -> UpdateFile -> Bool # (<=) :: UpdateFile -> UpdateFile -> Bool # (>) :: UpdateFile -> UpdateFile -> Bool # (>=) :: UpdateFile -> UpdateFile -> Bool # max :: UpdateFile -> UpdateFile -> UpdateFile # min :: UpdateFile -> UpdateFile -> UpdateFile # | |||||
type Rep UpdateFile Source # | |||||
Defined in GitHub.Data.Content type Rep UpdateFile = D1 ('MetaData "UpdateFile" "GitHub.Data.Content" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" 'False) (C1 ('MetaCons "UpdateFile" 'PrefixI 'True) ((S1 ('MetaSel ('Just "updateFilePath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "updateFileMessage") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "updateFileContent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) :*: ((S1 ('MetaSel ('Just "updateFileSHA") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "updateFileBranch") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "updateFileAuthor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Author)) :*: S1 ('MetaSel ('Just "updateFileCommitter") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Author)))))) |
data DeleteFile Source #
Constructors
DeleteFile | |
Fields
|
Instances
ToJSON DeleteFile Source # | |||||
Defined in GitHub.Data.Content Methods toJSON :: DeleteFile -> Value # toEncoding :: DeleteFile -> Encoding # toJSONList :: [DeleteFile] -> Value # toEncodingList :: [DeleteFile] -> Encoding # omitField :: DeleteFile -> Bool # | |||||
Data DeleteFile Source # | |||||
Defined in GitHub.Data.Content 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 :: forall r r'. (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 # | |||||
Generic DeleteFile Source # | |||||
Defined in GitHub.Data.Content Associated Types
| |||||
Show DeleteFile Source # | |||||
Defined in GitHub.Data.Content Methods showsPrec :: Int -> DeleteFile -> ShowS # show :: DeleteFile -> String # showList :: [DeleteFile] -> ShowS # | |||||
Binary DeleteFile Source # | |||||
Defined in GitHub.Data.Content | |||||
NFData DeleteFile Source # | |||||
Defined in GitHub.Data.Content Methods rnf :: DeleteFile -> () # | |||||
Eq DeleteFile Source # | |||||
Defined in GitHub.Data.Content | |||||
Ord DeleteFile Source # | |||||
Defined in GitHub.Data.Content Methods compare :: DeleteFile -> DeleteFile -> Ordering # (<) :: DeleteFile -> DeleteFile -> Bool # (<=) :: DeleteFile -> DeleteFile -> Bool # (>) :: DeleteFile -> DeleteFile -> Bool # (>=) :: DeleteFile -> DeleteFile -> Bool # max :: DeleteFile -> DeleteFile -> DeleteFile # min :: DeleteFile -> DeleteFile -> DeleteFile # | |||||
type Rep DeleteFile Source # | |||||
Defined in GitHub.Data.Content type Rep DeleteFile = D1 ('MetaData "DeleteFile" "GitHub.Data.Content" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" 'False) (C1 ('MetaCons "DeleteFile" 'PrefixI 'True) ((S1 ('MetaSel ('Just "deleteFilePath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "deleteFileMessage") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "deleteFileSHA") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) :*: (S1 ('MetaSel ('Just "deleteFileBranch") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "deleteFileAuthor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Author)) :*: S1 ('MetaSel ('Just "deleteFileCommitter") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Author)))))) |