github-0.26: Access to the GitHub API, v3.

LicenseBSD-3-Clause
MaintainerOleg Grenrus <oleg.grenrus@iki.fi>
Safe HaskellNone
LanguageHaskell2010

GitHub.Data.Request

Contents

Description

 
Synopsis

Request

type Request = GenRequest MtJSON Source #

Most requests ask for JSON.

data GenRequest (mt :: MediaType *) (rw :: RW) a where Source #

Github request data type.

  • rw describes whether authentication is required. It's required for non-GET requests.
  • mt describes the media type, i.e. how the response should be interpreted.
  • a is the result type

Note: Request is not Functor on purpose.

Constructors

Query :: Paths -> QueryString -> GenRequest mt rw a 
PagedQuery :: (a ~ t b, Foldable t, Semigroup a) => Paths -> QueryString -> FetchCount -> GenRequest mt rw a 
Command

Command

Fields

Instances
Eq (GenRequest rw mt a) Source # 
Instance details

Defined in GitHub.Data.Request

Methods

(==) :: GenRequest rw mt a -> GenRequest rw mt a -> Bool #

(/=) :: GenRequest rw mt a -> GenRequest rw mt a -> Bool #

Ord (GenRequest rw mt a) Source # 
Instance details

Defined in GitHub.Data.Request

Methods

compare :: GenRequest rw mt a -> GenRequest rw mt a -> Ordering #

(<) :: GenRequest rw mt a -> GenRequest rw mt a -> Bool #

(<=) :: GenRequest rw mt a -> GenRequest rw mt a -> Bool #

(>) :: GenRequest rw mt a -> GenRequest rw mt a -> Bool #

(>=) :: GenRequest rw mt a -> GenRequest rw mt a -> Bool #

max :: GenRequest rw mt a -> GenRequest rw mt a -> GenRequest rw mt a #

min :: GenRequest rw mt a -> GenRequest rw mt a -> GenRequest rw mt a #

Show (GenRequest rw mt a) Source # 
Instance details

Defined in GitHub.Data.Request

Methods

showsPrec :: Int -> GenRequest rw mt a -> ShowS #

show :: GenRequest rw mt a -> String #

showList :: [GenRequest rw mt a] -> ShowS #

Hashable (GenRequest rw mt a) Source # 
Instance details

Defined in GitHub.Data.Request

Methods

hashWithSalt :: Int -> GenRequest rw mt a -> Int #

hash :: GenRequest rw mt a -> Int #

(ParseResponse mt req, res ~ Either Error req, rw ~ RO) => GitHubRO (GenRequest mt rw req) (IO res) Source # 
Instance details

Defined in GitHub.Request

Methods

githubImpl' :: GenRequest mt rw req -> IO res

(ParseResponse mt req, res ~ Either Error req) => GitHubRW (GenRequest mt rw req) (IO res) Source # 
Instance details

Defined in GitHub.Request

Methods

githubImpl :: AuthMethod am => am -> GenRequest mt rw req -> IO res

Smart constructors

Auxiliary types

data RW Source #

Type used as with DataKinds to tag whether requests need authentication or aren't read-only.

Constructors

RO

Read-only, doesn't necessarily requires authentication

RA

Read authenticated

RW

Read-write, requires authentication

Instances
Bounded RW Source # 
Instance details

Defined in GitHub.Data.Request

Methods

minBound :: RW #

maxBound :: RW #

Enum RW Source # 
Instance details

Defined in GitHub.Data.Request

Methods

succ :: RW -> RW #

pred :: RW -> RW #

toEnum :: Int -> RW #

fromEnum :: RW -> Int #

enumFrom :: RW -> [RW] #

enumFromThen :: RW -> RW -> [RW] #

enumFromTo :: RW -> RW -> [RW] #

enumFromThenTo :: RW -> RW -> RW -> [RW] #

Eq RW Source # 
Instance details

Defined in GitHub.Data.Request

Methods

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

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

Data RW Source # 
Instance details

Defined in GitHub.Data.Request

Methods

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

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

toConstr :: RW -> Constr #

dataTypeOf :: RW -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RW Source # 
Instance details

Defined in GitHub.Data.Request

Methods

compare :: RW -> RW -> Ordering #

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

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

(>) :: RW -> RW -> Bool #

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

max :: RW -> RW -> RW #

min :: RW -> RW -> RW #

Read RW Source # 
Instance details

Defined in GitHub.Data.Request

Show RW Source # 
Instance details

Defined in GitHub.Data.Request

Methods

showsPrec :: Int -> RW -> ShowS #

show :: RW -> String #

showList :: [RW] -> ShowS #

Generic RW Source # 
Instance details

Defined in GitHub.Data.Request

Associated Types

type Rep RW :: Type -> Type #

Methods

from :: RW -> Rep RW x #

to :: Rep RW x -> RW #

type Rep RW Source # 
Instance details

Defined in GitHub.Data.Request

type Rep RW = D1 (MetaData "RW" "GitHub.Data.Request" "github-0.26-NGv9yMkIfb3ssAFkCPufN" False) (C1 (MetaCons "RO" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "RA" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RW" PrefixI False) (U1 :: Type -> Type)))

data CommandMethod Source #

Http method of requests with body.

Constructors

Post 
Patch 
Put 
Delete 
Instances
Bounded CommandMethod Source # 
Instance details

Defined in GitHub.Data.Request

Enum CommandMethod Source # 
Instance details

Defined in GitHub.Data.Request

Eq CommandMethod Source # 
Instance details

Defined in GitHub.Data.Request

Data CommandMethod Source # 
Instance details

Defined in GitHub.Data.Request

Methods

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

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

toConstr :: CommandMethod -> Constr #

dataTypeOf :: CommandMethod -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CommandMethod Source # 
Instance details

Defined in GitHub.Data.Request

Read CommandMethod Source # 
Instance details

Defined in GitHub.Data.Request

Show CommandMethod Source # 
Instance details

Defined in GitHub.Data.Request

Generic CommandMethod Source # 
Instance details

Defined in GitHub.Data.Request

Associated Types

type Rep CommandMethod :: Type -> Type #

Hashable CommandMethod Source # 
Instance details

Defined in GitHub.Data.Request

type Rep CommandMethod Source # 
Instance details

Defined in GitHub.Data.Request

type Rep CommandMethod = D1 (MetaData "CommandMethod" "GitHub.Data.Request" "github-0.26-NGv9yMkIfb3ssAFkCPufN" False) ((C1 (MetaCons "Post" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Patch" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Put" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Delete" PrefixI False) (U1 :: Type -> Type)))

data FetchCount Source #

PagedQuery returns just some results, using this data we can specify how many pages we want to fetch.

Constructors

FetchAtLeast !Word 
FetchAll 
Instances
Eq FetchCount Source # 
Instance details

Defined in GitHub.Data.Request

Num FetchCount Source #

This instance is there mostly for fromInteger.

Instance details

Defined in GitHub.Data.Request

Ord FetchCount Source # 
Instance details

Defined in GitHub.Data.Request

Read FetchCount Source # 
Instance details

Defined in GitHub.Data.Request

Show FetchCount Source # 
Instance details

Defined in GitHub.Data.Request

Generic FetchCount Source # 
Instance details

Defined in GitHub.Data.Request

Associated Types

type Rep FetchCount :: Type -> Type #

Hashable FetchCount Source # 
Instance details

Defined in GitHub.Data.Request

Binary FetchCount Source # 
Instance details

Defined in GitHub.Data.Request

NFData FetchCount Source # 
Instance details

Defined in GitHub.Data.Request

Methods

rnf :: FetchCount -> () #

type Rep FetchCount Source # 
Instance details

Defined in GitHub.Data.Request

type Rep FetchCount = D1 (MetaData "FetchCount" "GitHub.Data.Request" "github-0.26-NGv9yMkIfb3ssAFkCPufN" False) (C1 (MetaCons "FetchAtLeast" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word)) :+: C1 (MetaCons "FetchAll" PrefixI False) (U1 :: Type -> Type))

data MediaType a Source #

Constructors

MtJSON
application/vnd.github.v3+json
MtRaw

application/vnd.github.v3.raw https://developer.github.com/v3/media/#raw-1

MtDiff

application/vnd.github.v3.diff https://developer.github.com/v3/media/#diff

MtPatch

application/vnd.github.v3.patch https://developer.github.com/v3/media/#patch

MtSha

application/vnd.github.v3.sha https://developer.github.com/v3/media/#sha

MtStar

application/vnd.github.v3.star+json https://developer.github.com/v3/activity/starring/#alternative-response-with-star-creation-timestamps-1

MtRedirect

https://developer.github.com/v3/repos/contents/#get-archive-link

MtStatus

Parse status

MtUnit

Always succeeds

MtPreview a

Some other (preview) type; this is an extension point.

Instances
Eq a => Eq (MediaType a) Source # 
Instance details

Defined in GitHub.Data.Request

Methods

(==) :: MediaType a -> MediaType a -> Bool #

(/=) :: MediaType a -> MediaType a -> Bool #

Data a => Data (MediaType a) Source # 
Instance details

Defined in GitHub.Data.Request

Methods

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

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

toConstr :: MediaType a -> Constr #

dataTypeOf :: MediaType a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (MediaType a) Source # 
Instance details

Defined in GitHub.Data.Request

Read a => Read (MediaType a) Source # 
Instance details

Defined in GitHub.Data.Request

Show a => Show (MediaType a) Source # 
Instance details

Defined in GitHub.Data.Request

Generic (MediaType a) Source # 
Instance details

Defined in GitHub.Data.Request

Associated Types

type Rep (MediaType a) :: Type -> Type #

Methods

from :: MediaType a -> Rep (MediaType a) x #

to :: Rep (MediaType a) x -> MediaType a #

type Rep (MediaType a) Source # 
Instance details

Defined in GitHub.Data.Request

type Rep (MediaType a) = D1 (MetaData "MediaType" "GitHub.Data.Request" "github-0.26-NGv9yMkIfb3ssAFkCPufN" False) (((C1 (MetaCons "MtJSON" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MtRaw" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "MtDiff" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "MtPatch" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MtSha" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "MtStar" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MtRedirect" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "MtStatus" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "MtUnit" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MtPreview" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))))))

type Paths = [Text] Source #

class IsPathPart a where Source #

Methods

toPathPart :: a -> Text Source #

Instances
IsPathPart IssueNumber Source # 
Instance details

Defined in GitHub.Data.Request

IsPathPart ArchiveFormat Source # 
Instance details

Defined in GitHub.Data.Repos

IsPathPart (Name a) Source # 
Instance details

Defined in GitHub.Data.Request

Methods

toPathPart :: Name a -> Text Source #

IsPathPart (Id a) Source # 
Instance details

Defined in GitHub.Data.Request

Methods

toPathPart :: Id a -> Text Source #

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

Request query string

type Count = Int Source #

Count of elements