License | BSD-3-Clause |
---|---|
Maintainer | Oleg Grenrus <oleg.grenrus@iki.fi> |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module re-exports the GitHub.Data.
and GitHub.Auth submodules.
Synopsis
- data Name entity
- mkName :: proxy entity -> Text -> Name entity
- untagName :: Name entity -> Text
- mkOwnerName :: Text -> Name Owner
- mkUserName :: Text -> Name User
- mkTeamName :: Text -> Name Team
- mkOrganizationName :: Text -> Name Organization
- mkRepoName :: Text -> Name Repo
- mkCommitName :: Text -> Name Commit
- fromUserName :: Name User -> Name Owner
- fromOrganizationName :: Name Organization -> Name Owner
- data Id entity
- mkId :: proxy entity -> Int -> Id entity
- untagId :: Id entity -> Int
- mkOwnerId :: Int -> Id Owner
- mkUserId :: Int -> Id User
- mkTeamId :: Int -> Id Team
- mkOrganizationId :: Int -> Id Organization
- mkRepoId :: Int -> Id Repo
- fromUserId :: Id User -> Id Owner
- fromOrganizationId :: Id Organization -> Id Owner
- newtype IssueNumber = IssueNumber Int
- module GitHub.Auth
- module GitHub.Data.Activities
- module GitHub.Data.Comments
- module GitHub.Data.Content
- module GitHub.Data.Definitions
- module GitHub.Data.DeployKeys
- module GitHub.Data.Deployments
- module GitHub.Data.Email
- module GitHub.Data.Events
- module GitHub.Data.Gists
- module GitHub.Data.GitData
- module GitHub.Data.Invitation
- module GitHub.Data.Issues
- module GitHub.Data.Milestone
- module GitHub.Data.Options
- module GitHub.Data.PublicSSHKeys
- module GitHub.Data.PullRequests
- module GitHub.Data.RateLimit
- module GitHub.Data.Releases
- module GitHub.Data.Repos
- module GitHub.Data.Request
- module GitHub.Data.Reviews
- module GitHub.Data.Search
- module GitHub.Data.Statuses
- module GitHub.Data.Teams
- module GitHub.Data.URL
- module GitHub.Data.Webhooks
- module GitHub.Data.Webhooks.Validate
Tagged types
Name
Instances
Data entity => Data (Name entity) Source # | |
Defined in GitHub.Data.Name gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name entity -> c (Name entity) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Name entity) # toConstr :: Name entity -> Constr # dataTypeOf :: Name entity -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Name entity)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Name entity)) # gmapT :: (forall b. Data b => b -> b) -> Name entity -> Name entity # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name entity -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name entity -> r # gmapQ :: (forall d. Data d => d -> u) -> Name entity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Name entity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name entity -> m (Name entity) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name entity -> m (Name entity) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name entity -> m (Name entity) # | |
IsString (Name entity) Source # | |
Defined in GitHub.Data.Name fromString :: String -> Name entity # | |
Generic (Name entity) Source # | |
Show (Name entity) Source # | |
Binary (Name entity) Source # | |
NFData (Name entity) Source # | |
Defined in GitHub.Data.Name | |
Eq (Name entity) Source # | |
Ord (Name entity) Source # | |
Defined in GitHub.Data.Name | |
IsPathPart (Name a) Source # | |
Defined in GitHub.Data.Request toPathPart :: Name a -> Text Source # | |
Hashable (Name entity) Source # | |
Defined in GitHub.Data.Name | |
FromJSON (Name entity) Source # | |
Defined in GitHub.Data.Name | |
FromJSONKey (Name entity) Source # | Since: 0.15.0.0 |
Defined in GitHub.Data.Name fromJSONKey :: FromJSONKeyFunction (Name entity) fromJSONKeyList :: FromJSONKeyFunction [Name entity] | |
ToJSON (Name entity) Source # | |
Defined in GitHub.Data.Name toJSON :: Name entity -> Value # toEncoding :: Name entity -> Encoding # toJSONList :: [Name entity] -> Value # toEncodingList :: [Name entity] -> Encoding # | |
ToJSONKey (Name entity) Source # | Since: 0.15.0.0 |
Defined in GitHub.Data.Name toJSONKey :: ToJSONKeyFunction (Name entity) toJSONKeyList :: ToJSONKeyFunction [Name entity] | |
type Rep (Name entity) Source # | |
Defined in GitHub.Data.Name |
Id
Numeric identifier.
Instances
Data entity => Data (Id entity) Source # | |
Defined in GitHub.Data.Id gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Id entity -> c (Id entity) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Id entity) # toConstr :: Id entity -> Constr # dataTypeOf :: Id entity -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Id entity)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Id entity)) # gmapT :: (forall b. Data b => b -> b) -> Id entity -> Id entity # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Id entity -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Id entity -> r # gmapQ :: (forall d. Data d => d -> u) -> Id entity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Id entity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Id entity -> m (Id entity) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Id entity -> m (Id entity) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Id entity -> m (Id entity) # | |
Generic (Id entity) Source # | |
Show (Id entity) Source # | |
Binary (Id entity) Source # | |
NFData (Id entity) Source # | |
Defined in GitHub.Data.Id | |
Eq (Id entity) Source # | |
Ord (Id entity) Source # | |
Defined in GitHub.Data.Id | |
IsPathPart (Id a) Source # | |
Defined in GitHub.Data.Request toPathPart :: Id a -> Text Source # | |
Hashable (Id entity) Source # | |
Defined in GitHub.Data.Id | |
FromJSON (Id entity) Source # | |
Defined in GitHub.Data.Id | |
ToJSON (Id entity) Source # | |
Defined in GitHub.Data.Id toJSON :: Id entity -> Value # toEncoding :: Id entity -> Encoding # toJSONList :: [Id entity] -> Value # toEncodingList :: [Id entity] -> Encoding # | |
type Rep (Id entity) Source # | |
Defined in GitHub.Data.Id |
mkOrganizationId :: Int -> Id Organization Source #
fromOrganizationId :: Id Organization -> Id Owner Source #
IssueNumber
newtype IssueNumber Source #
Instances
Module re-exports
module GitHub.Auth
module GitHub.Data.Activities
module GitHub.Data.Comments
module GitHub.Data.Content
module GitHub.Data.Definitions
module GitHub.Data.DeployKeys
module GitHub.Data.Deployments
module GitHub.Data.Email
module GitHub.Data.Events
module GitHub.Data.Gists
module GitHub.Data.GitData
module GitHub.Data.Invitation
module GitHub.Data.Issues
module GitHub.Data.Milestone
module GitHub.Data.Options
module GitHub.Data.PublicSSHKeys
module GitHub.Data.PullRequests
module GitHub.Data.RateLimit
module GitHub.Data.Releases
module GitHub.Data.Repos
module GitHub.Data.Request
module GitHub.Data.Reviews
module GitHub.Data.Search
module GitHub.Data.Statuses
module GitHub.Data.Teams
module GitHub.Data.URL
module GitHub.Data.Webhooks