| 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 = singleton- data Request (k :: RW) a where
- 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
- RedirectQuery :: SimpleRequest k () -> Request k URI
- data CommandMethod a where
- Post :: CommandMethod a
- Patch :: CommandMethod a
- Put :: CommandMethod a
- Put' :: CommandMethod ()
- Delete :: CommandMethod ()
- toMethod :: CommandMethod a -> Method
- type Paths = [Text]
- type QueryString = [(ByteString, Maybe ByteString)]
- executeRequest :: Auth -> Request k a -> IO (Either Error a)
- executeRequestWithMgr :: Manager -> Auth -> Request k a -> IO (Either Error a)
- executeRequest' :: Request RO a -> IO (Either Error a)
- executeRequestWithMgr' :: Manager -> Request RO a -> IO (Either Error a)
- executeRequestMaybe :: Maybe Auth -> Request RO a -> IO (Either Error a)
- unsafeDropAuthRequirements :: Request k' a -> Request k a
- makeHttpRequest :: MonadThrow m => Maybe Auth -> Request k a -> m Request
- makeHttpSimpleRequest :: MonadThrow m => Maybe Auth -> SimpleRequest k a -> m Request
- parseResponse :: (FromJSON a, MonadError Error m) => Response ByteString -> m a
- parseStatus :: MonadError Error m => StatusMap a -> Status -> m a
- getNextUrl :: Response a -> Maybe URI
- performPagedRequest :: forall a m. (FromJSON a, Semigroup a, MonadCatch m, MonadError Error m) => (Request -> m (Response ByteString)) -> (a -> Bool) -> Request -> m a
Types
data Request (k :: RW) a where Source #
Github request data type.
kdescribes whether authentication is required. It's required for non-GETrequests.ais the result type
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 | |
| RedirectQuery :: SimpleRequest k () -> Request k URI |
data CommandMethod a where Source #
Http method of requests with body.
Constructors
| Post :: CommandMethod a | |
| Patch :: CommandMethod a | |
| Put :: CommandMethod a | |
| Put' :: CommandMethod () | |
| Delete :: CommandMethod () |
Instances
| Eq (CommandMethod a) Source # | |
| Ord (CommandMethod a) Source # | |
| Show (CommandMethod a) Source # | |
| Hashable (CommandMethod a) Source # | |
toMethod :: CommandMethod a -> Method Source #
type QueryString = [(ByteString, Maybe ByteString)] Source #
Request query string
Request execution in IO
executeRequestWithMgr :: Manager -> Auth -> Request k a -> IO (Either Error a) Source #
Like executeRequest but with provided Manager.
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 #
makeHttpSimpleRequest :: MonadThrow m => Maybe Auth -> SimpleRequest k a -> m Request Source #
parseResponse :: (FromJSON a, MonadError Error m) => Response ByteString -> m a Source #
Parse API response.
parseResponse ::FromJSONa =>ResponseByteString->EitherErrora
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
| :: (FromJSON a, Semigroup a, MonadCatch m, MonadError Error m) | |
| => (Request -> m (Response ByteString)) |
|
| -> (a -> Bool) | predicate to continue iteration |
| -> Request | initial request |
| -> m a |