github-0.28: Access to the GitHub API, v3.
LicenseBSD-3-Clause
MaintainerOleg Grenrus <oleg.grenrus@iki.fi>
Safe HaskellSafe-Inferred
LanguageHaskell2010

GitHub.Data.Gists

Description

 

Documentation

data Gist Source #

Instances

Instances details
Data Gist Source # 
Instance details

Defined in GitHub.Data.Gists

Methods

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

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

toConstr :: Gist -> Constr #

dataTypeOf :: Gist -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Gist Source # 
Instance details

Defined in GitHub.Data.Gists

Associated Types

type Rep Gist :: Type -> Type #

Methods

from :: Gist -> Rep Gist x #

to :: Rep Gist x -> Gist #

Show Gist Source # 
Instance details

Defined in GitHub.Data.Gists

Methods

showsPrec :: Int -> Gist -> ShowS #

show :: Gist -> String #

showList :: [Gist] -> ShowS #

Binary Gist Source # 
Instance details

Defined in GitHub.Data.Gists

Methods

put :: Gist -> Put #

get :: Get Gist #

putList :: [Gist] -> Put #

NFData Gist Source # 
Instance details

Defined in GitHub.Data.Gists

Methods

rnf :: Gist -> () #

Eq Gist Source # 
Instance details

Defined in GitHub.Data.Gists

Methods

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

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

FromJSON Gist Source # 
Instance details

Defined in GitHub.Data.Gists

Methods

parseJSON :: Value -> Parser Gist #

parseJSONList :: Value -> Parser [Gist] #

type Rep Gist Source # 
Instance details

Defined in GitHub.Data.Gists

data GistFile Source #

Instances

Instances details
Data GistFile Source # 
Instance details

Defined in GitHub.Data.Gists

Methods

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

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

toConstr :: GistFile -> Constr #

dataTypeOf :: GistFile -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic GistFile Source # 
Instance details

Defined in GitHub.Data.Gists

Associated Types

type Rep GistFile :: Type -> Type #

Methods

from :: GistFile -> Rep GistFile x #

to :: Rep GistFile x -> GistFile #

Show GistFile Source # 
Instance details

Defined in GitHub.Data.Gists

Binary GistFile Source # 
Instance details

Defined in GitHub.Data.Gists

Methods

put :: GistFile -> Put #

get :: Get GistFile #

putList :: [GistFile] -> Put #

NFData GistFile Source # 
Instance details

Defined in GitHub.Data.Gists

Methods

rnf :: GistFile -> () #

Eq GistFile Source # 
Instance details

Defined in GitHub.Data.Gists

FromJSON GistFile Source # 
Instance details

Defined in GitHub.Data.Gists

Methods

parseJSON :: Value -> Parser GistFile #

parseJSONList :: Value -> Parser [GistFile] #

type Rep GistFile Source # 
Instance details

Defined in GitHub.Data.Gists

type Rep GistFile = D1 ('MetaData "GistFile" "GitHub.Data.Gists" "github-0.28-inplace" 'False) (C1 ('MetaCons "GistFile" 'PrefixI 'True) ((S1 ('MetaSel ('Just "gistFileType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "gistFileRawUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "gistFileSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))) :*: (S1 ('MetaSel ('Just "gistFileLanguage") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Language)) :*: (S1 ('MetaSel ('Just "gistFileFilename") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "gistFileContent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text))))))

data GistComment Source #

Instances

Instances details
Data GistComment Source # 
Instance details

Defined in GitHub.Data.Gists

Methods

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

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

toConstr :: GistComment -> Constr #

dataTypeOf :: GistComment -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic GistComment Source # 
Instance details

Defined in GitHub.Data.Gists

Associated Types

type Rep GistComment :: Type -> Type #

Show GistComment Source # 
Instance details

Defined in GitHub.Data.Gists

Binary GistComment Source # 
Instance details

Defined in GitHub.Data.Gists

NFData GistComment Source # 
Instance details

Defined in GitHub.Data.Gists

Methods

rnf :: GistComment -> () #

Eq GistComment Source # 
Instance details

Defined in GitHub.Data.Gists

Ord GistComment Source # 
Instance details

Defined in GitHub.Data.Gists

FromJSON GistComment Source # 
Instance details

Defined in GitHub.Data.Gists

Methods

parseJSON :: Value -> Parser GistComment #

parseJSONList :: Value -> Parser [GistComment] #

type Rep GistComment Source # 
Instance details

Defined in GitHub.Data.Gists

type Rep GistComment = D1 ('MetaData "GistComment" "GitHub.Data.Gists" "github-0.28-inplace" 'False) (C1 ('MetaCons "GistComment" 'PrefixI 'True) ((S1 ('MetaSel ('Just "gistCommentUser") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SimpleUser) :*: (S1 ('MetaSel ('Just "gistCommentUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "gistCommentCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime))) :*: (S1 ('MetaSel ('Just "gistCommentBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "gistCommentUpdatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "gistCommentId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Id GistComment))))))

data NewGist Source #

Instances

Instances details
Data NewGist Source # 
Instance details

Defined in GitHub.Data.Gists

Methods

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

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

toConstr :: NewGist -> Constr #

dataTypeOf :: NewGist -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic NewGist Source # 
Instance details

Defined in GitHub.Data.Gists

Associated Types

type Rep NewGist :: Type -> Type #

Methods

from :: NewGist -> Rep NewGist x #

to :: Rep NewGist x -> NewGist #

Show NewGist Source # 
Instance details

Defined in GitHub.Data.Gists

Binary NewGist Source # 
Instance details

Defined in GitHub.Data.Gists

Methods

put :: NewGist -> Put #

get :: Get NewGist #

putList :: [NewGist] -> Put #

NFData NewGist Source # 
Instance details

Defined in GitHub.Data.Gists

Methods

rnf :: NewGist -> () #

Eq NewGist Source # 
Instance details

Defined in GitHub.Data.Gists

Methods

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

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

ToJSON NewGist Source # 
Instance details

Defined in GitHub.Data.Gists

Methods

toJSON :: NewGist -> Value #

toEncoding :: NewGist -> Encoding #

toJSONList :: [NewGist] -> Value #

toEncodingList :: [NewGist] -> Encoding #

type Rep NewGist Source # 
Instance details

Defined in GitHub.Data.Gists

type Rep NewGist = D1 ('MetaData "NewGist" "GitHub.Data.Gists" "github-0.28-inplace" 'False) (C1 ('MetaCons "NewGist" 'PrefixI 'True) (S1 ('MetaSel ('Just "newGistDescription") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "newGistFiles") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashMap Text NewGistFile)) :*: S1 ('MetaSel ('Just "newGistPublic") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)))))

data NewGistFile Source #

Constructors

NewGistFile 

Instances

Instances details
Data NewGistFile Source # 
Instance details

Defined in GitHub.Data.Gists

Methods

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

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

toConstr :: NewGistFile -> Constr #

dataTypeOf :: NewGistFile -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic NewGistFile Source # 
Instance details

Defined in GitHub.Data.Gists

Associated Types

type Rep NewGistFile :: Type -> Type #

Show NewGistFile Source # 
Instance details

Defined in GitHub.Data.Gists

Binary NewGistFile Source # 
Instance details

Defined in GitHub.Data.Gists

NFData NewGistFile Source # 
Instance details

Defined in GitHub.Data.Gists

Methods

rnf :: NewGistFile -> () #

Eq NewGistFile Source # 
Instance details

Defined in GitHub.Data.Gists

ToJSON NewGistFile Source # 
Instance details

Defined in GitHub.Data.Gists

type Rep NewGistFile Source # 
Instance details

Defined in GitHub.Data.Gists

type Rep NewGistFile = D1 ('MetaData "NewGistFile" "GitHub.Data.Gists" "github-0.28-inplace" 'False) (C1 ('MetaCons "NewGistFile" 'PrefixI 'True) (S1 ('MetaSel ('Just "newGistFileContent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))