{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}

----------------------------------------------------------------------
-- |
-- Module: Web.Slack.Auth
-- Description:
--
--
--
----------------------------------------------------------------------


module Web.Slack.Auth
  where

-- aeson
import Data.Aeson.TH

-- base
import GHC.Generics (Generic)

-- deepseq
import Control.DeepSeq (NFData)

-- slack-web
import Web.Slack.Util

-- text
import Data.Text (Text)


-- |
--
--

data TestRsp =
  TestRsp
    { TestRsp -> Text
testRspUrl :: Text
    , TestRsp -> Text
testRspTeam :: Text
    , TestRsp -> Text
testRspUser :: Text
    , TestRsp -> Text
testRspTeamId :: Text
    , TestRsp -> Text
testRspUserId :: Text
    , TestRsp -> Maybe Text
testRspEnterpriseId :: Maybe Text
    }
  deriving (TestRsp -> TestRsp -> Bool
(TestRsp -> TestRsp -> Bool)
-> (TestRsp -> TestRsp -> Bool) -> Eq TestRsp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestRsp -> TestRsp -> Bool
$c/= :: TestRsp -> TestRsp -> Bool
== :: TestRsp -> TestRsp -> Bool
$c== :: TestRsp -> TestRsp -> Bool
Eq, (forall x. TestRsp -> Rep TestRsp x)
-> (forall x. Rep TestRsp x -> TestRsp) -> Generic TestRsp
forall x. Rep TestRsp x -> TestRsp
forall x. TestRsp -> Rep TestRsp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestRsp x -> TestRsp
$cfrom :: forall x. TestRsp -> Rep TestRsp x
Generic, Int -> TestRsp -> ShowS
[TestRsp] -> ShowS
TestRsp -> String
(Int -> TestRsp -> ShowS)
-> (TestRsp -> String) -> ([TestRsp] -> ShowS) -> Show TestRsp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestRsp] -> ShowS
$cshowList :: [TestRsp] -> ShowS
show :: TestRsp -> String
$cshow :: TestRsp -> String
showsPrec :: Int -> TestRsp -> ShowS
$cshowsPrec :: Int -> TestRsp -> ShowS
Show)

instance NFData TestRsp


$(deriveJSON (jsonOpts "testRsp") ''TestRsp)