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

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

GitHub.Request

Contents

Description

This module provides data types and helper methods, which makes possible to build alternative API request intepreters in addition to provided IO functions.

Simple example using operational package. See samples/Operational/Operational.hs

type GithubMonad a = Program (GH.Request 'False) a

-- | Intepret GithubMonad value into IO
runMonad :: Manager -> GH.Auth -> GithubMonad a -> ExceptT GH.Error IO a
runMonad mgr auth m = case view m of
   Return a   -> return a
   req :>>= k -> do
       b <- ExceptT $ GH.executeRequestWithMgr mgr auth req
       runMonad mgr auth (k b)

-- | Lift request into Monad
githubRequest :: GH.Request 'False a -> GithubMonad a
githubRequest = singleton
Synopsis

Types

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 :: Paths -> QueryString -> FetchCount -> GenRequest mt rw (Vector 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 #

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.22-CooOCEhqNBO2WVzKDc0UNo" 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)))

type Paths = [Text] Source #

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

Request query string

Request execution in IO

executeRequest :: (AuthMethod am, ParseResponse mt a) => am -> GenRequest mt rw a -> IO (Either Error a) Source #

Execute Request in IO

executeRequestWithMgr :: (AuthMethod am, ParseResponse mt a) => Manager -> am -> GenRequest mt rw a -> IO (Either Error a) Source #

Like executeRequest but with provided Manager.

executeRequest' :: ParseResponse mt a => GenRequest mt RO a -> IO (Either Error a) Source #

Like executeRequest but without authentication.

executeRequestWithMgr' :: ParseResponse mt a => Manager -> GenRequest mt RO a -> IO (Either Error a) Source #

Like executeRequestWithMgr but without authentication.

executeRequestMaybe :: (AuthMethod am, ParseResponse mt a) => Maybe am -> GenRequest mt RO a -> IO (Either Error a) Source #

Helper for picking between executeRequest and executeRequest'.

The use is discouraged.

unsafeDropAuthRequirements :: GenRequest mt rw' a -> GenRequest mt rw a Source #

Partial function to drop authentication need.

Helpers

class Accept (mt :: MediaType *) where Source #

Minimal complete definition

Nothing

Instances
Accept (MtJSON :: MediaType Type) Source # 
Instance details

Defined in GitHub.Request

Accept (MtRaw :: MediaType Type) Source # 
Instance details

Defined in GitHub.Request

Accept (MtDiff :: MediaType Type) Source # 
Instance details

Defined in GitHub.Request

Accept (MtPatch :: MediaType Type) Source # 
Instance details

Defined in GitHub.Request

Accept (MtSha :: MediaType Type) Source # 
Instance details

Defined in GitHub.Request

Accept (MtStar :: MediaType Type) Source # 
Instance details

Defined in GitHub.Request

Accept (MtRedirect :: MediaType Type) Source # 
Instance details

Defined in GitHub.Request

Accept (MtStatus :: MediaType Type) Source # 
Instance details

Defined in GitHub.Request

Accept (MtUnit :: MediaType Type) Source #

Note: we don't ignore response status.

We only accept any response body.

Instance details

Defined in GitHub.Request

PreviewAccept p => Accept (MtPreview p) Source # 
Instance details

Defined in GitHub.Request

class Accept mt => ParseResponse (mt :: MediaType *) a where Source #

Instances
FromJSON a => ParseResponse (MtJSON :: MediaType Type) a Source # 
Instance details

Defined in GitHub.Request

a ~ ByteString => ParseResponse (MtRaw :: MediaType Type) a Source # 
Instance details

Defined in GitHub.Request

a ~ ByteString => ParseResponse (MtDiff :: MediaType Type) a Source # 
Instance details

Defined in GitHub.Request

a ~ ByteString => ParseResponse (MtPatch :: MediaType Type) a Source # 
Instance details

Defined in GitHub.Request

a ~ ByteString => ParseResponse (MtSha :: MediaType Type) a Source # 
Instance details

Defined in GitHub.Request

FromJSON a => ParseResponse (MtStar :: MediaType Type) a Source # 
Instance details

Defined in GitHub.Request

b ~ URI => ParseResponse (MtRedirect :: MediaType Type) b Source # 
Instance details

Defined in GitHub.Request

HasStatusMap a => ParseResponse (MtStatus :: MediaType Type) a Source # 
Instance details

Defined in GitHub.Request

a ~ () => ParseResponse (MtUnit :: MediaType Type) a Source # 
Instance details

Defined in GitHub.Request

PreviewParseResponse p a => ParseResponse (MtPreview p) a Source # 
Instance details

Defined in GitHub.Request

makeHttpRequest :: forall am mt rw a m. (AuthMethod am, MonadThrow m, Accept mt) => Maybe am -> GenRequest mt rw a -> m Request Source #

Create http-client Request.

parseStatus :: MonadError Error m => StatusMap a -> Status -> m a Source #

Helper for handling of RequestStatus.

parseStatus :: StatusMap a -> Status -> Either Error a

type StatusMap a = [(Int, a)] Source #

getNextUrl :: Response a -> Maybe URI Source #

Query Link header with rel=next from the request headers.

performPagedRequest Source #

Arguments

:: (ParseResponse mt a, Semigroup a, MonadCatch m, MonadError Error m) 
=> (Request -> m (Response ByteString))

httpLbs analogue

-> (a -> Bool)

predicate to continue iteration

-> Request

initial request

-> Tagged mt (m a) 

Helper for making paginated requests. Responses, a are combined monoidally.

performPagedRequest :: (FromJSON a, Semigroup a)
                    => (Request -> ExceptT Error IO (Response ByteString))
                    -> (a -> Value)
                    -> Request
                    -> ExceptT Error IO a

parseResponseJSON :: (FromJSON a, MonadError Error m) => Response ByteString -> m a Source #

Parse API response.

parseResponse :: FromJSON a => Response ByteString -> Either Error a

Preview