github-0.17.0: 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

data Request k a where Source #

Github request data type.

  • k describes whether authentication is required. It's required for non-GET requests.
  • a is the result type

Note: Request is not Functor on purpose.

Constructors

SimpleQuery :: FromJSON a => SimpleRequest k a -> Request k a 
StatusQuery :: StatusMap a -> SimpleRequest k () -> Request k a 
HeaderQuery :: FromJSON a => RequestHeaders -> SimpleRequest k a -> Request k a 

Instances

Eq a => Eq (Request k a) Source # 

Methods

(==) :: Request k a -> Request k a -> Bool #

(/=) :: Request k a -> Request k a -> Bool #

Ord a => Ord (Request k a) Source # 

Methods

compare :: Request k a -> Request k a -> Ordering #

(<) :: Request k a -> Request k a -> Bool #

(<=) :: Request k a -> Request k a -> Bool #

(>) :: Request k a -> Request k a -> Bool #

(>=) :: Request k a -> Request k a -> Bool #

max :: Request k a -> Request k a -> Request k a #

min :: Request k a -> Request k a -> Request k a #

Show (Request k a) Source # 

Methods

showsPrec :: Int -> Request k a -> ShowS #

show :: Request k a -> String #

showList :: [Request k a] -> ShowS #

Hashable (Request k a) Source # 

Methods

hashWithSalt :: Int -> Request k a -> Int #

hash :: Request k a -> Int #

type Paths = [Text] Source #

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

Request query string

Request execution in IO

executeRequest :: Auth -> Request k a -> IO (Either Error a) Source #

Execute Request in IO

executeRequest' :: Request RO a -> IO (Either Error a) Source #

Like executeRequest but without authentication.

executeRequestWithMgr' :: Manager -> Request RO a -> IO (Either Error a) Source #

Like executeRequestWithMgr but without authentication.

executeRequestMaybe :: Maybe Auth -> Request RO a -> IO (Either Error a) Source #

Helper for picking between executeRequest and executeRequest'.

The use is discouraged.

unsafeDropAuthRequirements :: Request k' a -> Request k a Source #

Partial function to drop authentication need.

Helpers

makeHttpRequest :: MonadThrow m => Maybe Auth -> Request k a -> m Request Source #

Create http-client Request.

parseResponse :: Maybe Auth -> Request k a -> Maybe Request

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

Parse API response.

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

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

Helper for handling of RequestStatus.

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

getNextUrl :: Response a -> Maybe URI Source #

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

performPagedRequest Source #

Arguments

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

httpLbs analogue

-> (a -> Bool)

predicate to continue iteration

-> Request

initial request

-> m a 

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

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