| License | BSD-3-Clause | 
|---|---|
| Maintainer | Oleg Grenrus <oleg.grenrus@iki.fi> | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
GitHub.Data.Definitions
Description
Synopsis
- data Error- = HTTPError !HttpException
- | ParseError !Text
- | JsonError !Text
- | UserError !Text
 
- data OwnerType
- data SimpleUser = SimpleUser {- simpleUserId :: !(Id User)
- simpleUserLogin :: !(Name User)
- simpleUserAvatarUrl :: !URL
- simpleUserUrl :: !URL
 
- data SimpleOrganization = SimpleOrganization {}
- data SimpleOwner = SimpleOwner {- simpleOwnerId :: !(Id Owner)
- simpleOwnerLogin :: !(Name Owner)
- simpleOwnerUrl :: !URL
- simpleOwnerAvatarUrl :: !URL
- simpleOwnerType :: !OwnerType
 
- data User = User {- userId :: !(Id User)
- userLogin :: !(Name User)
- userName :: !(Maybe Text)
- userType :: !OwnerType
- userCreatedAt :: !UTCTime
- userPublicGists :: !Int
- userAvatarUrl :: !URL
- userFollowers :: !Int
- userFollowing :: !Int
- userHireable :: !(Maybe Bool)
- userBlog :: !(Maybe Text)
- userBio :: !(Maybe Text)
- userPublicRepos :: !Int
- userLocation :: !(Maybe Text)
- userCompany :: !(Maybe Text)
- userEmail :: !(Maybe Text)
- userUrl :: !URL
- userHtmlUrl :: !URL
 
- data Organization = Organization {- organizationId :: !(Id Organization)
- organizationLogin :: !(Name Organization)
- organizationName :: !(Maybe Text)
- organizationType :: !OwnerType
- organizationBlog :: !(Maybe Text)
- organizationLocation :: !(Maybe Text)
- organizationFollowers :: !Int
- organizationCompany :: !(Maybe Text)
- organizationAvatarUrl :: !URL
- organizationPublicGists :: !Int
- organizationHtmlUrl :: !URL
- organizationEmail :: !(Maybe Text)
- organizationFollowing :: !Int
- organizationPublicRepos :: !Int
- organizationUrl :: !URL
- organizationCreatedAt :: !UTCTime
 
- newtype Owner = Owner (Either User Organization)
- fromOwner :: Owner -> Either User Organization
- parseUser :: Object -> Parser User
- parseOrganization :: Object -> Parser Organization
- data OrgMemberFilter
- data OrgMemberRole
- type QueryString = [(ByteString, Maybe ByteString)]
- type Count = Int
- newtype IssueNumber = IssueNumber Int
- unIssueNumber :: IssueNumber -> Int
- data IssueLabel = IssueLabel {- labelColor :: !Text
- labelUrl :: !URL
- labelName :: !(Name IssueLabel)
 
Documentation
Errors have been tagged according to their source, so you can more easily dispatch and handle them.
Constructors
| HTTPError !HttpException | A HTTP error occurred. The actual caught error is included. | 
| ParseError !Text | An error in the parser itself. | 
| JsonError !Text | The JSON is malformed or unexpected. | 
| UserError !Text | Incorrect input. | 
Instances
| Show Error Source # | |
| Exception Error Source # | |
| Defined in GitHub.Data.Definitions Methods toException :: Error -> SomeException # fromException :: SomeException -> Maybe Error # displayException :: Error -> String # | |
Type of the repository owners.
Constructors
| OwnerUser | |
| OwnerOrganization | 
Instances
data SimpleUser Source #
Constructors
| SimpleUser | |
| Fields 
 | |
Instances
data SimpleOrganization Source #
Constructors
| SimpleOrganization | |
| Fields | |
Instances
data SimpleOwner Source #
Sometimes we don't know the type of the owner, e.g. in Repo
Constructors
| SimpleOwner | |
| Fields 
 | |
Instances
Constructors
| User | |
| Fields 
 | |
Instances
data Organization Source #
Constructors
| Organization | |
| Fields 
 | |
Instances
In practic, you cam't have concrete values of Owner.
Constructors
| Owner (Either User Organization) | 
Instances
| Eq Owner Source # | |
| Data Owner Source # | |
| Defined in GitHub.Data.Definitions Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Owner -> c Owner # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Owner # dataTypeOf :: Owner -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Owner) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Owner) # gmapT :: (forall b. Data b => b -> b) -> Owner -> Owner # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Owner -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Owner -> r # gmapQ :: (forall d. Data d => d -> u) -> Owner -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Owner -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Owner -> m Owner # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Owner -> m Owner # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Owner -> m Owner # | |
| Ord Owner Source # | |
| Show Owner Source # | |
| Generic Owner Source # | |
| FromJSON Owner Source # | |
| Binary Owner Source # | |
| NFData Owner Source # | |
| Defined in GitHub.Data.Definitions | |
| type Rep Owner Source # | |
| Defined in GitHub.Data.Definitions | |
data OrgMemberFilter Source #
Filter members returned in the list.
Constructors
| OrgMemberFilter2faDisabled | Members without two-factor authentication enabled. Available for organization owners. | 
| OrgMemberFilterAll | All members the authenticated user can see. | 
Instances
data OrgMemberRole Source #
Filter members returned by their role.
Constructors
| OrgMemberRoleAll | All members of the organization, regardless of role. | 
| OrgMemberRoleAdmin | Organization owners. | 
| OrgMemberRoleMember | Non-owner organization members. | 
Instances
type QueryString = [(ByteString, Maybe ByteString)] Source #
Request query string
newtype IssueNumber Source #
Constructors
| IssueNumber Int | 
Instances
unIssueNumber :: IssueNumber -> Int Source #
data IssueLabel Source #
Constructors
| IssueLabel | |
| Fields 
 | |