module Network.Discord.Rest.Prelude where
import Control.Concurrent (threadDelay)
import Data.Version (showVersion)
import Control.Lens
import Data.Aeson
import Data.ByteString.Char8 (pack)
import Data.Default
import Data.Hashable
import Data.Time.Clock.POSIX
import Network.Wreq
import System.Log.Logger
import qualified Control.Monad.State as St
import Network.Discord.Types
import Paths_discord_hs (version)
readInteger :: String -> Integer
readInteger = read
baseURL :: String
baseURL = "https://discordapp.com/api/v6"
baseRequest :: DiscordM Options
baseRequest = do
DiscordState {getClient=client} <- St.get
return $ defaults
& header "Authorization" .~ [pack . show $ getAuth client]
& header "User-Agent" .~
[pack $ "DiscordBot (https://github.com/jano017/Discord.hs,"
++ showVersion version
++ ")"]
& header "Content-Type" .~ ["application/json"]
class RateLimit a where
getRateLimit :: a -> DiscordM (Maybe Int)
setRateLimit :: a -> Int -> DiscordM ()
waitRateLimit :: a -> DiscordM ()
waitRateLimit endpoint = do
rl <- getRateLimit endpoint
case rl of
Nothing -> return ()
Just a -> do
now <- St.liftIO (fmap round getPOSIXTime :: IO Int)
St.liftIO $ do
infoM "Discord-hs.Rest" "Waiting for rate limit to reset..."
threadDelay $ 1000000 * (a now)
putStrLn "Done"
return ()
class DoFetch a where
doFetch :: a -> DiscordM Fetched
data Fetchable = forall a. (DoFetch a, Hashable a) => Fetch a
instance DoFetch Fetchable where
doFetch (Fetch a) = doFetch a
instance Hashable Fetchable where
hashWithSalt s (Fetch a) = hashWithSalt s a
instance Eq Fetchable where
(Fetch a) == (Fetch b) = hash a == hash b
data Fetched = forall a. (FromJSON a) => SyncFetched a
data Range = Range { after :: Snowflake, before :: Snowflake, limit :: Int}
instance Default Range where
def = Range 0 18446744073709551615 100
toQueryString :: Range -> String
toQueryString (Range a b l) =
"after=" ++ show a ++ "&before=" ++ show b ++ "&limit=" ++ show l