-- | Audit Log endpoints
module Calamity.HTTP.AuditLog (
  AuditLogRequest (..),
  GetAuditLogOptions (..),
) where

import Calamity.HTTP.Internal.Request
import Calamity.HTTP.Internal.Route
import Calamity.Types.Model.Guild
import Calamity.Types.Model.User
import Calamity.Types.Snowflake
import Data.Default.Class
import Data.Function ((&))

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
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)

instance Default GetAuditLogOptions where
  def :: GetAuditLogOptions
def = Maybe (Snowflake User)
-> Maybe AuditLogAction
-> Maybe (Snowflake AuditLogEntry)
-> Maybe Integer
-> GetAuditLogOptions
GetAuditLogOptions forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing

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 b a. HasID b a => a -> Snowflake b
getID @Guild -> Snowflake Guild
gid) GetAuditLogOptions
_) =
    RouteBuilder '[]
mkRouteBuilder forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"guilds" forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// forall {k} (a :: k). ID a
ID @Guild forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"audit-logs"
      forall a b. a -> (a -> b) -> b
& forall t (reqs :: [(RequirementType, RouteRequirement)]).
Typeable t =>
Snowflake t
-> RouteBuilder reqs
-> RouteBuilder ('( 'IDRequirement t, 'Satisfied) : reqs)
giveID Snowflake Guild
gid
      forall a b. a -> (a -> b) -> b
& 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" forall a. ToHttpApiData a => Text -> Maybe a -> Option 'Https
=:? (forall t. Snowflake t -> Word64
fromSnowflake forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (Snowflake User)
userID)
          forall a. Semigroup a => a -> a -> a
<> Text
"action_type" forall a. ToHttpApiData a => Text -> Maybe a -> Option 'Https
=:? (forall a. Enum a => a -> Int
fromEnum forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe AuditLogAction
actionType)
          forall a. Semigroup a => a -> a -> a
<> Text
"before" forall a. ToHttpApiData a => Text -> Maybe a -> Option 'Https
=:? (forall t. Snowflake t -> Word64
fromSnowflake forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (Snowflake AuditLogEntry)
before)
          forall a. Semigroup a => a -> a -> a
<> Text
"limit" forall a. ToHttpApiData a => Text -> Maybe a -> Option 'Https
=:? Maybe Integer
limit
      )