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
{ Limits -> Int
limitsMax :: !Int
, Limits -> Int
limitsRemaining :: !Int
, Limits -> SystemTime
limitsReset :: !SystemTime
}
deriving (Int -> Limits -> ShowS
[Limits] -> ShowS
Limits -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Limits] -> ShowS
$cshowList :: [Limits] -> ShowS
show :: Limits -> String
$cshow :: Limits -> String
showsPrec :: Int -> Limits -> ShowS
$cshowsPrec :: Int -> Limits -> ShowS
Show, Typeable, Limits -> Limits -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Limits -> Limits -> Bool
$c/= :: Limits -> Limits -> Bool
== :: Limits -> Limits -> Bool
$c== :: Limits -> Limits -> Bool
Eq, Eq Limits
Limits -> Limits -> Bool
Limits -> Limits -> Ordering
Limits -> Limits -> Limits
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Limits -> Limits -> Limits
$cmin :: Limits -> Limits -> Limits
max :: Limits -> Limits -> Limits
$cmax :: Limits -> Limits -> Limits
>= :: Limits -> Limits -> Bool
$c>= :: Limits -> Limits -> Bool
> :: Limits -> Limits -> Bool
$c> :: Limits -> Limits -> Bool
<= :: Limits -> Limits -> Bool
$c<= :: Limits -> Limits -> Bool
< :: Limits -> Limits -> Bool
$c< :: Limits -> Limits -> Bool
compare :: Limits -> Limits -> Ordering
$ccompare :: Limits -> Limits -> Ordering
Ord, forall x. Rep Limits x -> Limits
forall x. Limits -> Rep Limits x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Limits x -> Limits
$cfrom :: forall x. Limits -> Rep Limits x
Generic)
instance NFData Limits where rnf :: Limits -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary Limits
instance FromJSON Limits where
parseJSON :: Value -> Parser Limits
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Limits" forall a b. (a -> b) -> a -> b
$ \Object
obj -> Int -> Int -> SystemTime -> Limits
Limits
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"limit"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"remaining"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Int64
t -> Int64 -> Word32 -> SystemTime
MkSystemTime Int64
t Word32
0) (Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"reset")
data RateLimit = RateLimit
{ RateLimit -> Limits
rateLimitCore :: Limits
, RateLimit -> Limits
rateLimitSearch :: Limits
, RateLimit -> Limits
rateLimitGraphQL :: Limits
}
deriving (Int -> RateLimit -> ShowS
[RateLimit] -> ShowS
RateLimit -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RateLimit] -> ShowS
$cshowList :: [RateLimit] -> ShowS
show :: RateLimit -> String
$cshow :: RateLimit -> String
showsPrec :: Int -> RateLimit -> ShowS
$cshowsPrec :: Int -> RateLimit -> ShowS
Show, Typeable, RateLimit -> RateLimit -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RateLimit -> RateLimit -> Bool
$c/= :: RateLimit -> RateLimit -> Bool
== :: RateLimit -> RateLimit -> Bool
$c== :: RateLimit -> RateLimit -> Bool
Eq, Eq RateLimit
RateLimit -> RateLimit -> Bool
RateLimit -> RateLimit -> Ordering
RateLimit -> RateLimit -> RateLimit
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RateLimit -> RateLimit -> RateLimit
$cmin :: RateLimit -> RateLimit -> RateLimit
max :: RateLimit -> RateLimit -> RateLimit
$cmax :: RateLimit -> RateLimit -> RateLimit
>= :: RateLimit -> RateLimit -> Bool
$c>= :: RateLimit -> RateLimit -> Bool
> :: RateLimit -> RateLimit -> Bool
$c> :: RateLimit -> RateLimit -> Bool
<= :: RateLimit -> RateLimit -> Bool
$c<= :: RateLimit -> RateLimit -> Bool
< :: RateLimit -> RateLimit -> Bool
$c< :: RateLimit -> RateLimit -> Bool
compare :: RateLimit -> RateLimit -> Ordering
$ccompare :: RateLimit -> RateLimit -> Ordering
Ord, forall x. Rep RateLimit x -> RateLimit
forall x. RateLimit -> Rep RateLimit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RateLimit x -> RateLimit
$cfrom :: forall x. RateLimit -> Rep RateLimit x
Generic)
instance NFData RateLimit where rnf :: RateLimit -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary RateLimit
instance FromJSON RateLimit where
parseJSON :: Value -> Parser RateLimit
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"RateLimit" forall a b. (a -> b) -> a -> b
$ \Object
obj -> do
Object
resources <- Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"resources"
Limits -> Limits -> Limits -> RateLimit
RateLimit
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
resources forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"core"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
resources forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"search"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
resources forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"graphql"
limitsFromHttpResponse :: HTTP.Response a -> Maybe Limits
limitsFromHttpResponse :: forall a. Response a -> Maybe Limits
limitsFromHttpResponse Response a
res = do
let hdrs :: ResponseHeaders
hdrs = forall body. Response body -> ResponseHeaders
HTTP.responseHeaders Response a
res
Int
m <- forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup HeaderName
"X-RateLimit-Limit" ResponseHeaders
hdrs forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. Num a => ByteString -> Maybe a
readIntegral
Int
r <- forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup HeaderName
"X-RateLimit-Remaining" ResponseHeaders
hdrs forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. Num a => ByteString -> Maybe a
readIntegral
Int64
t <- forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup HeaderName
"X-RateLimit-Reset" ResponseHeaders
hdrs forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. Num a => ByteString -> Maybe a
readIntegral
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Int -> SystemTime -> Limits
Limits Int
m Int
r (Int64 -> Word32 -> SystemTime
MkSystemTime Int64
t Word32
0))
where
readIntegral :: Num a => BS8.ByteString -> Maybe a
readIntegral :: forall a. Num a => ByteString -> Maybe a
readIntegral ByteString
bs = case ByteString -> Maybe (Int, ByteString)
BS8.readInt ByteString
bs of
Just (Int
n, ByteString
bs') | ByteString -> Bool
BS8.null ByteString
bs' -> forall a. a -> Maybe a
Just (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n)
Maybe (Int, ByteString)
_ -> forall a. Maybe a
Nothing