{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeApplications #-}
module Network.Reddit.Types
(
RedditT
, runRedditT
, MonadReddit
, UserAgent(..)
, ClientSite
, Client(..)
, ClientState(..)
, readClientState
, WithData(..)
, RateLimits(..)
, readRateLimits
, AppType(..)
, AuthConfig(..)
, AccessToken(..)
, Token
, Code
, Scope(..)
, PasswordFlow(..)
, CodeFlow(..)
, ClientID
, ClientSecret
, TokenDuration(..)
, TokenManager(..)
, APIAction(..)
, Method(..)
, PathSegment
, module M
) where
import Conduit ( MonadUnliftIO )
import Control.Monad.Catch
( MonadCatch
, MonadThrow
)
import Control.Monad.Reader
import Data.Aeson
( (.:)
, (.:?)
, FromJSON(parseJSON)
, Options(constructorTagModifier)
, Value(String)
, defaultOptions
, genericParseJSON
, withObject
, withText
)
import qualified Data.ByteString.Char8 as C8
import Data.Char ( toLower )
import Data.Generics.Product ( HasField(field) )
import Data.Text ( Text )
import qualified Data.Text as T
import Data.Time
import Data.Time.Clock.POSIX
import GHC.Exts ( IsList(fromList) )
import GHC.Generics ( Generic )
import Lens.Micro
import Network.HTTP.Client ( BodyReader )
import Network.HTTP.Client.Conduit
( HasHttpManager(..)
, Manager
, Request
, Response
)
import Network.HTTP.Client.MultipartFormData ( Part )
import Network.HTTP.Types
( HeaderName
, ResponseHeaders
)
import Network.Reddit.Types.Internal as M
import Text.Read ( readMaybe )
import UnliftIO.IORef
import Web.FormUrlEncoded ( Form, ToForm(..) )
import Web.HttpApiData
( ToHttpApiData(toQueryParam)
, showTextData
)
newtype RedditT m a = RedditT (ReaderT Client m a)
deriving newtype ( a -> RedditT m b -> RedditT m a
(a -> b) -> RedditT m a -> RedditT m b
(forall a b. (a -> b) -> RedditT m a -> RedditT m b)
-> (forall a b. a -> RedditT m b -> RedditT m a)
-> Functor (RedditT m)
forall a b. a -> RedditT m b -> RedditT m a
forall a b. (a -> b) -> RedditT m a -> RedditT m b
forall (m :: * -> *) a b.
Functor m =>
a -> RedditT m b -> RedditT m a
forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> RedditT m a -> RedditT m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> RedditT m b -> RedditT m a
$c<$ :: forall (m :: * -> *) a b.
Functor m =>
a -> RedditT m b -> RedditT m a
fmap :: (a -> b) -> RedditT m a -> RedditT m b
$cfmap :: forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> RedditT m a -> RedditT m b
Functor, Functor (RedditT m)
a -> RedditT m a
Functor (RedditT m)
-> (forall a. a -> RedditT m a)
-> (forall a b. RedditT m (a -> b) -> RedditT m a -> RedditT m b)
-> (forall a b c.
(a -> b -> c) -> RedditT m a -> RedditT m b -> RedditT m c)
-> (forall a b. RedditT m a -> RedditT m b -> RedditT m b)
-> (forall a b. RedditT m a -> RedditT m b -> RedditT m a)
-> Applicative (RedditT m)
RedditT m a -> RedditT m b -> RedditT m b
RedditT m a -> RedditT m b -> RedditT m a
RedditT m (a -> b) -> RedditT m a -> RedditT m b
(a -> b -> c) -> RedditT m a -> RedditT m b -> RedditT m c
forall a. a -> RedditT m a
forall a b. RedditT m a -> RedditT m b -> RedditT m a
forall a b. RedditT m a -> RedditT m b -> RedditT m b
forall a b. RedditT m (a -> b) -> RedditT m a -> RedditT m b
forall a b c.
(a -> b -> c) -> RedditT m a -> RedditT m b -> RedditT m c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
forall (m :: * -> *). Applicative m => Functor (RedditT m)
forall (m :: * -> *) a. Applicative m => a -> RedditT m a
forall (m :: * -> *) a b.
Applicative m =>
RedditT m a -> RedditT m b -> RedditT m a
forall (m :: * -> *) a b.
Applicative m =>
RedditT m a -> RedditT m b -> RedditT m b
forall (m :: * -> *) a b.
Applicative m =>
RedditT m (a -> b) -> RedditT m a -> RedditT m b
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c) -> RedditT m a -> RedditT m b -> RedditT m c
<* :: RedditT m a -> RedditT m b -> RedditT m a
$c<* :: forall (m :: * -> *) a b.
Applicative m =>
RedditT m a -> RedditT m b -> RedditT m a
*> :: RedditT m a -> RedditT m b -> RedditT m b
$c*> :: forall (m :: * -> *) a b.
Applicative m =>
RedditT m a -> RedditT m b -> RedditT m b
liftA2 :: (a -> b -> c) -> RedditT m a -> RedditT m b -> RedditT m c
$cliftA2 :: forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c) -> RedditT m a -> RedditT m b -> RedditT m c
<*> :: RedditT m (a -> b) -> RedditT m a -> RedditT m b
$c<*> :: forall (m :: * -> *) a b.
Applicative m =>
RedditT m (a -> b) -> RedditT m a -> RedditT m b
pure :: a -> RedditT m a
$cpure :: forall (m :: * -> *) a. Applicative m => a -> RedditT m a
$cp1Applicative :: forall (m :: * -> *). Applicative m => Functor (RedditT m)
Applicative, Applicative (RedditT m)
a -> RedditT m a
Applicative (RedditT m)
-> (forall a b. RedditT m a -> (a -> RedditT m b) -> RedditT m b)
-> (forall a b. RedditT m a -> RedditT m b -> RedditT m b)
-> (forall a. a -> RedditT m a)
-> Monad (RedditT m)
RedditT m a -> (a -> RedditT m b) -> RedditT m b
RedditT m a -> RedditT m b -> RedditT m b
forall a. a -> RedditT m a
forall a b. RedditT m a -> RedditT m b -> RedditT m b
forall a b. RedditT m a -> (a -> RedditT m b) -> RedditT m b
forall (m :: * -> *). Monad m => Applicative (RedditT m)
forall (m :: * -> *) a. Monad m => a -> RedditT m a
forall (m :: * -> *) a b.
Monad m =>
RedditT m a -> RedditT m b -> RedditT m b
forall (m :: * -> *) a b.
Monad m =>
RedditT m a -> (a -> RedditT m b) -> RedditT m b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> RedditT m a
$creturn :: forall (m :: * -> *) a. Monad m => a -> RedditT m a
>> :: RedditT m a -> RedditT m b -> RedditT m b
$c>> :: forall (m :: * -> *) a b.
Monad m =>
RedditT m a -> RedditT m b -> RedditT m b
>>= :: RedditT m a -> (a -> RedditT m b) -> RedditT m b
$c>>= :: forall (m :: * -> *) a b.
Monad m =>
RedditT m a -> (a -> RedditT m b) -> RedditT m b
$cp1Monad :: forall (m :: * -> *). Monad m => Applicative (RedditT m)
Monad, Monad (RedditT m)
Monad (RedditT m)
-> (forall a. IO a -> RedditT m a) -> MonadIO (RedditT m)
IO a -> RedditT m a
forall a. IO a -> RedditT m a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
forall (m :: * -> *). MonadIO m => Monad (RedditT m)
forall (m :: * -> *) a. MonadIO m => IO a -> RedditT m a
liftIO :: IO a -> RedditT m a
$cliftIO :: forall (m :: * -> *) a. MonadIO m => IO a -> RedditT m a
$cp1MonadIO :: forall (m :: * -> *). MonadIO m => Monad (RedditT m)
MonadIO, MonadIO (RedditT m)
MonadIO (RedditT m)
-> (forall b.
((forall a. RedditT m a -> IO a) -> IO b) -> RedditT m b)
-> MonadUnliftIO (RedditT m)
((forall a. RedditT m a -> IO a) -> IO b) -> RedditT m b
forall b. ((forall a. RedditT m a -> IO a) -> IO b) -> RedditT m b
forall (m :: * -> *).
MonadIO m
-> (forall b. ((forall a. m a -> IO a) -> IO b) -> m b)
-> MonadUnliftIO m
forall (m :: * -> *). MonadUnliftIO m => MonadIO (RedditT m)
forall (m :: * -> *) b.
MonadUnliftIO m =>
((forall a. RedditT m a -> IO a) -> IO b) -> RedditT m b
withRunInIO :: ((forall a. RedditT m a -> IO a) -> IO b) -> RedditT m b
$cwithRunInIO :: forall (m :: * -> *) b.
MonadUnliftIO m =>
((forall a. RedditT m a -> IO a) -> IO b) -> RedditT m b
$cp1MonadUnliftIO :: forall (m :: * -> *). MonadUnliftIO m => MonadIO (RedditT m)
MonadUnliftIO
, MonadReader Client, Monad (RedditT m)
e -> RedditT m a
Monad (RedditT m)
-> (forall e a. Exception e => e -> RedditT m a)
-> MonadThrow (RedditT m)
forall e a. Exception e => e -> RedditT m a
forall (m :: * -> *).
Monad m -> (forall e a. Exception e => e -> m a) -> MonadThrow m
forall (m :: * -> *). MonadThrow m => Monad (RedditT m)
forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> RedditT m a
throwM :: e -> RedditT m a
$cthrowM :: forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> RedditT m a
$cp1MonadThrow :: forall (m :: * -> *). MonadThrow m => Monad (RedditT m)
MonadThrow, MonadThrow (RedditT m)
MonadThrow (RedditT m)
-> (forall e a.
Exception e =>
RedditT m a -> (e -> RedditT m a) -> RedditT m a)
-> MonadCatch (RedditT m)
RedditT m a -> (e -> RedditT m a) -> RedditT m a
forall e a.
Exception e =>
RedditT m a -> (e -> RedditT m a) -> RedditT m a
forall (m :: * -> *).
MonadThrow m
-> (forall e a. Exception e => m a -> (e -> m a) -> m a)
-> MonadCatch m
forall (m :: * -> *). MonadCatch m => MonadThrow (RedditT m)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
RedditT m a -> (e -> RedditT m a) -> RedditT m a
catch :: RedditT m a -> (e -> RedditT m a) -> RedditT m a
$ccatch :: forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
RedditT m a -> (e -> RedditT m a) -> RedditT m a
$cp1MonadCatch :: forall (m :: * -> *). MonadCatch m => MonadThrow (RedditT m)
MonadCatch )
runRedditT :: Client -> RedditT m a -> m a
runRedditT :: Client -> RedditT m a -> m a
runRedditT Client
c (RedditT ReaderT Client m a
x) = ReaderT Client m a -> Client -> m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT Client m a
x Client
c
type MonadReddit m =
(MonadUnliftIO m, MonadThrow m, MonadCatch m, MonadReader Client m)
data Client = Client
{ Client -> AuthConfig
authConfig :: AuthConfig
, Client -> Manager
manager :: Manager
, Client -> IORef ClientState
clientState :: IORef ClientState
, Client -> Maybe TokenManager
tokenManager :: Maybe TokenManager
}
deriving stock ( (forall x. Client -> Rep Client x)
-> (forall x. Rep Client x -> Client) -> Generic Client
forall x. Rep Client x -> Client
forall x. Client -> Rep Client x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Client x -> Client
$cfrom :: forall x. Client -> Rep Client x
Generic )
instance HasHttpManager Client where
getHttpManager :: Client -> Manager
getHttpManager Client { Manager
manager :: Manager
$sel:manager:Client :: Client -> Manager
manager } = Manager
manager
data ClientState = ClientState
{ ClientState -> AccessToken
accessToken :: AccessToken
, ClientState -> POSIXTime
tokenObtained :: POSIXTime
, ClientState -> Maybe RateLimits
limits :: Maybe RateLimits
}
deriving stock ( Int -> ClientState -> ShowS
[ClientState] -> ShowS
ClientState -> String
(Int -> ClientState -> ShowS)
-> (ClientState -> String)
-> ([ClientState] -> ShowS)
-> Show ClientState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClientState] -> ShowS
$cshowList :: [ClientState] -> ShowS
show :: ClientState -> String
$cshow :: ClientState -> String
showsPrec :: Int -> ClientState -> ShowS
$cshowsPrec :: Int -> ClientState -> ShowS
Show, ClientState -> ClientState -> Bool
(ClientState -> ClientState -> Bool)
-> (ClientState -> ClientState -> Bool) -> Eq ClientState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClientState -> ClientState -> Bool
$c/= :: ClientState -> ClientState -> Bool
== :: ClientState -> ClientState -> Bool
$c== :: ClientState -> ClientState -> Bool
Eq, (forall x. ClientState -> Rep ClientState x)
-> (forall x. Rep ClientState x -> ClientState)
-> Generic ClientState
forall x. Rep ClientState x -> ClientState
forall x. ClientState -> Rep ClientState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ClientState x -> ClientState
$cfrom :: forall x. ClientState -> Rep ClientState x
Generic )
readClientState :: MonadReddit m => Lens' ClientState a -> m a
readClientState :: Lens' ClientState a -> m a
readClientState Lens' ClientState a
l = (Client -> IORef ClientState) -> m (IORef ClientState)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Client
-> Getting (IORef ClientState) Client (IORef ClientState)
-> IORef ClientState
forall s a. s -> Getting a s a -> a
^. forall s t a b. HasField "clientState" s t a b => Lens s t a b
forall (field :: Symbol) s t a b.
HasField field s t a b =>
Lens s t a b
field @"clientState") m (IORef ClientState)
-> (IORef ClientState -> m ClientState) -> m ClientState
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IORef ClientState -> m ClientState
forall (m :: * -> *) a. MonadIO m => IORef a -> m a
readIORef m ClientState -> (ClientState -> a) -> m a
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (ClientState -> Getting a ClientState a -> a
forall s a. s -> Getting a s a -> a
^. Getting a ClientState a
Lens' ClientState a
l)
data UserAgent = UserAgent
{
UserAgent -> Text
platform :: Text
, UserAgent -> Text
appID :: Text
, UserAgent -> Text
version :: Text
, UserAgent -> Text
author :: Text
}
deriving stock ( Int -> UserAgent -> ShowS
[UserAgent] -> ShowS
UserAgent -> String
(Int -> UserAgent -> ShowS)
-> (UserAgent -> String)
-> ([UserAgent] -> ShowS)
-> Show UserAgent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UserAgent] -> ShowS
$cshowList :: [UserAgent] -> ShowS
show :: UserAgent -> String
$cshow :: UserAgent -> String
showsPrec :: Int -> UserAgent -> ShowS
$cshowsPrec :: Int -> UserAgent -> ShowS
Show, UserAgent -> UserAgent -> Bool
(UserAgent -> UserAgent -> Bool)
-> (UserAgent -> UserAgent -> Bool) -> Eq UserAgent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UserAgent -> UserAgent -> Bool
$c/= :: UserAgent -> UserAgent -> Bool
== :: UserAgent -> UserAgent -> Bool
$c== :: UserAgent -> UserAgent -> Bool
Eq, (forall x. UserAgent -> Rep UserAgent x)
-> (forall x. Rep UserAgent x -> UserAgent) -> Generic UserAgent
forall x. Rep UserAgent x -> UserAgent
forall x. UserAgent -> Rep UserAgent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UserAgent x -> UserAgent
$cfrom :: forall x. UserAgent -> Rep UserAgent x
Generic )
type ClientSite = Text
data RateLimits = RateLimits
{
RateLimits -> Integer
remaining :: Integer
, RateLimits -> Integer
used :: Integer
, RateLimits -> POSIXTime
reset :: POSIXTime
, RateLimits -> POSIXTime
nextRequest :: POSIXTime
}
deriving stock ( Int -> RateLimits -> ShowS
[RateLimits] -> ShowS
RateLimits -> String
(Int -> RateLimits -> ShowS)
-> (RateLimits -> String)
-> ([RateLimits] -> ShowS)
-> Show RateLimits
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RateLimits] -> ShowS
$cshowList :: [RateLimits] -> ShowS
show :: RateLimits -> String
$cshow :: RateLimits -> String
showsPrec :: Int -> RateLimits -> ShowS
$cshowsPrec :: Int -> RateLimits -> ShowS
Show, RateLimits -> RateLimits -> Bool
(RateLimits -> RateLimits -> Bool)
-> (RateLimits -> RateLimits -> Bool) -> Eq RateLimits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RateLimits -> RateLimits -> Bool
$c/= :: RateLimits -> RateLimits -> Bool
== :: RateLimits -> RateLimits -> Bool
$c== :: RateLimits -> RateLimits -> Bool
Eq, (forall x. RateLimits -> Rep RateLimits x)
-> (forall x. Rep RateLimits x -> RateLimits) -> Generic RateLimits
forall x. Rep RateLimits x -> RateLimits
forall x. RateLimits -> Rep RateLimits x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RateLimits x -> RateLimits
$cfrom :: forall x. RateLimits -> Rep RateLimits x
Generic )
readRateLimits :: POSIXTime -> ResponseHeaders -> Maybe RateLimits
readRateLimits :: POSIXTime -> ResponseHeaders -> Maybe RateLimits
readRateLimits POSIXTime
time ResponseHeaders
hs = do
Integer
remaining <- Double -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
round (Double -> Integer) -> Maybe Double -> Maybe Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HeaderName -> Maybe Double
forall a. Read a => HeaderName -> Maybe a
lookupHeader @Double HeaderName
"x-ratelimit-remaining"
Integer
used <- HeaderName -> Maybe Integer
forall a. Read a => HeaderName -> Maybe a
lookupHeader HeaderName
"x-ratelimit-used"
POSIXTime
reset <- (POSIXTime
time POSIXTime -> POSIXTime -> POSIXTime
forall a. Num a => a -> a -> a
+) (POSIXTime -> POSIXTime)
-> (Integer -> POSIXTime) -> Integer -> POSIXTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> POSIXTime
forall a. Num a => Integer -> a
fromInteger
(Integer -> POSIXTime) -> Maybe Integer -> Maybe POSIXTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HeaderName -> Maybe Integer
forall a. Read a => HeaderName -> Maybe a
lookupHeader @Integer HeaderName
"x-ratelimit-reset"
let nextTimeStamp :: POSIXTime
nextTimeStamp = POSIXTime -> POSIXTime -> POSIXTime
forall a. Ord a => a -> a -> a
max POSIXTime
0 (POSIXTime -> POSIXTime)
-> (POSIXTime -> POSIXTime) -> POSIXTime -> POSIXTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. POSIXTime -> POSIXTime -> POSIXTime
forall a. Ord a => a -> a -> a
min POSIXTime
10 (POSIXTime -> POSIXTime) -> POSIXTime -> POSIXTime
forall a b. (a -> b) -> a -> b
$ (POSIXTime
reset POSIXTime -> POSIXTime -> POSIXTime
forall a. Num a => a -> a -> a
- Integer -> POSIXTime
forall a. Num a => Integer -> a
fromInteger Integer
remaining) POSIXTime -> POSIXTime -> POSIXTime
forall a. Fractional a => a -> a -> a
/ POSIXTime
2
nextRequest :: POSIXTime
nextRequest = POSIXTime -> POSIXTime -> POSIXTime
forall a. Ord a => a -> a -> a
min POSIXTime
reset (POSIXTime -> POSIXTime) -> POSIXTime -> POSIXTime
forall a b. (a -> b) -> a -> b
$ POSIXTime
time POSIXTime -> POSIXTime -> POSIXTime
forall a. Num a => a -> a -> a
+ POSIXTime
nextTimeStamp
RateLimits -> Maybe RateLimits
forall (f :: * -> *) a. Applicative f => a -> f a
pure RateLimits :: Integer -> Integer -> POSIXTime -> POSIXTime -> RateLimits
RateLimits { Integer
POSIXTime
nextRequest :: POSIXTime
reset :: POSIXTime
used :: Integer
remaining :: Integer
$sel:nextRequest:RateLimits :: POSIXTime
$sel:reset:RateLimits :: POSIXTime
$sel:used:RateLimits :: Integer
$sel:remaining:RateLimits :: Integer
.. }
where
lookupHeader :: forall a. Read a => HeaderName -> Maybe a
lookupHeader :: HeaderName -> Maybe a
lookupHeader HeaderName
v = Read a => String -> Maybe a
forall a. Read a => String -> Maybe a
readMaybe @a (String -> Maybe a)
-> (ByteString -> String) -> ByteString -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> String
C8.unpack (ByteString -> Maybe a) -> Maybe ByteString -> Maybe a
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< HeaderName -> ResponseHeaders -> Maybe ByteString
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup HeaderName
v ResponseHeaders
hs
data AuthConfig = AuthConfig
{
AuthConfig -> Text
clientID :: ClientID
, AuthConfig -> AppType
appType :: AppType
, AuthConfig -> UserAgent
userAgent :: UserAgent
}
deriving stock ( Int -> AuthConfig -> ShowS
[AuthConfig] -> ShowS
AuthConfig -> String
(Int -> AuthConfig -> ShowS)
-> (AuthConfig -> String)
-> ([AuthConfig] -> ShowS)
-> Show AuthConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AuthConfig] -> ShowS
$cshowList :: [AuthConfig] -> ShowS
show :: AuthConfig -> String
$cshow :: AuthConfig -> String
showsPrec :: Int -> AuthConfig -> ShowS
$cshowsPrec :: Int -> AuthConfig -> ShowS
Show, AuthConfig -> AuthConfig -> Bool
(AuthConfig -> AuthConfig -> Bool)
-> (AuthConfig -> AuthConfig -> Bool) -> Eq AuthConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AuthConfig -> AuthConfig -> Bool
$c/= :: AuthConfig -> AuthConfig -> Bool
== :: AuthConfig -> AuthConfig -> Bool
$c== :: AuthConfig -> AuthConfig -> Bool
Eq, (forall x. AuthConfig -> Rep AuthConfig x)
-> (forall x. Rep AuthConfig x -> AuthConfig) -> Generic AuthConfig
forall x. Rep AuthConfig x -> AuthConfig
forall x. AuthConfig -> Rep AuthConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AuthConfig x -> AuthConfig
$cfrom :: forall x. AuthConfig -> Rep AuthConfig x
Generic )
data AppType
=
ScriptApp ClientSecret PasswordFlow
| WebApp ClientSecret CodeFlow
| InstalledApp CodeFlow
| ApplicationOnly ClientSecret
deriving stock ( Int -> AppType -> ShowS
[AppType] -> ShowS
AppType -> String
(Int -> AppType -> ShowS)
-> (AppType -> String) -> ([AppType] -> ShowS) -> Show AppType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AppType] -> ShowS
$cshowList :: [AppType] -> ShowS
show :: AppType -> String
$cshow :: AppType -> String
showsPrec :: Int -> AppType -> ShowS
$cshowsPrec :: Int -> AppType -> ShowS
Show, AppType -> AppType -> Bool
(AppType -> AppType -> Bool)
-> (AppType -> AppType -> Bool) -> Eq AppType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AppType -> AppType -> Bool
$c/= :: AppType -> AppType -> Bool
== :: AppType -> AppType -> Bool
$c== :: AppType -> AppType -> Bool
Eq, (forall x. AppType -> Rep AppType x)
-> (forall x. Rep AppType x -> AppType) -> Generic AppType
forall x. Rep AppType x -> AppType
forall x. AppType -> Rep AppType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AppType x -> AppType
$cfrom :: forall x. AppType -> Rep AppType x
Generic )
instance ToForm AppType where
toForm :: AppType -> Form
toForm = \case
ScriptApp Text
_ PasswordFlow
pf -> PasswordFlow -> Form
forall a. ToForm a => a -> Form
toForm PasswordFlow
pf
ApplicationOnly Text
_ -> [Item Form] -> Form
forall l. IsList l => [Item l] -> l
fromList [ (Text
"grant_type", Text
"client_credentials") ]
WebApp Text
_ CodeFlow
cf -> CodeFlow -> Form
forall a. ToForm a => a -> Form
toForm CodeFlow
cf
InstalledApp CodeFlow
cf -> CodeFlow -> Form
forall a. ToForm a => a -> Form
toForm CodeFlow
cf
type ClientID = Text
type ClientSecret = Text
type Token = Text
type Code = Text
data AccessToken = AccessToken
{ AccessToken -> Text
token :: Token
, AccessToken -> POSIXTime
expiresIn :: NominalDiffTime
, AccessToken -> [Scope]
scope :: [Scope]
, AccessToken -> Maybe Text
refreshToken :: Maybe Token
}
deriving stock ( Int -> AccessToken -> ShowS
[AccessToken] -> ShowS
AccessToken -> String
(Int -> AccessToken -> ShowS)
-> (AccessToken -> String)
-> ([AccessToken] -> ShowS)
-> Show AccessToken
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccessToken] -> ShowS
$cshowList :: [AccessToken] -> ShowS
show :: AccessToken -> String
$cshow :: AccessToken -> String
showsPrec :: Int -> AccessToken -> ShowS
$cshowsPrec :: Int -> AccessToken -> ShowS
Show, AccessToken -> AccessToken -> Bool
(AccessToken -> AccessToken -> Bool)
-> (AccessToken -> AccessToken -> Bool) -> Eq AccessToken
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccessToken -> AccessToken -> Bool
$c/= :: AccessToken -> AccessToken -> Bool
== :: AccessToken -> AccessToken -> Bool
$c== :: AccessToken -> AccessToken -> Bool
Eq, (forall x. AccessToken -> Rep AccessToken x)
-> (forall x. Rep AccessToken x -> AccessToken)
-> Generic AccessToken
forall x. Rep AccessToken x -> AccessToken
forall x. AccessToken -> Rep AccessToken x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AccessToken x -> AccessToken
$cfrom :: forall x. AccessToken -> Rep AccessToken x
Generic )
instance FromJSON AccessToken where
parseJSON :: Value -> Parser AccessToken
parseJSON = String
-> (Object -> Parser AccessToken) -> Value -> Parser AccessToken
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"AccessToken" ((Object -> Parser AccessToken) -> Value -> Parser AccessToken)
-> (Object -> Parser AccessToken) -> Value -> Parser AccessToken
forall a b. (a -> b) -> a -> b
$ \Object
o -> Text -> POSIXTime -> [Scope] -> Maybe Text -> AccessToken
AccessToken
(Text -> POSIXTime -> [Scope] -> Maybe Text -> AccessToken)
-> Parser Text
-> Parser (POSIXTime -> [Scope] -> Maybe Text -> AccessToken)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"access_token"
Parser (POSIXTime -> [Scope] -> Maybe Text -> AccessToken)
-> Parser POSIXTime
-> Parser ([Scope] -> Maybe Text -> AccessToken)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser POSIXTime
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"expires_in"
Parser ([Scope] -> Maybe Text -> AccessToken)
-> Parser [Scope] -> Parser (Maybe Text -> AccessToken)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Value -> Parser [Scope]
scopeP (Value -> Parser [Scope]) -> Parser Value -> Parser [Scope]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"scope")
Parser (Maybe Text -> AccessToken)
-> Parser (Maybe Text) -> Parser AccessToken
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"refresh_token"
where
scopeP :: Value -> Parser [Scope]
scopeP = String -> (Text -> Parser [Scope]) -> Value -> Parser [Scope]
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"Scope"
((Text -> Parser [Scope]) -> Value -> Parser [Scope])
-> (Text -> Parser [Scope]) -> Value -> Parser [Scope]
forall a b. (a -> b) -> a -> b
$ (Text -> Parser Scope) -> [Text] -> Parser [Scope]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (Value -> Parser Scope
forall a. FromJSON a => Value -> Parser a
parseJSON (Value -> Parser Scope) -> (Text -> Value) -> Text -> Parser Scope
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Value
String) ([Text] -> Parser [Scope])
-> (Text -> [Text]) -> Text -> Parser [Scope]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
splitScopes
where
splitScopes :: Text -> [Text]
splitScopes Text
t = (Char -> Bool) -> Text -> [Text]
T.split (Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ Char
' ', Char
',' ]) Text
t
data PasswordFlow = PasswordFlow
{
PasswordFlow -> Text
username :: Text
, PasswordFlow -> Text
password :: Text
}
deriving stock ( Int -> PasswordFlow -> ShowS
[PasswordFlow] -> ShowS
PasswordFlow -> String
(Int -> PasswordFlow -> ShowS)
-> (PasswordFlow -> String)
-> ([PasswordFlow] -> ShowS)
-> Show PasswordFlow
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PasswordFlow] -> ShowS
$cshowList :: [PasswordFlow] -> ShowS
show :: PasswordFlow -> String
$cshow :: PasswordFlow -> String
showsPrec :: Int -> PasswordFlow -> ShowS
$cshowsPrec :: Int -> PasswordFlow -> ShowS
Show, PasswordFlow -> PasswordFlow -> Bool
(PasswordFlow -> PasswordFlow -> Bool)
-> (PasswordFlow -> PasswordFlow -> Bool) -> Eq PasswordFlow
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PasswordFlow -> PasswordFlow -> Bool
$c/= :: PasswordFlow -> PasswordFlow -> Bool
== :: PasswordFlow -> PasswordFlow -> Bool
$c== :: PasswordFlow -> PasswordFlow -> Bool
Eq, (forall x. PasswordFlow -> Rep PasswordFlow x)
-> (forall x. Rep PasswordFlow x -> PasswordFlow)
-> Generic PasswordFlow
forall x. Rep PasswordFlow x -> PasswordFlow
forall x. PasswordFlow -> Rep PasswordFlow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PasswordFlow x -> PasswordFlow
$cfrom :: forall x. PasswordFlow -> Rep PasswordFlow x
Generic )
instance ToForm PasswordFlow where
toForm :: PasswordFlow -> Form
toForm PasswordFlow { Text
password :: Text
username :: Text
$sel:password:PasswordFlow :: PasswordFlow -> Text
$sel:username:PasswordFlow :: PasswordFlow -> Text
.. } =
[Item Form] -> Form
forall l. IsList l => [Item l] -> l
fromList [ (Text
"grant_type", Text
"password")
, (Text
"username", Text
username)
, (Text
"password", Text
password)
]
data CodeFlow = CodeFlow
{
CodeFlow -> Text
redirectURI :: URL
, CodeFlow -> Text
code :: Code
}
deriving stock ( Int -> CodeFlow -> ShowS
[CodeFlow] -> ShowS
CodeFlow -> String
(Int -> CodeFlow -> ShowS)
-> (CodeFlow -> String) -> ([CodeFlow] -> ShowS) -> Show CodeFlow
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CodeFlow] -> ShowS
$cshowList :: [CodeFlow] -> ShowS
show :: CodeFlow -> String
$cshow :: CodeFlow -> String
showsPrec :: Int -> CodeFlow -> ShowS
$cshowsPrec :: Int -> CodeFlow -> ShowS
Show, CodeFlow -> CodeFlow -> Bool
(CodeFlow -> CodeFlow -> Bool)
-> (CodeFlow -> CodeFlow -> Bool) -> Eq CodeFlow
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CodeFlow -> CodeFlow -> Bool
$c/= :: CodeFlow -> CodeFlow -> Bool
== :: CodeFlow -> CodeFlow -> Bool
$c== :: CodeFlow -> CodeFlow -> Bool
Eq, (forall x. CodeFlow -> Rep CodeFlow x)
-> (forall x. Rep CodeFlow x -> CodeFlow) -> Generic CodeFlow
forall x. Rep CodeFlow x -> CodeFlow
forall x. CodeFlow -> Rep CodeFlow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CodeFlow x -> CodeFlow
$cfrom :: forall x. CodeFlow -> Rep CodeFlow x
Generic )
instance ToForm CodeFlow where
toForm :: CodeFlow -> Form
toForm CodeFlow { Text
code :: Text
redirectURI :: Text
$sel:code:CodeFlow :: CodeFlow -> Text
$sel:redirectURI:CodeFlow :: CodeFlow -> Text
.. } = [Item Form] -> Form
forall l. IsList l => [Item l] -> l
fromList [ (Text
"code", Text
code)
, (Text
"redirect_uri", Text
redirectURI)
, (Text
"grant_type", Text
"authorization_code")
]
data TokenDuration
=
Temporary
| Permanent
deriving stock ( Int -> TokenDuration -> ShowS
[TokenDuration] -> ShowS
TokenDuration -> String
(Int -> TokenDuration -> ShowS)
-> (TokenDuration -> String)
-> ([TokenDuration] -> ShowS)
-> Show TokenDuration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TokenDuration] -> ShowS
$cshowList :: [TokenDuration] -> ShowS
show :: TokenDuration -> String
$cshow :: TokenDuration -> String
showsPrec :: Int -> TokenDuration -> ShowS
$cshowsPrec :: Int -> TokenDuration -> ShowS
Show, TokenDuration -> TokenDuration -> Bool
(TokenDuration -> TokenDuration -> Bool)
-> (TokenDuration -> TokenDuration -> Bool) -> Eq TokenDuration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TokenDuration -> TokenDuration -> Bool
$c/= :: TokenDuration -> TokenDuration -> Bool
== :: TokenDuration -> TokenDuration -> Bool
$c== :: TokenDuration -> TokenDuration -> Bool
Eq, (forall x. TokenDuration -> Rep TokenDuration x)
-> (forall x. Rep TokenDuration x -> TokenDuration)
-> Generic TokenDuration
forall x. Rep TokenDuration x -> TokenDuration
forall x. TokenDuration -> Rep TokenDuration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TokenDuration x -> TokenDuration
$cfrom :: forall x. TokenDuration -> Rep TokenDuration x
Generic )
instance ToHttpApiData TokenDuration where
toQueryParam :: TokenDuration -> Text
toQueryParam = TokenDuration -> Text
forall a. Show a => a -> Text
showTextData
data TokenManager = TokenManager
{
TokenManager
-> forall (m :: * -> *). (MonadIO m, MonadThrow m) => m Text
loadToken :: forall m. (MonadIO m, MonadThrow m) => m Token
, TokenManager
-> forall (m :: * -> *).
(MonadIO m, MonadThrow m) =>
Maybe Text -> m ()
putToken :: forall m. (MonadIO m, MonadThrow m) => Maybe Token -> m ()
}
data Scope
= Accounts
| Creddits
| Edit
| Flair
| History
| Identity
| LiveManage
| ModConfig
| ModContributors
| ModFlair
| ModLog
| ModMail
| ModOthers
| ModPosts
| ModSelf
| ModTraffic
| ModWiki
| MySubreddits
| PrivateMessages
| Read
| Report
| Save
| StructuredStyles
| Submit
| Subscribe
| Vote
| WikiEdit
| WikiRead
| Unlimited
deriving stock ( (forall x. Scope -> Rep Scope x)
-> (forall x. Rep Scope x -> Scope) -> Generic Scope
forall x. Rep Scope x -> Scope
forall x. Scope -> Rep Scope x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Scope x -> Scope
$cfrom :: forall x. Scope -> Rep Scope x
Generic, Scope -> Scope -> Bool
(Scope -> Scope -> Bool) -> (Scope -> Scope -> Bool) -> Eq Scope
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Scope -> Scope -> Bool
$c/= :: Scope -> Scope -> Bool
== :: Scope -> Scope -> Bool
$c== :: Scope -> Scope -> Bool
Eq, Int -> Scope -> ShowS
[Scope] -> ShowS
Scope -> String
(Int -> Scope -> ShowS)
-> (Scope -> String) -> ([Scope] -> ShowS) -> Show Scope
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Scope] -> ShowS
$cshowList :: [Scope] -> ShowS
show :: Scope -> String
$cshow :: Scope -> String
showsPrec :: Int -> Scope -> ShowS
$cshowsPrec :: Int -> Scope -> ShowS
Show, Eq Scope
Eq Scope
-> (Scope -> Scope -> Ordering)
-> (Scope -> Scope -> Bool)
-> (Scope -> Scope -> Bool)
-> (Scope -> Scope -> Bool)
-> (Scope -> Scope -> Bool)
-> (Scope -> Scope -> Scope)
-> (Scope -> Scope -> Scope)
-> Ord Scope
Scope -> Scope -> Bool
Scope -> Scope -> Ordering
Scope -> Scope -> Scope
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 :: Scope -> Scope -> Scope
$cmin :: Scope -> Scope -> Scope
max :: Scope -> Scope -> Scope
$cmax :: Scope -> Scope -> Scope
>= :: Scope -> Scope -> Bool
$c>= :: Scope -> Scope -> Bool
> :: Scope -> Scope -> Bool
$c> :: Scope -> Scope -> Bool
<= :: Scope -> Scope -> Bool
$c<= :: Scope -> Scope -> Bool
< :: Scope -> Scope -> Bool
$c< :: Scope -> Scope -> Bool
compare :: Scope -> Scope -> Ordering
$ccompare :: Scope -> Scope -> Ordering
$cp1Ord :: Eq Scope
Ord, Int -> Scope
Scope -> Int
Scope -> [Scope]
Scope -> Scope
Scope -> Scope -> [Scope]
Scope -> Scope -> Scope -> [Scope]
(Scope -> Scope)
-> (Scope -> Scope)
-> (Int -> Scope)
-> (Scope -> Int)
-> (Scope -> [Scope])
-> (Scope -> Scope -> [Scope])
-> (Scope -> Scope -> [Scope])
-> (Scope -> Scope -> Scope -> [Scope])
-> Enum Scope
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Scope -> Scope -> Scope -> [Scope]
$cenumFromThenTo :: Scope -> Scope -> Scope -> [Scope]
enumFromTo :: Scope -> Scope -> [Scope]
$cenumFromTo :: Scope -> Scope -> [Scope]
enumFromThen :: Scope -> Scope -> [Scope]
$cenumFromThen :: Scope -> Scope -> [Scope]
enumFrom :: Scope -> [Scope]
$cenumFrom :: Scope -> [Scope]
fromEnum :: Scope -> Int
$cfromEnum :: Scope -> Int
toEnum :: Int -> Scope
$ctoEnum :: Int -> Scope
pred :: Scope -> Scope
$cpred :: Scope -> Scope
succ :: Scope -> Scope
$csucc :: Scope -> Scope
Enum )
instance FromJSON Scope where
parseJSON :: Value -> Parser Scope
parseJSON = Options -> Value -> Parser Scope
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions { ShowS
constructorTagModifier :: ShowS
constructorTagModifier :: ShowS
constructorTagModifier }
where
constructorTagModifier :: ShowS
constructorTagModifier = \case
String
"Unlimited" -> String
"*"
String
"Accounts" -> String
"account"
String
scope -> Char -> Char
toLower (Char -> Char) -> ShowS
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String
scope
instance ToHttpApiData Scope where
toQueryParam :: Scope -> Text
toQueryParam = \case
Scope
Unlimited -> Text
"*"
Scope
Accounts -> Text
"account"
Scope
s -> Scope -> Text
forall a. Show a => a -> Text
showTextData Scope
s
data Method
= GET
| POST
| DELETE
| PUT
| PATCH
deriving stock ( Int -> Method -> ShowS
[Method] -> ShowS
Method -> String
(Int -> Method -> ShowS)
-> (Method -> String) -> ([Method] -> ShowS) -> Show Method
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Method] -> ShowS
$cshowList :: [Method] -> ShowS
show :: Method -> String
$cshow :: Method -> String
showsPrec :: Int -> Method -> ShowS
$cshowsPrec :: Int -> Method -> ShowS
Show, Method -> Method -> Bool
(Method -> Method -> Bool)
-> (Method -> Method -> Bool) -> Eq Method
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Method -> Method -> Bool
$c/= :: Method -> Method -> Bool
== :: Method -> Method -> Bool
$c== :: Method -> Method -> Bool
Eq, (forall x. Method -> Rep Method x)
-> (forall x. Rep Method x -> Method) -> Generic Method
forall x. Rep Method x -> Method
forall x. Method -> Rep Method x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Method x -> Method
$cfrom :: forall x. Method -> Rep Method x
Generic )
data WithData
= WithJSON Value
| WithForm Form
| WithMultipart [Part]
| NoData
deriving stock ( Int -> WithData -> ShowS
[WithData] -> ShowS
WithData -> String
(Int -> WithData -> ShowS)
-> (WithData -> String) -> ([WithData] -> ShowS) -> Show WithData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WithData] -> ShowS
$cshowList :: [WithData] -> ShowS
show :: WithData -> String
$cshow :: WithData -> String
showsPrec :: Int -> WithData -> ShowS
$cshowsPrec :: Int -> WithData -> ShowS
Show, (forall x. WithData -> Rep WithData x)
-> (forall x. Rep WithData x -> WithData) -> Generic WithData
forall x. Rep WithData x -> WithData
forall x. WithData -> Rep WithData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WithData x -> WithData
$cfrom :: forall x. WithData -> Rep WithData x
Generic )
data APIAction a = APIAction
{ APIAction a -> Method
method :: Method
, APIAction a -> [Text]
pathSegments :: [PathSegment]
, APIAction a -> WithData
requestData :: WithData
, APIAction a -> Bool
needsAuth :: Bool
, APIAction a -> Bool
followRedirects :: Bool
, APIAction a -> Bool
rawJSON :: Bool
, APIAction a -> Request -> Response BodyReader -> IO ()
checkResponse :: Request -> Response BodyReader -> IO ()
}
deriving stock ( (forall x. APIAction a -> Rep (APIAction a) x)
-> (forall x. Rep (APIAction a) x -> APIAction a)
-> Generic (APIAction a)
forall x. Rep (APIAction a) x -> APIAction a
forall x. APIAction a -> Rep (APIAction a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (APIAction a) x -> APIAction a
forall a x. APIAction a -> Rep (APIAction a) x
$cto :: forall a x. Rep (APIAction a) x -> APIAction a
$cfrom :: forall a x. APIAction a -> Rep (APIAction a) x
Generic )
type PathSegment = Text