{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE TemplateHaskell #-}
module Honeycomb.API.Auth.Types where
import Control.Exception
import Data.Aeson.TH (defaultOptions, deriveFromJSON)
import Data.ByteString (ByteString)
import Data.ByteString.Lazy as L
import Data.Text (Text)
import Honeycomb.Aeson (snakeCaseOptions)
data NameAndSlug = NameAndSlug
{ NameAndSlug -> Text
name :: Text
, NameAndSlug -> Text
slug :: Text
}
deriving stock (Int -> NameAndSlug -> ShowS
[NameAndSlug] -> ShowS
NameAndSlug -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NameAndSlug] -> ShowS
$cshowList :: [NameAndSlug] -> ShowS
show :: NameAndSlug -> String
$cshow :: NameAndSlug -> String
showsPrec :: Int -> NameAndSlug -> ShowS
$cshowsPrec :: Int -> NameAndSlug -> ShowS
Show, NameAndSlug -> NameAndSlug -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NameAndSlug -> NameAndSlug -> Bool
$c/= :: NameAndSlug -> NameAndSlug -> Bool
== :: NameAndSlug -> NameAndSlug -> Bool
$c== :: NameAndSlug -> NameAndSlug -> Bool
Eq)
$(deriveFromJSON snakeCaseOptions ''NameAndSlug)
data ApiKeyAccess = ApiKeyAccess
{ ApiKeyAccess -> Bool
events :: Bool
, ApiKeyAccess -> Bool
markers :: Bool
, ApiKeyAccess -> Bool
triggers :: Bool
, ApiKeyAccess -> Bool
boards :: Bool
, ApiKeyAccess -> Bool
queries :: Bool
, ApiKeyAccess -> Bool
columns :: Bool
, ApiKeyAccess -> Bool
createDatasets :: Bool
, ApiKeyAccess -> Bool
slos :: Bool
, ApiKeyAccess -> Bool
recipients :: Bool
, ApiKeyAccess -> Bool
privateBoards :: Bool
}
deriving stock (Int -> ApiKeyAccess -> ShowS
[ApiKeyAccess] -> ShowS
ApiKeyAccess -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApiKeyAccess] -> ShowS
$cshowList :: [ApiKeyAccess] -> ShowS
show :: ApiKeyAccess -> String
$cshow :: ApiKeyAccess -> String
showsPrec :: Int -> ApiKeyAccess -> ShowS
$cshowsPrec :: Int -> ApiKeyAccess -> ShowS
Show, ApiKeyAccess -> ApiKeyAccess -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApiKeyAccess -> ApiKeyAccess -> Bool
$c/= :: ApiKeyAccess -> ApiKeyAccess -> Bool
== :: ApiKeyAccess -> ApiKeyAccess -> Bool
$c== :: ApiKeyAccess -> ApiKeyAccess -> Bool
Eq)
$(deriveFromJSON defaultOptions ''ApiKeyAccess)
data Auth = Auth
{ Auth -> ApiKeyAccess
apiKeyAccess :: ApiKeyAccess
, Auth -> NameAndSlug
environment :: NameAndSlug
, Auth -> NameAndSlug
team :: NameAndSlug
}
deriving stock (Int -> Auth -> ShowS
[Auth] -> ShowS
Auth -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Auth] -> ShowS
$cshowList :: [Auth] -> ShowS
show :: Auth -> String
$cshow :: Auth -> String
showsPrec :: Int -> Auth -> ShowS
$cshowsPrec :: Int -> Auth -> ShowS
Show, Auth -> Auth -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Auth -> Auth -> Bool
$c/= :: Auth -> Auth -> Bool
== :: Auth -> Auth -> Bool
$c== :: Auth -> Auth -> Bool
Eq)
$(deriveFromJSON snakeCaseOptions ''Auth)
data FailureResponse
= FailureCode Int L.ByteString
| JsonDecodeFailed Text
deriving stock (Int -> FailureResponse -> ShowS
[FailureResponse] -> ShowS
FailureResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FailureResponse] -> ShowS
$cshowList :: [FailureResponse] -> ShowS
show :: FailureResponse -> String
$cshow :: FailureResponse -> String
showsPrec :: Int -> FailureResponse -> ShowS
$cshowsPrec :: Int -> FailureResponse -> ShowS
Show)
deriving anyclass (Show FailureResponse
Typeable FailureResponse
SomeException -> Maybe FailureResponse
FailureResponse -> String
FailureResponse -> SomeException
forall e.
Typeable e
-> Show e
-> (e -> SomeException)
-> (SomeException -> Maybe e)
-> (e -> String)
-> Exception e
displayException :: FailureResponse -> String
$cdisplayException :: FailureResponse -> String
fromException :: SomeException -> Maybe FailureResponse
$cfromException :: SomeException -> Maybe FailureResponse
toException :: FailureResponse -> SomeException
$ctoException :: FailureResponse -> SomeException
Exception)