-- | Types of channels
module Calamity.Types.Model.Channel.ChannelType
    ( ChannelType(..) ) where

import           Data.Aeson
import           Data.Scientific

import           GHC.Generics

import           TextShow
import qualified TextShow.Generic as TSG

-- Thanks sbrg (https://github.com/saevarb/haskord/blob/d1bb07bcc4f3dbc29f2dfd3351ff9f16fc100c07/haskord-lib/src/Haskord/Types/Common.hsfield#L182)
data ChannelType
  = GuildTextType
  | DMType
  | GuildVoiceType
  | GroupDMType
  | GuildCategoryType
  deriving ( ChannelType -> ChannelType -> Bool
(ChannelType -> ChannelType -> Bool)
-> (ChannelType -> ChannelType -> Bool) -> Eq ChannelType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChannelType -> ChannelType -> Bool
$c/= :: ChannelType -> ChannelType -> Bool
== :: ChannelType -> ChannelType -> Bool
$c== :: ChannelType -> ChannelType -> Bool
Eq, (forall x. ChannelType -> Rep ChannelType x)
-> (forall x. Rep ChannelType x -> ChannelType)
-> Generic ChannelType
forall x. Rep ChannelType x -> ChannelType
forall x. ChannelType -> Rep ChannelType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChannelType x -> ChannelType
$cfrom :: forall x. ChannelType -> Rep ChannelType x
Generic, Int -> ChannelType -> ShowS
[ChannelType] -> ShowS
ChannelType -> String
(Int -> ChannelType -> ShowS)
-> (ChannelType -> String)
-> ([ChannelType] -> ShowS)
-> Show ChannelType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChannelType] -> ShowS
$cshowList :: [ChannelType] -> ShowS
show :: ChannelType -> String
$cshow :: ChannelType -> String
showsPrec :: Int -> ChannelType -> ShowS
$cshowsPrec :: Int -> ChannelType -> ShowS
Show, Int -> ChannelType
ChannelType -> Int
ChannelType -> [ChannelType]
ChannelType -> ChannelType
ChannelType -> ChannelType -> [ChannelType]
ChannelType -> ChannelType -> ChannelType -> [ChannelType]
(ChannelType -> ChannelType)
-> (ChannelType -> ChannelType)
-> (Int -> ChannelType)
-> (ChannelType -> Int)
-> (ChannelType -> [ChannelType])
-> (ChannelType -> ChannelType -> [ChannelType])
-> (ChannelType -> ChannelType -> [ChannelType])
-> (ChannelType -> ChannelType -> ChannelType -> [ChannelType])
-> Enum ChannelType
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 :: ChannelType -> ChannelType -> ChannelType -> [ChannelType]
$cenumFromThenTo :: ChannelType -> ChannelType -> ChannelType -> [ChannelType]
enumFromTo :: ChannelType -> ChannelType -> [ChannelType]
$cenumFromTo :: ChannelType -> ChannelType -> [ChannelType]
enumFromThen :: ChannelType -> ChannelType -> [ChannelType]
$cenumFromThen :: ChannelType -> ChannelType -> [ChannelType]
enumFrom :: ChannelType -> [ChannelType]
$cenumFrom :: ChannelType -> [ChannelType]
fromEnum :: ChannelType -> Int
$cfromEnum :: ChannelType -> Int
toEnum :: Int -> ChannelType
$ctoEnum :: Int -> ChannelType
pred :: ChannelType -> ChannelType
$cpred :: ChannelType -> ChannelType
succ :: ChannelType -> ChannelType
$csucc :: ChannelType -> ChannelType
Enum )
  deriving ( Int -> ChannelType -> Builder
Int -> ChannelType -> Text
Int -> ChannelType -> Text
[ChannelType] -> Builder
[ChannelType] -> Text
[ChannelType] -> Text
ChannelType -> Builder
ChannelType -> Text
ChannelType -> Text
(Int -> ChannelType -> Builder)
-> (ChannelType -> Builder)
-> ([ChannelType] -> Builder)
-> (Int -> ChannelType -> Text)
-> (ChannelType -> Text)
-> ([ChannelType] -> Text)
-> (Int -> ChannelType -> Text)
-> (ChannelType -> Text)
-> ([ChannelType] -> Text)
-> TextShow ChannelType
forall a.
(Int -> a -> Builder)
-> (a -> Builder)
-> ([a] -> Builder)
-> (Int -> a -> Text)
-> (a -> Text)
-> ([a] -> Text)
-> (Int -> a -> Text)
-> (a -> Text)
-> ([a] -> Text)
-> TextShow a
showtlList :: [ChannelType] -> Text
$cshowtlList :: [ChannelType] -> Text
showtl :: ChannelType -> Text
$cshowtl :: ChannelType -> Text
showtlPrec :: Int -> ChannelType -> Text
$cshowtlPrec :: Int -> ChannelType -> Text
showtList :: [ChannelType] -> Text
$cshowtList :: [ChannelType] -> Text
showt :: ChannelType -> Text
$cshowt :: ChannelType -> Text
showtPrec :: Int -> ChannelType -> Text
$cshowtPrec :: Int -> ChannelType -> Text
showbList :: [ChannelType] -> Builder
$cshowbList :: [ChannelType] -> Builder
showb :: ChannelType -> Builder
$cshowb :: ChannelType -> Builder
showbPrec :: Int -> ChannelType -> Builder
$cshowbPrec :: Int -> ChannelType -> Builder
TextShow ) via TSG.FromGeneric ChannelType

instance ToJSON ChannelType where
  toJSON :: ChannelType -> Value
toJSON ChannelType
t = Scientific -> Value
Number (Scientific -> Value) -> Scientific -> Value
forall a b. (a -> b) -> a -> b
$ Int -> Scientific
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ChannelType -> Int
forall a. Enum a => a -> Int
fromEnum ChannelType
t)

instance FromJSON ChannelType where
  parseJSON :: Value -> Parser ChannelType
parseJSON = String
-> (Scientific -> Parser ChannelType)
-> Value
-> Parser ChannelType
forall a. String -> (Scientific -> Parser a) -> Value -> Parser a
withScientific String
"ChannelType" ((Scientific -> Parser ChannelType) -> Value -> Parser ChannelType)
-> (Scientific -> Parser ChannelType)
-> Value
-> Parser ChannelType
forall a b. (a -> b) -> a -> b
$ \Scientific
n -> case Scientific -> Maybe Int
forall i. (Integral i, Bounded i) => Scientific -> Maybe i
toBoundedInteger @Int Scientific
n of
    Just !Int
v  -> case Int
v of
      Int
0 -> ChannelType -> Parser ChannelType
forall (f :: * -> *) a. Applicative f => a -> f a
pure ChannelType
GuildTextType
      Int
1 -> ChannelType -> Parser ChannelType
forall (f :: * -> *) a. Applicative f => a -> f a
pure ChannelType
DMType
      Int
2 -> ChannelType -> Parser ChannelType
forall (f :: * -> *) a. Applicative f => a -> f a
pure ChannelType
GuildVoiceType
      Int
4 -> ChannelType -> Parser ChannelType
forall (f :: * -> *) a. Applicative f => a -> f a
pure ChannelType
GuildCategoryType
      Int
_ -> String -> Parser ChannelType
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser ChannelType) -> String -> Parser ChannelType
forall a b. (a -> b) -> a -> b
$ String
"Invalid ChannelType: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Scientific -> String
forall a. Show a => a -> String
show Scientific
n
    Maybe Int
Nothing -> String -> Parser ChannelType
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser ChannelType) -> String -> Parser ChannelType
forall a b. (a -> b) -> a -> b
$ String
"Invalid ChannelType: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Scientific -> String
forall a. Show a => a -> String
show Scientific
n