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

GitHub.Data.Definitions

Description

 
Synopsis

Documentation

data Error Source #

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

Instances details
Exception Error Source # 
Instance details

Defined in GitHub.Data.Definitions

Show Error Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

data OwnerType Source #

Type of the repository owners.

Instances

Instances details
Data OwnerType Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

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

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

toConstr :: OwnerType -> Constr #

dataTypeOf :: OwnerType -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded OwnerType Source # 
Instance details

Defined in GitHub.Data.Definitions

Enum OwnerType Source # 
Instance details

Defined in GitHub.Data.Definitions

Generic OwnerType Source # 
Instance details

Defined in GitHub.Data.Definitions

Associated Types

type Rep OwnerType :: Type -> Type #

Read OwnerType Source # 
Instance details

Defined in GitHub.Data.Definitions

Show OwnerType Source # 
Instance details

Defined in GitHub.Data.Definitions

Binary OwnerType Source # 
Instance details

Defined in GitHub.Data.Definitions

NFData OwnerType Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

rnf :: OwnerType -> () #

Eq OwnerType Source # 
Instance details

Defined in GitHub.Data.Definitions

Ord OwnerType Source # 
Instance details

Defined in GitHub.Data.Definitions

FromJSON OwnerType Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

parseJSON :: Value -> Parser OwnerType #

parseJSONList :: Value -> Parser [OwnerType] #

type Rep OwnerType Source # 
Instance details

Defined in GitHub.Data.Definitions

type Rep OwnerType = D1 ('MetaData "OwnerType" "GitHub.Data.Definitions" "github-0.28-inplace" 'False) (C1 ('MetaCons "OwnerUser" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OwnerOrganization" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OwnerBot" 'PrefixI 'False) (U1 :: Type -> Type)))

data SimpleUser Source #

Instances

Instances details
Data SimpleUser Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

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

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

toConstr :: SimpleUser -> Constr #

dataTypeOf :: SimpleUser -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic SimpleUser Source # 
Instance details

Defined in GitHub.Data.Definitions

Associated Types

type Rep SimpleUser :: Type -> Type #

Show SimpleUser Source # 
Instance details

Defined in GitHub.Data.Definitions

Binary SimpleUser Source # 
Instance details

Defined in GitHub.Data.Definitions

NFData SimpleUser Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

rnf :: SimpleUser -> () #

Eq SimpleUser Source # 
Instance details

Defined in GitHub.Data.Definitions

Ord SimpleUser Source # 
Instance details

Defined in GitHub.Data.Definitions

FromJSON SimpleUser Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

parseJSON :: Value -> Parser SimpleUser #

parseJSONList :: Value -> Parser [SimpleUser] #

type Rep SimpleUser Source # 
Instance details

Defined in GitHub.Data.Definitions

type Rep SimpleUser = D1 ('MetaData "SimpleUser" "GitHub.Data.Definitions" "github-0.28-inplace" 'False) (C1 ('MetaCons "SimpleUser" 'PrefixI 'True) ((S1 ('MetaSel ('Just "simpleUserId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Id User)) :*: S1 ('MetaSel ('Just "simpleUserLogin") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Name User))) :*: (S1 ('MetaSel ('Just "simpleUserAvatarUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "simpleUserUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))))

data SimpleOrganization Source #

Instances

Instances details
Data SimpleOrganization Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

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

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

toConstr :: SimpleOrganization -> Constr #

dataTypeOf :: SimpleOrganization -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic SimpleOrganization Source # 
Instance details

Defined in GitHub.Data.Definitions

Associated Types

type Rep SimpleOrganization :: Type -> Type #

Show SimpleOrganization Source # 
Instance details

Defined in GitHub.Data.Definitions

Binary SimpleOrganization Source # 
Instance details

Defined in GitHub.Data.Definitions

NFData SimpleOrganization Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

rnf :: SimpleOrganization -> () #

Eq SimpleOrganization Source # 
Instance details

Defined in GitHub.Data.Definitions

Ord SimpleOrganization Source # 
Instance details

Defined in GitHub.Data.Definitions

FromJSON SimpleOrganization Source # 
Instance details

Defined in GitHub.Data.Definitions

type Rep SimpleOrganization Source # 
Instance details

Defined in GitHub.Data.Definitions

type Rep SimpleOrganization = D1 ('MetaData "SimpleOrganization" "GitHub.Data.Definitions" "github-0.28-inplace" 'False) (C1 ('MetaCons "SimpleOrganization" 'PrefixI 'True) ((S1 ('MetaSel ('Just "simpleOrganizationId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Id Organization)) :*: S1 ('MetaSel ('Just "simpleOrganizationLogin") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Name Organization))) :*: (S1 ('MetaSel ('Just "simpleOrganizationUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "simpleOrganizationAvatarUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))))

data SimpleOwner Source #

Sometimes we don't know the type of the owner, e.g. in Repo

Instances

Instances details
Data SimpleOwner Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

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

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

toConstr :: SimpleOwner -> Constr #

dataTypeOf :: SimpleOwner -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic SimpleOwner Source # 
Instance details

Defined in GitHub.Data.Definitions

Associated Types

type Rep SimpleOwner :: Type -> Type #

Show SimpleOwner Source # 
Instance details

Defined in GitHub.Data.Definitions

Binary SimpleOwner Source # 
Instance details

Defined in GitHub.Data.Definitions

NFData SimpleOwner Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

rnf :: SimpleOwner -> () #

Eq SimpleOwner Source # 
Instance details

Defined in GitHub.Data.Definitions

Ord SimpleOwner Source # 
Instance details

Defined in GitHub.Data.Definitions

FromJSON SimpleOwner Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

parseJSON :: Value -> Parser SimpleOwner #

parseJSONList :: Value -> Parser [SimpleOwner] #

type Rep SimpleOwner Source # 
Instance details

Defined in GitHub.Data.Definitions

type Rep SimpleOwner = D1 ('MetaData "SimpleOwner" "GitHub.Data.Definitions" "github-0.28-inplace" 'False) (C1 ('MetaCons "SimpleOwner" 'PrefixI 'True) ((S1 ('MetaSel ('Just "simpleOwnerId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Id Owner)) :*: S1 ('MetaSel ('Just "simpleOwnerLogin") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Name Owner))) :*: (S1 ('MetaSel ('Just "simpleOwnerUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: (S1 ('MetaSel ('Just "simpleOwnerAvatarUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "simpleOwnerType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OwnerType)))))

data User Source #

Instances

Instances details
Data User Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

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

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

toConstr :: User -> Constr #

dataTypeOf :: User -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic User Source # 
Instance details

Defined in GitHub.Data.Definitions

Associated Types

type Rep User :: Type -> Type #

Methods

from :: User -> Rep User x #

to :: Rep User x -> User #

Show User Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

showsPrec :: Int -> User -> ShowS #

show :: User -> String #

showList :: [User] -> ShowS #

Binary User Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

put :: User -> Put #

get :: Get User #

putList :: [User] -> Put #

NFData User Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

rnf :: User -> () #

Eq User Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

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

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

Ord User Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

compare :: User -> User -> Ordering #

(<) :: User -> User -> Bool #

(<=) :: User -> User -> Bool #

(>) :: User -> User -> Bool #

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

max :: User -> User -> User #

min :: User -> User -> User #

FromJSON User Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

parseJSON :: Value -> Parser User #

parseJSONList :: Value -> Parser [User] #

type Rep User Source # 
Instance details

Defined in GitHub.Data.Definitions

type Rep User = D1 ('MetaData "User" "GitHub.Data.Definitions" "github-0.28-inplace" 'False) (C1 ('MetaCons "User" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "userId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Id User)) :*: S1 ('MetaSel ('Just "userLogin") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Name User))) :*: (S1 ('MetaSel ('Just "userName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "userType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OwnerType))) :*: ((S1 ('MetaSel ('Just "userCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "userPublicGists") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "userAvatarUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: (S1 ('MetaSel ('Just "userFollowers") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "userFollowing") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))))) :*: (((S1 ('MetaSel ('Just "userHireable") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "userBlog") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "userBio") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "userPublicRepos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))) :*: ((S1 ('MetaSel ('Just "userLocation") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "userCompany") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "userEmail") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "userUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "userHtmlUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)))))))

data Organization Source #

Instances

Instances details
Data Organization Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

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

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

toConstr :: Organization -> Constr #

dataTypeOf :: Organization -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Organization Source # 
Instance details

Defined in GitHub.Data.Definitions

Associated Types

type Rep Organization :: Type -> Type #

Show Organization Source # 
Instance details

Defined in GitHub.Data.Definitions

Binary Organization Source # 
Instance details

Defined in GitHub.Data.Definitions

NFData Organization Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

rnf :: Organization -> () #

Eq Organization Source # 
Instance details

Defined in GitHub.Data.Definitions

Ord Organization Source # 
Instance details

Defined in GitHub.Data.Definitions

FromJSON Organization Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

parseJSON :: Value -> Parser Organization #

parseJSONList :: Value -> Parser [Organization] #

type Rep Organization Source # 
Instance details

Defined in GitHub.Data.Definitions

type Rep Organization = D1 ('MetaData "Organization" "GitHub.Data.Definitions" "github-0.28-inplace" 'False) (C1 ('MetaCons "Organization" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "organizationId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Id Organization)) :*: S1 ('MetaSel ('Just "organizationLogin") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Name Organization))) :*: (S1 ('MetaSel ('Just "organizationName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "organizationType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OwnerType))) :*: ((S1 ('MetaSel ('Just "organizationBlog") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "organizationLocation") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "organizationFollowers") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "organizationCompany") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text))))) :*: (((S1 ('MetaSel ('Just "organizationAvatarUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "organizationPublicGists") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "organizationHtmlUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "organizationEmail") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 ('MetaSel ('Just "organizationFollowing") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "organizationPublicRepos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "organizationUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "organizationCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime))))))

newtype Owner Source #

In practice you can't have concrete values of Owner.

Constructors

Owner (Either User Organization) 

Instances

Instances details
Data Owner Source # 
Instance details

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 #

toConstr :: Owner -> Constr #

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 :: forall r r'. (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 #

Generic Owner Source # 
Instance details

Defined in GitHub.Data.Definitions

Associated Types

type Rep Owner :: Type -> Type #

Methods

from :: Owner -> Rep Owner x #

to :: Rep Owner x -> Owner #

Show Owner Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

showsPrec :: Int -> Owner -> ShowS #

show :: Owner -> String #

showList :: [Owner] -> ShowS #

Binary Owner Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

put :: Owner -> Put #

get :: Get Owner #

putList :: [Owner] -> Put #

NFData Owner Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

rnf :: Owner -> () #

Eq Owner Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

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

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

Ord Owner Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

compare :: Owner -> Owner -> Ordering #

(<) :: Owner -> Owner -> Bool #

(<=) :: Owner -> Owner -> Bool #

(>) :: Owner -> Owner -> Bool #

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

max :: Owner -> Owner -> Owner #

min :: Owner -> Owner -> Owner #

FromJSON Owner Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

parseJSON :: Value -> Parser Owner #

parseJSONList :: Value -> Parser [Owner] #

type Rep Owner Source # 
Instance details

Defined in GitHub.Data.Definitions

type Rep Owner = D1 ('MetaData "Owner" "GitHub.Data.Definitions" "github-0.28-inplace" 'True) (C1 ('MetaCons "Owner" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either User Organization))))

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

Instances details
Data OrgMemberFilter Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

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

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

toConstr :: OrgMemberFilter -> Constr #

dataTypeOf :: OrgMemberFilter -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded OrgMemberFilter Source # 
Instance details

Defined in GitHub.Data.Definitions

Enum OrgMemberFilter Source # 
Instance details

Defined in GitHub.Data.Definitions

Generic OrgMemberFilter Source # 
Instance details

Defined in GitHub.Data.Definitions

Associated Types

type Rep OrgMemberFilter :: Type -> Type #

Show OrgMemberFilter Source # 
Instance details

Defined in GitHub.Data.Definitions

Eq OrgMemberFilter Source # 
Instance details

Defined in GitHub.Data.Definitions

Ord OrgMemberFilter Source # 
Instance details

Defined in GitHub.Data.Definitions

type Rep OrgMemberFilter Source # 
Instance details

Defined in GitHub.Data.Definitions

type Rep OrgMemberFilter = D1 ('MetaData "OrgMemberFilter" "GitHub.Data.Definitions" "github-0.28-inplace" 'False) (C1 ('MetaCons "OrgMemberFilter2faDisabled" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OrgMemberFilterAll" 'PrefixI 'False) (U1 :: Type -> Type))

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

Instances details
Data OrgMemberRole Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

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

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

toConstr :: OrgMemberRole -> Constr #

dataTypeOf :: OrgMemberRole -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded OrgMemberRole Source # 
Instance details

Defined in GitHub.Data.Definitions

Enum OrgMemberRole Source # 
Instance details

Defined in GitHub.Data.Definitions

Generic OrgMemberRole Source # 
Instance details

Defined in GitHub.Data.Definitions

Associated Types

type Rep OrgMemberRole :: Type -> Type #

Show OrgMemberRole Source # 
Instance details

Defined in GitHub.Data.Definitions

Eq OrgMemberRole Source # 
Instance details

Defined in GitHub.Data.Definitions

Ord OrgMemberRole Source # 
Instance details

Defined in GitHub.Data.Definitions

type Rep OrgMemberRole Source # 
Instance details

Defined in GitHub.Data.Definitions

type Rep OrgMemberRole = D1 ('MetaData "OrgMemberRole" "GitHub.Data.Definitions" "github-0.28-inplace" 'False) (C1 ('MetaCons "OrgMemberRoleAll" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OrgMemberRoleAdmin" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OrgMemberRoleMember" 'PrefixI 'False) (U1 :: Type -> Type)))

type QueryString = [(ByteString, Maybe ByteString)] Source #

Request query string

type Count = Int Source #

Count of elements

newtype IssueNumber Source #

Constructors

IssueNumber Int 

Instances

Instances details
Data IssueNumber Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

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

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

toConstr :: IssueNumber -> Constr #

dataTypeOf :: IssueNumber -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic IssueNumber Source # 
Instance details

Defined in GitHub.Data.Definitions

Associated Types

type Rep IssueNumber :: Type -> Type #

Show IssueNumber Source # 
Instance details

Defined in GitHub.Data.Definitions

Binary IssueNumber Source # 
Instance details

Defined in GitHub.Data.Definitions

NFData IssueNumber Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

rnf :: IssueNumber -> () #

Eq IssueNumber Source # 
Instance details

Defined in GitHub.Data.Definitions

Ord IssueNumber Source # 
Instance details

Defined in GitHub.Data.Definitions

IsPathPart IssueNumber Source # 
Instance details

Defined in GitHub.Data.Request

Hashable IssueNumber Source # 
Instance details

Defined in GitHub.Data.Definitions

FromJSON IssueNumber Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

parseJSON :: Value -> Parser IssueNumber #

parseJSONList :: Value -> Parser [IssueNumber] #

ToJSON IssueNumber Source # 
Instance details

Defined in GitHub.Data.Definitions

type Rep IssueNumber Source # 
Instance details

Defined in GitHub.Data.Definitions

type Rep IssueNumber = D1 ('MetaData "IssueNumber" "GitHub.Data.Definitions" "github-0.28-inplace" 'True) (C1 ('MetaCons "IssueNumber" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data IssueLabel Source #

Constructors

IssueLabel 

Instances

Instances details
Data IssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

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

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

toConstr :: IssueLabel -> Constr #

dataTypeOf :: IssueLabel -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic IssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

Associated Types

type Rep IssueLabel :: Type -> Type #

Show IssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

Binary IssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

NFData IssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

rnf :: IssueLabel -> () #

Eq IssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

Ord IssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

FromJSON IssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

parseJSON :: Value -> Parser IssueLabel #

parseJSONList :: Value -> Parser [IssueLabel] #

type Rep IssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

type Rep IssueLabel = D1 ('MetaData "IssueLabel" "GitHub.Data.Definitions" "github-0.28-inplace" 'False) (C1 ('MetaCons "IssueLabel" 'PrefixI 'True) ((S1 ('MetaSel ('Just "labelColor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "labelUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "labelName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Name IssueLabel)) :*: S1 ('MetaSel ('Just "labelDesc") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)))))

data NewIssueLabel Source #

Instances

Instances details
Data NewIssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

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

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

toConstr :: NewIssueLabel -> Constr #

dataTypeOf :: NewIssueLabel -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic NewIssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

Associated Types

type Rep NewIssueLabel :: Type -> Type #

Show NewIssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

Binary NewIssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

NFData NewIssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

rnf :: NewIssueLabel -> () #

Eq NewIssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

Ord NewIssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

ToJSON NewIssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

type Rep NewIssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

type Rep NewIssueLabel = D1 ('MetaData "NewIssueLabel" "GitHub.Data.Definitions" "github-0.28-inplace" 'False) (C1 ('MetaCons "NewIssueLabel" 'PrefixI 'True) (S1 ('MetaSel ('Just "newLabelColor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "newLabelName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Name NewIssueLabel)) :*: S1 ('MetaSel ('Just "newLabelDesc") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)))))

data UpdateIssueLabel Source #

Instances

Instances details
Data UpdateIssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

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

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

toConstr :: UpdateIssueLabel -> Constr #

dataTypeOf :: UpdateIssueLabel -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic UpdateIssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

Associated Types

type Rep UpdateIssueLabel :: Type -> Type #

Show UpdateIssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

Binary UpdateIssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

NFData UpdateIssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

Methods

rnf :: UpdateIssueLabel -> () #

Eq UpdateIssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

Ord UpdateIssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

ToJSON UpdateIssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

type Rep UpdateIssueLabel Source # 
Instance details

Defined in GitHub.Data.Definitions

type Rep UpdateIssueLabel = D1 ('MetaData "UpdateIssueLabel" "GitHub.Data.Definitions" "github-0.28-inplace" 'False) (C1 ('MetaCons "UpdateIssueLabel" 'PrefixI 'True) (S1 ('MetaSel ('Just "updateLabelColor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "updateLabelName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Name UpdateIssueLabel)) :*: S1 ('MetaSel ('Just "updateLabelDesc") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)))))