| License | BSD-3-Clause | 
|---|---|
| Maintainer | Oleg Grenrus <oleg.grenrus@iki.fi> | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
GitHub.Request
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 = singletonSynopsis
- type Request = GenRequest MtJSON
- data GenRequest (mt :: MediaType *) (rw :: RW) a where- Query :: Paths -> QueryString -> GenRequest mt rw a
- PagedQuery :: Paths -> QueryString -> FetchCount -> GenRequest mt rw (Vector a)
- Command :: CommandMethod -> Paths -> ByteString -> GenRequest mt RW a
 
- data CommandMethod
- toMethod :: CommandMethod -> Method
- type Paths = [Text]
- type QueryString = [(ByteString, Maybe ByteString)]
- executeRequest :: (AuthMethod am, ParseResponse mt a) => am -> GenRequest mt rw a -> IO (Either Error a)
- executeRequestWithMgr :: (AuthMethod am, ParseResponse mt a) => Manager -> am -> GenRequest mt rw a -> IO (Either Error a)
- executeRequest' :: ParseResponse mt a => GenRequest mt RO a -> IO (Either Error a)
- executeRequestWithMgr' :: ParseResponse mt a => Manager -> GenRequest mt RO a -> IO (Either Error a)
- executeRequestMaybe :: (AuthMethod am, ParseResponse mt a) => Maybe am -> GenRequest mt RO a -> IO (Either Error a)
- unsafeDropAuthRequirements :: GenRequest mt rw' a -> GenRequest mt rw a
- class Accept (mt :: MediaType *) where- contentType :: Tagged mt ByteString
- modifyRequest :: Tagged mt (Request -> Request)
 
- class Accept mt => ParseResponse (mt :: MediaType *) a where- parseResponse :: MonadError Error m => Request -> Response ByteString -> Tagged mt (m a)
 
- makeHttpRequest :: forall am mt rw a m. (AuthMethod am, MonadThrow m, Accept mt) => Maybe am -> GenRequest mt rw a -> m Request
- parseStatus :: MonadError Error m => StatusMap a -> Status -> m a
- type StatusMap a = [(Int, a)]
- getNextUrl :: Response a -> Maybe URI
- performPagedRequest :: forall a m mt. (ParseResponse mt a, Semigroup a, MonadCatch m, MonadError Error m) => (Request -> m (Response ByteString)) -> (a -> Bool) -> Request -> Tagged mt (m a)
- parseResponseJSON :: (FromJSON a, MonadError Error m) => Response ByteString -> m a
- class PreviewAccept p where- previewContentType :: Tagged (MtPreview p) ByteString
- previewModifyRequest :: Tagged (MtPreview p) (Request -> Request)
 
- class PreviewAccept p => PreviewParseResponse p a where- previewParseResponse :: MonadError Error m => Request -> Response ByteString -> Tagged (MtPreview p) (m a)
 
Types
type Request = GenRequest MtJSON Source #
Most requests ask for JSON.
data GenRequest (mt :: MediaType *) (rw :: RW) a where Source #
Github request data type.
- rwdescribes whether authentication is required. It's required for non-- GETrequests.
- mtdescribes the media type, i.e. how the response should be interpreted.
- ais the result type
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 # | |
| 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 # | |
| 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 # | |
| 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 # | |
| Defined in GitHub.Data.Request | |
data CommandMethod Source #
Http method of requests with body.
Instances
toMethod :: CommandMethod -> Method 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 #
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
Methods
contentType :: Tagged mt ByteString Source #
Instances
class Accept mt => ParseResponse (mt :: MediaType *) a where Source #
Methods
parseResponse :: MonadError Error m => Request -> Response ByteString -> Tagged mt (m a) Source #
Instances
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.
- for PagedQuery, the initial request is created.
- for Status, theRequestfor underlyingRequestis created, status checking is modifying accordingly.
parseStatus :: MonadError Error m => StatusMap a -> Status -> m a Source #
getNextUrl :: Response a -> Maybe URI Source #
Query Link header with rel=next from the request headers.
Arguments
| :: (ParseResponse mt a, Semigroup a, MonadCatch m, MonadError Error m) | |
| => (Request -> m (Response ByteString)) | 
 | 
| -> (a -> Bool) | predicate to continue iteration | 
| -> Request | initial request | 
| -> Tagged mt (m a) | 
parseResponseJSON :: (FromJSON a, MonadError Error m) => Response ByteString -> m a Source #
Parse API response.
parseResponse ::FromJSONa =>ResponseByteString->EitherErrora
Preview
class PreviewAccept p where Source #
Minimal complete definition
Methods
previewContentType :: Tagged (MtPreview p) ByteString Source #
previewModifyRequest :: Tagged (MtPreview p) (Request -> Request) Source #
class PreviewAccept p => PreviewParseResponse p a where Source #
Methods
previewParseResponse :: MonadError Error m => Request -> Response ByteString -> Tagged (MtPreview p) (m a) Source #