Skip to content

Commit

Permalink
Add executeRequestWithMgrAndRes
Browse files Browse the repository at this point in the history
  • Loading branch information
phadej committed Dec 20, 2019
1 parent 2503b54 commit bbe378b
Show file tree
Hide file tree
Showing 8 changed files with 102 additions and 54 deletions.
6 changes: 6 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,12 @@ This reduces symbol bloat in the library.
[#409](https://github.com/phadej/github/pull/409)
- Update `Repo`, `NewRepo` and `EditRepo` data types
[#407](https://github.com/phadej/github/pull/407)
- Add `executeRequestWithMgrAndRes`
[#421](https://github.com/phadej/github/pull/421)
- Add `limitsFromHttpResponse`
[#421](https://github.com/phadej/github/pull/421)
- Add label descriptions
[#418](https://github.com/phadej/github/pull/418)

## Changes for 0.23

Expand Down
2 changes: 1 addition & 1 deletion github.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -165,7 +165,7 @@ library
, deepseq >=1.3.0.2 && <1.5
, mtl >=2.1.3.1 && <2.2 || >=2.2.1 && <2.3
, text >=1.2.0.6 && <1.3
, time >=1.4 && <1.10
, time-compat >=1.9.2.2 && <1.10
, transformers >=0.3.0.0 && <0.6

-- other packages
Expand Down
34 changes: 23 additions & 11 deletions samples/Operational/Operational.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,23 +7,26 @@ module Main (main) where
import Common
import Prelude ()

import Control.Monad.Operational
import Control.Monad.Trans.Except (ExceptT (..), runExceptT)
import Network.HTTP.Client (Manager, newManager)
import Control.Exception (throw)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Operational (Program, ProgramViewT (..), singleton, view)
import Control.Monad.Trans.Except (ExceptT (..), runExceptT)
import Network.HTTP.Client (Manager, newManager, responseBody)

import qualified GitHub as GH
import qualified GitHub as GH

data R a where
R :: FromJSON a => GH.Request 'GH.RA a -> R a

type GithubMonad a = Program R a

runMonad :: Manager -> GH.Auth -> GithubMonad a -> ExceptT GH.Error IO a
runMonad :: GH.AuthMethod auth => Manager -> auth -> GithubMonad a -> ExceptT GH.Error IO a
runMonad mgr auth m = case view m of
Return a -> return a
R req :>>= k -> do
b <- ExceptT $ GH.executeRequestWithMgr mgr auth req
runMonad mgr auth (k b)
res <- ExceptT $ GH.executeRequestWithMgrAndRes mgr auth req
liftIO $ print $ GH.limitsFromHttpResponse res
runMonad mgr auth (k (responseBody res))

githubRequest :: FromJSON a => GH.Request 'GH.RA a -> GithubMonad a
githubRequest = singleton . R
Expand All @@ -33,9 +36,18 @@ main = GH.withOpenSSL $ do
manager <- newManager GH.tlsManagerSettings
auth' <- getAuth
case auth' of
Nothing -> return ()
Nothing -> do
(owner, rl) <- runExceptT (runMonad manager () script) >>= either throw return
print owner
print rl
Just auth -> do
owner <- runExceptT $ runMonad manager auth $ do
repo <- githubRequest $ GH.repositoryR "phadej" "github"
githubRequest $ GH.ownerInfoForR (GH.simpleOwnerLogin . GH.repoOwner $ repo)
(owner, rl) <- runExceptT (runMonad manager auth script) >>= either throw return
print owner
print rl

script :: Program R (GH.Owner, GH.Limits)
script = do
repo <- githubRequest $ GH.repositoryR "phadej" "github"
owner <- githubRequest $ GH.ownerInfoForR (GH.simpleOwnerLogin . GH.repoOwner $ repo)
rl <- githubRequest GH.rateLimitR
return (owner, GH.rateLimitCore rl)
6 changes: 6 additions & 0 deletions src/GitHub/Auth.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,12 +30,18 @@ instance Binary Auth
instance Hashable Auth

-- | A type class for different authentication methods
--
-- Note the '()' intance, which doee nothing, i.e. is unauthenticated.
class AuthMethod a where
-- | Custom API endpoint without trailing slash
endpoint :: a -> Maybe Text
-- | A function which sets authorisation on an HTTP request
setAuthRequest :: a -> HTTP.Request -> HTTP.Request

instance AuthMethod () where
endpoint _ = Nothing
setAuthRequest _ = id

instance AuthMethod Auth where
endpoint (BasicAuth _ _) = Nothing
endpoint (OAuth _) = Nothing
Expand Down
1 change: 0 additions & 1 deletion src/GitHub/Data/Deployments.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,6 @@ import Control.Arrow (second)
import Data.ByteString (ByteString)
import Data.Maybe (catMaybes)
import Data.Text (Text)
import Data.Time.Clock (UTCTime)
import Data.Vector (Vector)

import GitHub.Data.Definitions (SimpleUser)
Expand Down
31 changes: 27 additions & 4 deletions src/GitHub/Data/RateLimit.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,12 +8,17 @@ module GitHub.Data.RateLimit where
import GitHub.Internal.Prelude
import Prelude ()

import Data.Time.Clock.System.Compat (SystemTime (..))

import qualified Data.ByteString.Char8 as BS8
import qualified Network.HTTP.Client as HTTP

data Limits = Limits
{ limitsMax :: !Int
, limitsRemaining :: !Int
, limitsReset :: !Int -- TODO: change to proper type
, limitsReset :: !SystemTime
}
deriving (Show, Data, Typeable, Eq, Ord, Generic)
deriving (Show, {- Data, -} Typeable, Eq, Ord, Generic)

instance NFData Limits where rnf = genericRnf
instance Binary Limits
Expand All @@ -22,14 +27,14 @@ instance FromJSON Limits where
parseJSON = withObject "Limits" $ \obj -> Limits
<$> obj .: "limit"
<*> obj .: "remaining"
<*> obj .: "reset"
<*> fmap (\t -> MkSystemTime t 0) (obj .: "reset")

data RateLimit = RateLimit
{ rateLimitCore :: Limits
, rateLimitSearch :: Limits
, rateLimitGraphQL :: Limits
}
deriving (Show, Data, Typeable, Eq, Ord, Generic)
deriving (Show, {- Data, -} Typeable, Eq, Ord, Generic)

instance NFData RateLimit where rnf = genericRnf
instance Binary RateLimit
Expand All @@ -41,3 +46,21 @@ instance FromJSON RateLimit where
<$> resources .: "core"
<*> resources .: "search"
<*> resources .: "graphql"

-------------------------------------------------------------------------------
-- Extras
-------------------------------------------------------------------------------

-- | @since 0.24
limitsFromHttpResponse :: HTTP.Response a -> Maybe Limits
limitsFromHttpResponse res = do
let hdrs = HTTP.responseHeaders res
m <- lookup "X-RateLimit-Limit" hdrs >>= readIntegral
r <- lookup "X-RateLimit-Remaining" hdrs >>= readIntegral
t <- lookup "X-RateLimit-Reset" hdrs >>= readIntegral
return (Limits m r (MkSystemTime t 0))
where
readIntegral :: Num a => BS8.ByteString -> Maybe a
readIntegral bs = case BS8.readInt bs of
Just (n, bs') | BS8.null bs' -> Just (fromIntegral n)
_ -> Nothing
2 changes: 1 addition & 1 deletion src/GitHub/Internal/Prelude.hs
Original file line number Diff line number Diff line change
Expand Up @@ -53,7 +53,7 @@ import Data.Maybe (catMaybes)
import Data.Semigroup (Semigroup (..))
import Data.String (IsString (..))
import Data.Text (Text, pack, unpack)
import Data.Time (UTCTime)
import Data.Time.Compat (UTCTime)
import Data.Time.ISO8601 (formatISO8601)
import Data.Vector (Vector)
import Data.Vector.Instances ()
Expand Down
74 changes: 38 additions & 36 deletions src/GitHub/Request.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,6 +46,7 @@ module GitHub.Request (
-- * Request execution in IO
executeRequest,
executeRequestWithMgr,
executeRequestWithMgrAndRes,
executeRequest',
executeRequestWithMgr',
executeRequestMaybe,
Expand All @@ -66,7 +67,7 @@ module GitHub.Request (
-- | This always exist, independently of @openssl@ configuration flag.
-- They change accordingly, to make use of the library simpler.
withOpenSSL,
tlsManagerSettings,
tlsManagerSettings,
) where

import GitHub.Internal.Prelude
Expand Down Expand Up @@ -112,7 +113,7 @@ import qualified OpenSSL.Session as SSL
import qualified OpenSSL.X509.SystemStore as SSL
#endif

import GitHub.Auth (Auth, AuthMethod, endpoint, setAuthRequest)
import GitHub.Auth (AuthMethod, endpoint, setAuthRequest)
import GitHub.Data (Error (..))
import GitHub.Data.PullRequests (MergeResult (..))
import GitHub.Data.Request
Expand Down Expand Up @@ -206,33 +207,46 @@ lessFetchCount :: Int -> FetchCount -> Bool
lessFetchCount _ FetchAll = True
lessFetchCount i (FetchAtLeast j) = i < fromIntegral j


-- | Like 'executeRequest' but with provided 'Manager'.
executeRequestWithMgr
:: (AuthMethod am, ParseResponse mt a)
=> Manager
-> am
-> GenRequest mt rw a
-> IO (Either Error a)
executeRequestWithMgr mgr auth req = runExceptT $ do
executeRequestWithMgr mgr auth req =
fmap (fmap responseBody) (executeRequestWithMgrAndRes mgr auth req)

-- | Execute request and return the last received 'HTTP.Response'.
--
-- @since 0.24
executeRequestWithMgrAndRes
:: (AuthMethod am, ParseResponse mt a)
=> Manager
-> am
-> GenRequest mt rw a
-> IO (Either Error (HTTP.Response a))
executeRequestWithMgrAndRes mgr auth req = runExceptT $ do
httpReq <- makeHttpRequest (Just auth) req
performHttpReq httpReq req
where
httpLbs' :: HTTP.Request -> ExceptT Error IO (Response LBS.ByteString)
httpLbs' :: HTTP.Request -> ExceptT Error IO (HTTP.Response LBS.ByteString)
httpLbs' req' = lift (httpLbs req' mgr) `catch` onHttpException

performHttpReq :: forall rw mt b. ParseResponse mt b => HTTP.Request -> GenRequest mt rw b -> ExceptT Error IO b
performHttpReq :: forall rw mt b. ParseResponse mt b => HTTP.Request -> GenRequest mt rw b -> ExceptT Error IO (HTTP.Response b)
performHttpReq httpReq Query {} = do
res <- httpLbs' httpReq
unTagged (parseResponse httpReq res :: Tagged mt (ExceptT Error IO b))
(<$ res) <$> unTagged (parseResponse httpReq res :: Tagged mt (ExceptT Error IO b))

performHttpReq httpReq (PagedQuery _ _ l) =
unTagged (performPagedRequest httpLbs' predicate httpReq :: Tagged mt (ExceptT Error IO b))
unTagged (performPagedRequest httpLbs' predicate httpReq :: Tagged mt (ExceptT Error IO (HTTP.Response b)))
where
predicate v = lessFetchCount (V.length v) l

performHttpReq httpReq (Command _ _ _) = do
res <- httpLbs' httpReq
unTagged (parseResponse httpReq res :: Tagged mt (ExceptT Error IO b))
(<$ res) <$> unTagged (parseResponse httpReq res :: Tagged mt (ExceptT Error IO b))

-- | Like 'executeRequest' but without authentication.
executeRequest' :: ParseResponse mt a => GenRequest mt 'RO a -> IO (Either Error a)
Expand All @@ -246,21 +260,7 @@ executeRequestWithMgr'
=> Manager
-> GenRequest mt 'RO a
-> IO (Either Error a)
executeRequestWithMgr' mgr req = runExceptT $ do
httpReq <- makeHttpRequest (Nothing :: Maybe Auth) req
performHttpReq httpReq req
where
httpLbs' :: HTTP.Request -> ExceptT Error IO (Response LBS.ByteString)
httpLbs' req' = lift (httpLbs req' mgr) `catch` onHttpException

performHttpReq :: forall mt b. ParseResponse mt b => HTTP.Request -> GenRequest mt 'RO b -> ExceptT Error IO b
performHttpReq httpReq Query {} = do
res <- httpLbs' httpReq
unTagged (parseResponse httpReq res :: Tagged mt (ExceptT Error IO b))
performHttpReq httpReq (PagedQuery _ _ l) =
unTagged (performPagedRequest httpLbs' predicate httpReq :: Tagged mt (ExceptT Error IO b))
where
predicate v = lessFetchCount (V.length v) l
executeRequestWithMgr' mgr = executeRequestWithMgr mgr ()

-- | Helper for picking between 'executeRequest' and 'executeRequest''.
--
Expand Down Expand Up @@ -302,9 +302,9 @@ class Accept mt => ParseResponse (mt :: MediaType *) a where
-- | Parse API response.
--
-- @
-- parseResponse :: 'FromJSON' a => 'Response' 'LBS.ByteString' -> 'Either' 'Error' a
-- parseResponse :: 'FromJSON' a => 'HTTP.Response' 'LBS.ByteString' -> 'Either' 'Error' a
-- @
parseResponseJSON :: (FromJSON a, MonadError Error m) => Response LBS.ByteString -> m a
parseResponseJSON :: (FromJSON a, MonadError Error m) => HTTP.Response LBS.ByteString -> m a
parseResponseJSON res = case eitherDecode (responseBody res) of
Right x -> return x
Left err -> throwError . ParseError . T.pack $ err
Expand Down Expand Up @@ -349,9 +349,9 @@ instance b ~ URI => ParseResponse 'MtRedirect b where
-- | Helper for handling of 'RequestRedirect'.
--
-- @
-- parseRedirect :: 'Response' 'LBS.ByteString' -> 'Either' 'Error' a
-- parseRedirect :: 'HTTP.Response' 'LBS.ByteString' -> 'Either' 'Error' a
-- @
parseRedirect :: MonadError Error m => URI -> Response LBS.ByteString -> m URI
parseRedirect :: MonadError Error m => URI -> HTTP.Response LBS.ByteString -> m URI
parseRedirect originalUri rsp = do
let status = responseStatus rsp
when (statusCode status /= 302) $
Expand Down Expand Up @@ -501,7 +501,7 @@ makeHttpRequest auth r = case r of
setBody body req = req { requestBody = RequestBodyLBS body }

-- | Query @Link@ header with @rel=next@ from the request headers.
getNextUrl :: Response a -> Maybe URI
getNextUrl :: HTTP.Response a -> Maybe URI
getNextUrl req = do
linkHeader <- lookup "Link" (responseHeaders req)
links <- parseLinkHeaderBS linkHeader
Expand All @@ -516,33 +516,35 @@ getNextUrl req = do

-- | Helper for making paginated requests. Responses, @a@ are combined monoidally.
--
-- The result is wrapped in the last received 'HTTP.Response'.
--
-- @
-- performPagedRequest :: ('FromJSON' a, 'Semigroup' a)
-- => ('HTTP.Request' -> 'ExceptT' 'Error' 'IO' ('Response' 'LBS.ByteString'))
-- => ('HTTP.Request' -> 'ExceptT' 'Error' 'IO' ('HTTP.Response' 'LBS.ByteString'))
-- -> (a -> 'Bool')
-- -> 'HTTP.Request'
-- -> 'ExceptT' 'Error' 'IO' a
-- -> 'ExceptT' 'Error' 'IO' ('HTTP.Response' a)
-- @
performPagedRequest
:: forall a m mt. (ParseResponse mt a, Semigroup a, MonadCatch m, MonadError Error m)
=> (HTTP.Request -> m (Response LBS.ByteString)) -- ^ `httpLbs` analogue
-> (a -> Bool) -- ^ predicate to continue iteration
-> HTTP.Request -- ^ initial request
-> Tagged mt (m a)
=> (HTTP.Request -> m (HTTP.Response LBS.ByteString)) -- ^ `httpLbs` analogue
-> (a -> Bool) -- ^ predicate to continue iteration
-> HTTP.Request -- ^ initial request
-> Tagged mt (m (HTTP.Response a))
performPagedRequest httpLbs' predicate initReq = Tagged $ do
res <- httpLbs' initReq
m <- unTagged (parseResponse initReq res :: Tagged mt (m a))
go m res initReq
where
go :: a -> Response LBS.ByteString -> HTTP.Request -> m a
go :: a -> HTTP.Response LBS.ByteString -> HTTP.Request -> m (HTTP.Response a)
go acc res req =
case (predicate acc, getNextUrl res) of
(True, Just uri) -> do
req' <- HTTP.setUri req uri
res' <- httpLbs' req'
m <- unTagged (parseResponse req' res' :: Tagged mt (m a))
go (acc <> m) res' req'
(_, _) -> return acc
(_, _) -> return (acc <$ res)

-------------------------------------------------------------------------------
-- Internal
Expand Down

0 comments on commit bbe378b

Please sign in to comment.