module Calamity.HTTP.AuditLog (
AuditLogRequest (..),
GetAuditLogOptions (..),
) where
import Calamity.HTTP.Internal.Request
import Calamity.HTTP.Internal.Route
import Calamity.Internal.Utils ()
import Calamity.Types.Model.Guild
import Calamity.Types.Model.User
import Calamity.Types.Snowflake
import Control.Lens
import Data.Default.Class
import GHC.Generics
data GetAuditLogOptions = GetAuditLogOptions
{ GetAuditLogOptions -> Maybe (Snowflake User)
userID :: Maybe (Snowflake User)
, GetAuditLogOptions -> Maybe AuditLogAction
actionType :: Maybe AuditLogAction
, GetAuditLogOptions -> Maybe (Snowflake AuditLogEntry)
before :: Maybe (Snowflake AuditLogEntry)
, GetAuditLogOptions -> Maybe Integer
limit :: Maybe Integer
}
deriving (Int -> GetAuditLogOptions -> ShowS
[GetAuditLogOptions] -> ShowS
GetAuditLogOptions -> String
(Int -> GetAuditLogOptions -> ShowS)
-> (GetAuditLogOptions -> String)
-> ([GetAuditLogOptions] -> ShowS)
-> Show GetAuditLogOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAuditLogOptions] -> ShowS
$cshowList :: [GetAuditLogOptions] -> ShowS
show :: GetAuditLogOptions -> String
$cshow :: GetAuditLogOptions -> String
showsPrec :: Int -> GetAuditLogOptions -> ShowS
$cshowsPrec :: Int -> GetAuditLogOptions -> ShowS
Show, (forall x. GetAuditLogOptions -> Rep GetAuditLogOptions x)
-> (forall x. Rep GetAuditLogOptions x -> GetAuditLogOptions)
-> Generic GetAuditLogOptions
forall x. Rep GetAuditLogOptions x -> GetAuditLogOptions
forall x. GetAuditLogOptions -> Rep GetAuditLogOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetAuditLogOptions x -> GetAuditLogOptions
$cfrom :: forall x. GetAuditLogOptions -> Rep GetAuditLogOptions x
Generic, GetAuditLogOptions
GetAuditLogOptions -> Default GetAuditLogOptions
forall a. a -> Default a
def :: GetAuditLogOptions
$cdef :: GetAuditLogOptions
Default)
data AuditLogRequest a where
GetAuditLog :: HasID Guild g => g -> GetAuditLogOptions -> AuditLogRequest AuditLog
instance Request (AuditLogRequest a) where
type Result (AuditLogRequest a) = a
route :: AuditLogRequest a -> Route
route (GetAuditLog (forall a. HasID Guild a => a -> Snowflake Guild
forall b a. HasID b a => a -> Snowflake b
getID @Guild -> Snowflake Guild
gid) GetAuditLogOptions
_) =
RouteBuilder '[]
mkRouteBuilder RouteBuilder '[] -> S -> ConsRes S '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"guilds" RouteBuilder '[] -> ID Guild -> ConsRes (ID Guild) '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// ID Guild
forall k (a :: k). ID a
ID @Guild RouteBuilder '[ '( 'IDRequirement Guild, 'Required)]
-> S -> ConsRes S '[ '( 'IDRequirement Guild, 'Required)]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"audit-logs"
RouteBuilder '[ '( 'IDRequirement Guild, 'Required)]
-> (RouteBuilder '[ '( 'IDRequirement Guild, 'Required)]
-> RouteBuilder
'[ '( 'IDRequirement Guild, 'Satisfied),
'( 'IDRequirement Guild, 'Required)])
-> RouteBuilder
'[ '( 'IDRequirement Guild, 'Satisfied),
'( 'IDRequirement Guild, 'Required)]
forall a b. a -> (a -> b) -> b
& Snowflake Guild
-> RouteBuilder '[ '( 'IDRequirement Guild, 'Required)]
-> RouteBuilder
'[ '( 'IDRequirement Guild, 'Satisfied),
'( 'IDRequirement Guild, 'Required)]
forall t (reqs :: [(RequirementType, RouteRequirement)]).
Typeable t =>
Snowflake t
-> RouteBuilder reqs
-> RouteBuilder ('( 'IDRequirement t, 'Satisfied) : reqs)
giveID Snowflake Guild
gid
RouteBuilder
'[ '( 'IDRequirement Guild, 'Satisfied),
'( 'IDRequirement Guild, 'Required)]
-> (RouteBuilder
'[ '( 'IDRequirement Guild, 'Satisfied),
'( 'IDRequirement Guild, 'Required)]
-> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
'[ '( 'IDRequirement Guild, 'Satisfied),
'( 'IDRequirement Guild, 'Required)]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
action :: AuditLogRequest a -> Url 'Https -> Option 'Https -> Req LbsResponse
action (GetAuditLog g
_ GetAuditLogOptions{Maybe (Snowflake User)
userID :: Maybe (Snowflake User)
$sel:userID:GetAuditLogOptions :: GetAuditLogOptions -> Maybe (Snowflake User)
userID, Maybe AuditLogAction
actionType :: Maybe AuditLogAction
$sel:actionType:GetAuditLogOptions :: GetAuditLogOptions -> Maybe AuditLogAction
actionType, Maybe (Snowflake AuditLogEntry)
before :: Maybe (Snowflake AuditLogEntry)
$sel:before:GetAuditLogOptions :: GetAuditLogOptions -> Maybe (Snowflake AuditLogEntry)
before, Maybe Integer
limit :: Maybe Integer
$sel:limit:GetAuditLogOptions :: GetAuditLogOptions -> Maybe Integer
limit}) =
Option 'Https -> Url 'Https -> Option 'Https -> Req LbsResponse
getWithP
( Text
"user_id" Text -> Maybe Word64 -> Option 'Https
forall a. ToHttpApiData a => Text -> Maybe a -> Option 'Https
=:? (Snowflake User -> Word64
forall t. Snowflake t -> Word64
fromSnowflake (Snowflake User -> Word64)
-> Maybe (Snowflake User) -> Maybe Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (Snowflake User)
userID)
Option 'Https -> Option 'Https -> Option 'Https
forall a. Semigroup a => a -> a -> a
<> Text
"action_type" Text -> Maybe Int -> Option 'Https
forall a. ToHttpApiData a => Text -> Maybe a -> Option 'Https
=:? (AuditLogAction -> Int
forall a. Enum a => a -> Int
fromEnum (AuditLogAction -> Int) -> Maybe AuditLogAction -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe AuditLogAction
actionType)
Option 'Https -> Option 'Https -> Option 'Https
forall a. Semigroup a => a -> a -> a
<> Text
"before" Text -> Maybe Word64 -> Option 'Https
forall a. ToHttpApiData a => Text -> Maybe a -> Option 'Https
=:? (Snowflake AuditLogEntry -> Word64
forall t. Snowflake t -> Word64
fromSnowflake (Snowflake AuditLogEntry -> Word64)
-> Maybe (Snowflake AuditLogEntry) -> Maybe Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (Snowflake AuditLogEntry)
before)
Option 'Https -> Option 'Https -> Option 'Https
forall a. Semigroup a => a -> a -> a
<> Text
"limit" Text -> Maybe Integer -> Option 'Https
forall a. ToHttpApiData a => Text -> Maybe a -> Option 'Https
=:? Maybe Integer
limit
)