{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE RecordWildCards     #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Web.TwitchAPI.Helix.Bits where

import Prelude

import qualified Data.ByteString.Char8 as BS
import qualified Data.Time             as Time
import qualified Data.Time.RFC3339     as Time ( formatTimeRFC3339, parseTimeRFC3339 )
import qualified Data.Text             as Text
import qualified Data.Text.Encoding    as Text ( encodeUtf8 )
import qualified Network.HTTP.Client   as HTTP

import Data.Aeson ( FromJSON(..), (.:), withObject
                  , Object
                  )

import qualified Web.TwitchAPI.Helix.Request as Req

data Leaderboard = Leaderboard { Leaderboard -> Maybe Integer
count    :: Maybe Integer
                               , Leaderboard -> Maybe Period
period   :: Maybe Period
                               , Leaderboard -> Maybe UTCTime
start    :: Maybe Time.UTCTime
                               , Leaderboard -> Maybe Integer
searchId :: Maybe Integer
                               } deriving ( Int -> Leaderboard -> ShowS
[Leaderboard] -> ShowS
Leaderboard -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Leaderboard] -> ShowS
$cshowList :: [Leaderboard] -> ShowS
show :: Leaderboard -> String
$cshow :: Leaderboard -> String
showsPrec :: Int -> Leaderboard -> ShowS
$cshowsPrec :: Int -> Leaderboard -> ShowS
Show, Leaderboard -> Leaderboard -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Leaderboard -> Leaderboard -> Bool
$c/= :: Leaderboard -> Leaderboard -> Bool
== :: Leaderboard -> Leaderboard -> Bool
$c== :: Leaderboard -> Leaderboard -> Bool
Eq )

data Period = Day | Week | Month | Year | All deriving ( Period -> Period -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Period -> Period -> Bool
$c/= :: Period -> Period -> Bool
== :: Period -> Period -> Bool
$c== :: Period -> Period -> Bool
Eq )
instance Show Period where
    show :: Period -> String
show Period
Day   = String
"day"
    show Period
Week  = String
"week"
    show Period
Month = String
"month"
    show Period
Year  = String
"year"
    show Period
All   = String
"all"

instance Req.HelixRequest Leaderboard where
    toRequest :: Leaderboard -> Request
toRequest Leaderboard
leaderboard =
        let [(ByteString, Maybe ByteString)]
count'    :: [(BS.ByteString, Maybe BS.ByteString)] = forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Integer
c -> [(ByteString
"count", forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
BS.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ Integer
c)]) (Leaderboard -> Maybe Integer
count Leaderboard
leaderboard)
            [(ByteString, Maybe ByteString)]
period'   :: [(BS.ByteString, Maybe BS.ByteString)] = forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Period
p -> [(ByteString
"period", forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
BS.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ Period
p)]) (Leaderboard -> Maybe Period
period Leaderboard
leaderboard)
            [(ByteString, Maybe ByteString)]
start'    :: [(BS.ByteString, Maybe BS.ByteString)] = forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\UTCTime
s -> [(ByteString
"started_at", forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
Text.encodeUtf8 forall a b. (a -> b) -> a -> b
$ (forall t. TextualMonoid t => ZonedTime -> t
Time.formatTimeRFC3339 forall a b. (a -> b) -> a -> b
$ TimeZone -> UTCTime -> ZonedTime
Time.utcToZonedTime TimeZone
Time.utc UTCTime
s :: Text.Text))]) (Leaderboard -> Maybe UTCTime
start Leaderboard
leaderboard)
            [(ByteString, Maybe ByteString)]
searchId' :: [(BS.ByteString, Maybe BS.ByteString)] = forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Integer
u -> [(ByteString
"user_id", forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
Text.encodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ Integer
u)]) (Leaderboard -> Maybe Integer
searchId Leaderboard
leaderboard)
            setQuery :: Request -> Request
setQuery = [(ByteString, Maybe ByteString)] -> Request -> Request
HTTP.setQueryString forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[(ByteString, Maybe ByteString)]
count', [(ByteString, Maybe ByteString)]
period', [(ByteString, Maybe ByteString)]
start', [(ByteString, Maybe ByteString)]
searchId']
        in Request -> Request
setQuery forall a b. (a -> b) -> a -> b
$ String -> Request
HTTP.parseRequest_ String
"GET https://api.twitch.tv/helix/bits/leaderboard"
    scope :: Leaderboard -> Maybe String
scope Leaderboard{} = forall a. a -> Maybe a
Just String
"bits:read"

data LeaderboardEntry = LeaderboardEntry { LeaderboardEntry -> Integer
userId    :: Integer
                                         , LeaderboardEntry -> String
userLogin :: String
                                         , LeaderboardEntry -> String
userName  :: String
                                         , LeaderboardEntry -> Integer
rank      :: Integer
                                         , LeaderboardEntry -> Integer
score     :: Integer
                                         } deriving ( Int -> LeaderboardEntry -> ShowS
[LeaderboardEntry] -> ShowS
LeaderboardEntry -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LeaderboardEntry] -> ShowS
$cshowList :: [LeaderboardEntry] -> ShowS
show :: LeaderboardEntry -> String
$cshow :: LeaderboardEntry -> String
showsPrec :: Int -> LeaderboardEntry -> ShowS
$cshowsPrec :: Int -> LeaderboardEntry -> ShowS
Show, LeaderboardEntry -> LeaderboardEntry -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LeaderboardEntry -> LeaderboardEntry -> Bool
$c/= :: LeaderboardEntry -> LeaderboardEntry -> Bool
== :: LeaderboardEntry -> LeaderboardEntry -> Bool
$c== :: LeaderboardEntry -> LeaderboardEntry -> Bool
Eq )

instance FromJSON LeaderboardEntry where
    parseJSON :: Value -> Parser LeaderboardEntry
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"LeaderboardEntry" forall a b. (a -> b) -> a -> b
$ \Object
o -> do
        String
uid <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"user_id"
        String
userLogin <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"user_login"
        String
userName <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"user_login"
        Integer
rank <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"rank"
        Integer
score <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"score"
        let userId :: Integer
userId = forall a. Read a => String -> a
read String
uid :: Integer
        forall (m :: * -> *) a. Monad m => a -> m a
return LeaderboardEntry{Integer
String
userId :: Integer
score :: Integer
rank :: Integer
userName :: String
userLogin :: String
score :: Integer
rank :: Integer
userName :: String
userLogin :: String
userId :: Integer
..}

data LeaderboardResponse = LeaderboardResponse { LeaderboardResponse -> Maybe UTCTime
endedAt   :: Maybe Time.UTCTime
                                               , LeaderboardResponse -> Maybe UTCTime
startedAt :: Maybe Time.UTCTime
                                               , LeaderboardResponse -> Integer
total     :: Integer
                                               , LeaderboardResponse -> [LeaderboardEntry]
entries   :: [LeaderboardEntry]
                                               } deriving ( Int -> LeaderboardResponse -> ShowS
[LeaderboardResponse] -> ShowS
LeaderboardResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LeaderboardResponse] -> ShowS
$cshowList :: [LeaderboardResponse] -> ShowS
show :: LeaderboardResponse -> String
$cshow :: LeaderboardResponse -> String
showsPrec :: Int -> LeaderboardResponse -> ShowS
$cshowsPrec :: Int -> LeaderboardResponse -> ShowS
Show, LeaderboardResponse -> LeaderboardResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LeaderboardResponse -> LeaderboardResponse -> Bool
$c/= :: LeaderboardResponse -> LeaderboardResponse -> Bool
== :: LeaderboardResponse -> LeaderboardResponse -> Bool
$c== :: LeaderboardResponse -> LeaderboardResponse -> Bool
Eq)

instance FromJSON LeaderboardResponse where
    parseJSON :: Value -> Parser LeaderboardResponse
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"LeaderboardResponse" forall a b. (a -> b) -> a -> b
$ \Object
o -> do
        Object
dates :: Object <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"date_range"
        String
ended :: String <- Object
dates forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"ended_at"
        String
started :: String <- Object
dates forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"started_at"
        [LeaderboardEntry]
entries :: [LeaderboardEntry] <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"data"
        Integer
total <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total"
        let endedAt :: Maybe UTCTime
endedAt = ZonedTime -> UTCTime
Time.zonedTimeToUTC forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. TextualMonoid t => t -> Maybe ZonedTime
Time.parseTimeRFC3339 String
ended
            startedAt :: Maybe UTCTime
startedAt = ZonedTime -> UTCTime
Time.zonedTimeToUTC forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. TextualMonoid t => t -> Maybe ZonedTime
Time.parseTimeRFC3339 String
started
        forall (m :: * -> *) a. Monad m => a -> m a
return LeaderboardResponse{Integer
[LeaderboardEntry]
Maybe UTCTime
startedAt :: Maybe UTCTime
endedAt :: Maybe UTCTime
total :: Integer
entries :: [LeaderboardEntry]
entries :: [LeaderboardEntry]
total :: Integer
startedAt :: Maybe UTCTime
endedAt :: Maybe UTCTime
..}

newtype Cheermotes = Cheermotes { Cheermotes -> Integer
broadcasterId :: Integer } deriving ( Int -> Cheermotes -> ShowS
[Cheermotes] -> ShowS
Cheermotes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Cheermotes] -> ShowS
$cshowList :: [Cheermotes] -> ShowS
show :: Cheermotes -> String
$cshow :: Cheermotes -> String
showsPrec :: Int -> Cheermotes -> ShowS
$cshowsPrec :: Int -> Cheermotes -> ShowS
Show, Cheermotes -> Cheermotes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Cheermotes -> Cheermotes -> Bool
$c/= :: Cheermotes -> Cheermotes -> Bool
== :: Cheermotes -> Cheermotes -> Bool
$c== :: Cheermotes -> Cheermotes -> Bool
Eq )

instance Req.HelixRequest Cheermotes where
    toRequest :: Cheermotes -> Request
toRequest Cheermotes
c =
        let setQuery :: Request -> Request
setQuery  = [(ByteString, Maybe ByteString)] -> Request -> Request
HTTP.setQueryString [(ByteString
"broadcaster_id", forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
BS.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ (Cheermotes -> Integer
broadcasterId :: Cheermotes -> Integer) Cheermotes
c)]
        in Request -> Request
setQuery forall a b. (a -> b) -> a -> b
$ String -> Request
HTTP.parseRequest_ String
"GET https://api.twitch.tv/helix/bits/leaderboard"
    scope :: Cheermotes -> Maybe String
scope Cheermotes{} = forall a. Maybe a
Nothing

data CheermoteClass = GlobalFirstParty | GlobalThirdParty | ChannelCustom | DisplayOnly |  | Unknown deriving ( CheermoteClass -> CheermoteClass -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheermoteClass -> CheermoteClass -> Bool
$c/= :: CheermoteClass -> CheermoteClass -> Bool
== :: CheermoteClass -> CheermoteClass -> Bool
$c== :: CheermoteClass -> CheermoteClass -> Bool
Eq, Int -> CheermoteClass -> ShowS
[CheermoteClass] -> ShowS
CheermoteClass -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheermoteClass] -> ShowS
$cshowList :: [CheermoteClass] -> ShowS
show :: CheermoteClass -> String
$cshow :: CheermoteClass -> String
showsPrec :: Int -> CheermoteClass -> ShowS
$cshowsPrec :: Int -> CheermoteClass -> ShowS
Show )

instance Read CheermoteClass where
    readsPrec :: Int -> ReadS CheermoteClass
readsPrec Int
_ String
"global_first_party" = [(CheermoteClass
GlobalFirstParty, String
"")]
    readsPrec Int
_ String
"global_third_party" = [(CheermoteClass
GlobalThirdParty, String
"")]
    readsPrec Int
_ String
"channel_custom"     = [(CheermoteClass
ChannelCustom, String
"")]
    readsPrec Int
_ String
"display_only"       = [(CheermoteClass
DisplayOnly, String
"")]
    readsPrec Int
_ String
"sponsored"          = [(CheermoteClass
Sponsored, String
"")]
    readsPrec Int
_ String
_                    = [(CheermoteClass
Unknown, String
"")]

data CheermoteData = CheermoteData { CheermoteData -> Maybe String
tinyURI   :: Maybe String
                                   , CheermoteData -> Maybe String
smallURI  :: Maybe String
                                   , CheermoteData -> Maybe String
mediumURI :: Maybe String
                                   , CheermoteData -> Maybe String
largeURI  :: Maybe String
                                   , CheermoteData -> Maybe String
hugeURI   :: Maybe String
                                   } deriving ( CheermoteData -> CheermoteData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheermoteData -> CheermoteData -> Bool
$c/= :: CheermoteData -> CheermoteData -> Bool
== :: CheermoteData -> CheermoteData -> Bool
$c== :: CheermoteData -> CheermoteData -> Bool
Eq, Int -> CheermoteData -> ShowS
[CheermoteData] -> ShowS
CheermoteData -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheermoteData] -> ShowS
$cshowList :: [CheermoteData] -> ShowS
show :: CheermoteData -> String
$cshow :: CheermoteData -> String
showsPrec :: Int -> CheermoteData -> ShowS
$cshowsPrec :: Int -> CheermoteData -> ShowS
Show )

instance FromJSON CheermoteData where
    parseJSON :: Value -> Parser CheermoteData
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CheermoteData" forall a b. (a -> b) -> a -> b
$ \Object
o -> do
        Maybe String
tinyURI   <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"1"
        Maybe String
smallURI  <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"1.5"
        Maybe String
mediumURI <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"2"
        Maybe String
largeURI  <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"3"
        Maybe String
hugeURI   <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"4"
        forall (m :: * -> *) a. Monad m => a -> m a
return CheermoteData{Maybe String
hugeURI :: Maybe String
largeURI :: Maybe String
mediumURI :: Maybe String
smallURI :: Maybe String
tinyURI :: Maybe String
hugeURI :: Maybe String
largeURI :: Maybe String
mediumURI :: Maybe String
smallURI :: Maybe String
tinyURI :: Maybe String
..}

data CheermoteImages = CheermoteImages { CheermoteImages -> CheermoteData
darkAnimated  :: CheermoteData
                                       , CheermoteImages -> CheermoteData
darkStatic    :: CheermoteData
                                       , CheermoteImages -> CheermoteData
lightAnimated :: CheermoteData
                                       , CheermoteImages -> CheermoteData
lightStatic   :: CheermoteData
                                       } deriving ( CheermoteImages -> CheermoteImages -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheermoteImages -> CheermoteImages -> Bool
$c/= :: CheermoteImages -> CheermoteImages -> Bool
== :: CheermoteImages -> CheermoteImages -> Bool
$c== :: CheermoteImages -> CheermoteImages -> Bool
Eq, Int -> CheermoteImages -> ShowS
[CheermoteImages] -> ShowS
CheermoteImages -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheermoteImages] -> ShowS
$cshowList :: [CheermoteImages] -> ShowS
show :: CheermoteImages -> String
$cshow :: CheermoteImages -> String
showsPrec :: Int -> CheermoteImages -> ShowS
$cshowsPrec :: Int -> CheermoteImages -> ShowS
Show )

instance FromJSON CheermoteImages where
    parseJSON :: Value -> Parser CheermoteImages
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CheermoteImages" forall a b. (a -> b) -> a -> b
$ \Object
o -> do
        Object
dark :: Object  <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"dark"
        Object
light :: Object <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"light"
        CheermoteData
darkAnimated    <- Object
dark forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"animated"
        CheermoteData
darkStatic      <- Object
dark forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"static"
        CheermoteData
lightAnimated   <- Object
light forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"animated"
        CheermoteData
lightStatic     <- Object
light forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"static"
        forall (m :: * -> *) a. Monad m => a -> m a
return CheermoteImages{CheermoteData
lightStatic :: CheermoteData
lightAnimated :: CheermoteData
darkStatic :: CheermoteData
darkAnimated :: CheermoteData
lightStatic :: CheermoteData
lightAnimated :: CheermoteData
darkStatic :: CheermoteData
darkAnimated :: CheermoteData
..}

data CheermoteTier = CheermoteTier { CheermoteTier -> Integer
minBits :: Integer
                                   , CheermoteTier -> Integer
cheermoteId :: Integer
                                   , CheermoteTier -> String
color :: String
                                   , CheermoteTier -> CheermoteImages
images :: CheermoteImages
                                   , CheermoteTier -> Bool
enabled :: Bool
                                   , CheermoteTier -> Bool
visible :: Bool
                                   } deriving ( CheermoteTier -> CheermoteTier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheermoteTier -> CheermoteTier -> Bool
$c/= :: CheermoteTier -> CheermoteTier -> Bool
== :: CheermoteTier -> CheermoteTier -> Bool
$c== :: CheermoteTier -> CheermoteTier -> Bool
Eq, Int -> CheermoteTier -> ShowS
[CheermoteTier] -> ShowS
CheermoteTier -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheermoteTier] -> ShowS
$cshowList :: [CheermoteTier] -> ShowS
show :: CheermoteTier -> String
$cshow :: CheermoteTier -> String
showsPrec :: Int -> CheermoteTier -> ShowS
$cshowsPrec :: Int -> CheermoteTier -> ShowS
Show )

instance FromJSON CheermoteTier where
    parseJSON :: Value -> Parser CheermoteTier
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CheermoteTier" forall a b. (a -> b) -> a -> b
$ \Object
o -> do
        Integer
minBits <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"min_bits"
        Integer
cheermoteId <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
        String
color <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"color"
        CheermoteImages
images <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"images"
        Bool
enabled <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"can_cheer"
        Bool
visible <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"show_in_bits_card"
        forall (m :: * -> *) a. Monad m => a -> m a
return CheermoteTier{Bool
Integer
String
CheermoteImages
visible :: Bool
enabled :: Bool
images :: CheermoteImages
color :: String
cheermoteId :: Integer
minBits :: Integer
visible :: Bool
enabled :: Bool
images :: CheermoteImages
color :: String
cheermoteId :: Integer
minBits :: Integer
..}

data CheermotesResponse = CheermotesResponse { CheermotesResponse -> String
prefix :: String
                                             , CheermotesResponse -> [CheermoteTier]
tiers :: [CheermoteTier]
                                             , CheermotesResponse -> String
cheermoteType :: String
                                             , CheermotesResponse -> Integer
order :: Integer
                                             , CheermotesResponse -> Maybe UTCTime
lastUpdated :: Maybe Time.UTCTime
                                             , CheermotesResponse -> Bool
charitable :: Bool
                                             } deriving ( CheermotesResponse -> CheermotesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheermotesResponse -> CheermotesResponse -> Bool
$c/= :: CheermotesResponse -> CheermotesResponse -> Bool
== :: CheermotesResponse -> CheermotesResponse -> Bool
$c== :: CheermotesResponse -> CheermotesResponse -> Bool
Eq, Int -> CheermotesResponse -> ShowS
[CheermotesResponse] -> ShowS
CheermotesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheermotesResponse] -> ShowS
$cshowList :: [CheermotesResponse] -> ShowS
show :: CheermotesResponse -> String
$cshow :: CheermotesResponse -> String
showsPrec :: Int -> CheermotesResponse -> ShowS
$cshowsPrec :: Int -> CheermotesResponse -> ShowS
Show )

instance FromJSON CheermotesResponse where
    parseJSON :: Value -> Parser CheermotesResponse
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CheermotesResponse" forall a b. (a -> b) -> a -> b
$ \Object
o -> do
        String
updated :: String <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"last_updated"
        let lastUpdated :: Maybe UTCTime
lastUpdated = ZonedTime -> UTCTime
Time.zonedTimeToUTC forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. TextualMonoid t => t -> Maybe ZonedTime
Time.parseTimeRFC3339 String
updated
        String
prefix <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"prefix"
        [CheermoteTier]
tiers <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"tiers"
        String
cheermoteType <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
        Integer
order <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"order"
        Bool
charitable <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"is_charitable"
        forall (m :: * -> *) a. Monad m => a -> m a
return CheermotesResponse{Bool
Integer
String
[CheermoteTier]
Maybe UTCTime
charitable :: Bool
order :: Integer
cheermoteType :: String
tiers :: [CheermoteTier]
prefix :: String
lastUpdated :: Maybe UTCTime
charitable :: Bool
lastUpdated :: Maybe UTCTime
order :: Integer
cheermoteType :: String
tiers :: [CheermoteTier]
prefix :: String
..}