{-# 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
(Int -> Leaderboard -> ShowS)
-> (Leaderboard -> String)
-> ([Leaderboard] -> ShowS)
-> Show Leaderboard
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Leaderboard -> ShowS
showsPrec :: Int -> Leaderboard -> ShowS
$cshow :: Leaderboard -> String
show :: Leaderboard -> String
$cshowList :: [Leaderboard] -> ShowS
showList :: [Leaderboard] -> ShowS
Show, Leaderboard -> Leaderboard -> Bool
(Leaderboard -> Leaderboard -> Bool)
-> (Leaderboard -> Leaderboard -> Bool) -> Eq Leaderboard
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Leaderboard -> Leaderboard -> Bool
== :: Leaderboard -> Leaderboard -> Bool
$c/= :: Leaderboard -> Leaderboard -> Bool
/= :: Leaderboard -> Leaderboard -> Bool
Eq )
data Period = Day | Week | Month | Year | All deriving ( Period -> Period -> Bool
(Period -> Period -> Bool)
-> (Period -> Period -> Bool) -> Eq Period
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Period -> Period -> Bool
== :: Period -> Period -> Bool
$c/= :: Period -> Period -> Bool
/= :: 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)] = [(ByteString, Maybe ByteString)]
-> (Integer -> [(ByteString, Maybe ByteString)])
-> Maybe Integer
-> [(ByteString, Maybe ByteString)]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Integer
c -> [(ByteString
"count", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> (Integer -> ByteString) -> Integer -> Maybe ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
BS.pack (String -> ByteString)
-> (Integer -> String) -> Integer -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> String
forall a. Show a => a -> String
show (Integer -> Maybe ByteString) -> Integer -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ Integer
c)]) (Leaderboard -> Maybe Integer
count Leaderboard
leaderboard)
[(ByteString, Maybe ByteString)]
period' :: [(BS.ByteString, Maybe BS.ByteString)] = [(ByteString, Maybe ByteString)]
-> (Period -> [(ByteString, Maybe ByteString)])
-> Maybe Period
-> [(ByteString, Maybe ByteString)]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Period
p -> [(ByteString
"period", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> (Period -> ByteString) -> Period -> Maybe ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
BS.pack (String -> ByteString)
-> (Period -> String) -> Period -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Period -> String
forall a. Show a => a -> String
show (Period -> Maybe ByteString) -> Period -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ Period
p)]) (Leaderboard -> Maybe Period
period Leaderboard
leaderboard)
[(ByteString, Maybe ByteString)]
start' :: [(BS.ByteString, Maybe BS.ByteString)] = [(ByteString, Maybe ByteString)]
-> (UTCTime -> [(ByteString, Maybe ByteString)])
-> Maybe UTCTime
-> [(ByteString, Maybe ByteString)]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\UTCTime
s -> [(ByteString
"started_at", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> (Text -> ByteString) -> Text -> Maybe ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
Text.encodeUtf8 (Text -> Maybe ByteString) -> Text -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ (ZonedTime -> Text
forall t. TextualMonoid t => ZonedTime -> t
Time.formatTimeRFC3339 (ZonedTime -> Text) -> ZonedTime -> Text
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)] = [(ByteString, Maybe ByteString)]
-> (Integer -> [(ByteString, Maybe ByteString)])
-> Maybe Integer
-> [(ByteString, Maybe ByteString)]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Integer
u -> [(ByteString
"user_id", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> (Integer -> ByteString) -> Integer -> Maybe ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
Text.encodeUtf8 (Text -> ByteString) -> (Integer -> Text) -> Integer -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack (String -> Text) -> (Integer -> String) -> Integer -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> String
forall a. Show a => a -> String
show (Integer -> Maybe ByteString) -> Integer -> Maybe ByteString
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 ([(ByteString, Maybe ByteString)] -> Request -> Request)
-> [(ByteString, Maybe ByteString)] -> Request -> Request
forall a b. (a -> b) -> a -> b
$ [[(ByteString, Maybe ByteString)]]
-> [(ByteString, Maybe ByteString)]
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 (Request -> Request) -> Request -> Request
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{} = String -> Maybe String
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
(Int -> LeaderboardEntry -> ShowS)
-> (LeaderboardEntry -> String)
-> ([LeaderboardEntry] -> ShowS)
-> Show LeaderboardEntry
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LeaderboardEntry -> ShowS
showsPrec :: Int -> LeaderboardEntry -> ShowS
$cshow :: LeaderboardEntry -> String
show :: LeaderboardEntry -> String
$cshowList :: [LeaderboardEntry] -> ShowS
showList :: [LeaderboardEntry] -> ShowS
Show, LeaderboardEntry -> LeaderboardEntry -> Bool
(LeaderboardEntry -> LeaderboardEntry -> Bool)
-> (LeaderboardEntry -> LeaderboardEntry -> Bool)
-> Eq LeaderboardEntry
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LeaderboardEntry -> LeaderboardEntry -> Bool
== :: LeaderboardEntry -> LeaderboardEntry -> Bool
$c/= :: LeaderboardEntry -> LeaderboardEntry -> Bool
/= :: LeaderboardEntry -> LeaderboardEntry -> Bool
Eq )
instance FromJSON LeaderboardEntry where
parseJSON :: Value -> Parser LeaderboardEntry
parseJSON = String
-> (Object -> Parser LeaderboardEntry)
-> Value
-> Parser LeaderboardEntry
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"LeaderboardEntry" ((Object -> Parser LeaderboardEntry)
-> Value -> Parser LeaderboardEntry)
-> (Object -> Parser LeaderboardEntry)
-> Value
-> Parser LeaderboardEntry
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
String
uid <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"user_id"
String
userLogin <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"user_login"
String
userName <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"user_login"
Integer
rank <- Object
o Object -> Key -> Parser Integer
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"rank"
Integer
score <- Object
o Object -> Key -> Parser Integer
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"score"
let userId :: Integer
userId = String -> Integer
forall a. Read a => String -> a
read String
uid :: Integer
LeaderboardEntry -> Parser LeaderboardEntry
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return LeaderboardEntry{Integer
String
userId :: Integer
userLogin :: String
userName :: String
rank :: Integer
score :: Integer
userLogin :: String
userName :: String
rank :: Integer
score :: Integer
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
(Int -> LeaderboardResponse -> ShowS)
-> (LeaderboardResponse -> String)
-> ([LeaderboardResponse] -> ShowS)
-> Show LeaderboardResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LeaderboardResponse -> ShowS
showsPrec :: Int -> LeaderboardResponse -> ShowS
$cshow :: LeaderboardResponse -> String
show :: LeaderboardResponse -> String
$cshowList :: [LeaderboardResponse] -> ShowS
showList :: [LeaderboardResponse] -> ShowS
Show, LeaderboardResponse -> LeaderboardResponse -> Bool
(LeaderboardResponse -> LeaderboardResponse -> Bool)
-> (LeaderboardResponse -> LeaderboardResponse -> Bool)
-> Eq LeaderboardResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LeaderboardResponse -> LeaderboardResponse -> Bool
== :: LeaderboardResponse -> LeaderboardResponse -> Bool
$c/= :: LeaderboardResponse -> LeaderboardResponse -> Bool
/= :: LeaderboardResponse -> LeaderboardResponse -> Bool
Eq)
instance FromJSON LeaderboardResponse where
parseJSON :: Value -> Parser LeaderboardResponse
parseJSON = String
-> (Object -> Parser LeaderboardResponse)
-> Value
-> Parser LeaderboardResponse
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"LeaderboardResponse" ((Object -> Parser LeaderboardResponse)
-> Value -> Parser LeaderboardResponse)
-> (Object -> Parser LeaderboardResponse)
-> Value
-> Parser LeaderboardResponse
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Object
dates :: Object <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"date_range"
String
ended :: String <- Object
dates Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"ended_at"
String
started :: String <- Object
dates Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"started_at"
[LeaderboardEntry]
entries :: [LeaderboardEntry] <- Object
o Object -> Key -> Parser [LeaderboardEntry]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"data"
Integer
total <- Object
o Object -> Key -> Parser Integer
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"total"
let endedAt :: Maybe UTCTime
endedAt = ZonedTime -> UTCTime
Time.zonedTimeToUTC (ZonedTime -> UTCTime) -> Maybe ZonedTime -> Maybe UTCTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> Maybe ZonedTime
forall t. TextualMonoid t => t -> Maybe ZonedTime
Time.parseTimeRFC3339 String
ended
startedAt :: Maybe UTCTime
startedAt = ZonedTime -> UTCTime
Time.zonedTimeToUTC (ZonedTime -> UTCTime) -> Maybe ZonedTime -> Maybe UTCTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> Maybe ZonedTime
forall t. TextualMonoid t => t -> Maybe ZonedTime
Time.parseTimeRFC3339 String
started
LeaderboardResponse -> Parser LeaderboardResponse
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return LeaderboardResponse{Integer
[LeaderboardEntry]
Maybe UTCTime
endedAt :: Maybe UTCTime
startedAt :: Maybe UTCTime
total :: Integer
entries :: [LeaderboardEntry]
entries :: [LeaderboardEntry]
total :: Integer
endedAt :: Maybe UTCTime
startedAt :: Maybe UTCTime
..}
newtype Cheermotes = Cheermotes { Cheermotes -> Integer
broadcasterId :: Integer } deriving ( Int -> Cheermotes -> ShowS
[Cheermotes] -> ShowS
Cheermotes -> String
(Int -> Cheermotes -> ShowS)
-> (Cheermotes -> String)
-> ([Cheermotes] -> ShowS)
-> Show Cheermotes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Cheermotes -> ShowS
showsPrec :: Int -> Cheermotes -> ShowS
$cshow :: Cheermotes -> String
show :: Cheermotes -> String
$cshowList :: [Cheermotes] -> ShowS
showList :: [Cheermotes] -> ShowS
Show, Cheermotes -> Cheermotes -> Bool
(Cheermotes -> Cheermotes -> Bool)
-> (Cheermotes -> Cheermotes -> Bool) -> Eq Cheermotes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Cheermotes -> Cheermotes -> Bool
== :: Cheermotes -> Cheermotes -> Bool
$c/= :: Cheermotes -> Cheermotes -> Bool
/= :: 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", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> (Integer -> ByteString) -> Integer -> Maybe ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
BS.pack (String -> ByteString)
-> (Integer -> String) -> Integer -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> String
forall a. Show a => a -> String
show (Integer -> Maybe ByteString) -> Integer -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ (Cheermotes -> Integer
broadcasterId :: Cheermotes -> Integer) Cheermotes
c)]
in Request -> Request
setQuery (Request -> Request) -> Request -> Request
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{} = Maybe String
forall a. Maybe a
Nothing
data CheermoteClass = GlobalFirstParty | GlobalThirdParty | ChannelCustom | DisplayOnly | | Unknown deriving ( CheermoteClass -> CheermoteClass -> Bool
(CheermoteClass -> CheermoteClass -> Bool)
-> (CheermoteClass -> CheermoteClass -> Bool) -> Eq CheermoteClass
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CheermoteClass -> CheermoteClass -> Bool
== :: CheermoteClass -> CheermoteClass -> Bool
$c/= :: CheermoteClass -> CheermoteClass -> Bool
/= :: CheermoteClass -> CheermoteClass -> Bool
Eq, Int -> CheermoteClass -> ShowS
[CheermoteClass] -> ShowS
CheermoteClass -> String
(Int -> CheermoteClass -> ShowS)
-> (CheermoteClass -> String)
-> ([CheermoteClass] -> ShowS)
-> Show CheermoteClass
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CheermoteClass -> ShowS
showsPrec :: Int -> CheermoteClass -> ShowS
$cshow :: CheermoteClass -> String
show :: CheermoteClass -> String
$cshowList :: [CheermoteClass] -> ShowS
showList :: [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
(CheermoteData -> CheermoteData -> Bool)
-> (CheermoteData -> CheermoteData -> Bool) -> Eq CheermoteData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CheermoteData -> CheermoteData -> Bool
== :: CheermoteData -> CheermoteData -> Bool
$c/= :: CheermoteData -> CheermoteData -> Bool
/= :: CheermoteData -> CheermoteData -> Bool
Eq, Int -> CheermoteData -> ShowS
[CheermoteData] -> ShowS
CheermoteData -> String
(Int -> CheermoteData -> ShowS)
-> (CheermoteData -> String)
-> ([CheermoteData] -> ShowS)
-> Show CheermoteData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CheermoteData -> ShowS
showsPrec :: Int -> CheermoteData -> ShowS
$cshow :: CheermoteData -> String
show :: CheermoteData -> String
$cshowList :: [CheermoteData] -> ShowS
showList :: [CheermoteData] -> ShowS
Show )
instance FromJSON CheermoteData where
parseJSON :: Value -> Parser CheermoteData
parseJSON = String
-> (Object -> Parser CheermoteData)
-> Value
-> Parser CheermoteData
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CheermoteData" ((Object -> Parser CheermoteData) -> Value -> Parser CheermoteData)
-> (Object -> Parser CheermoteData)
-> Value
-> Parser CheermoteData
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Maybe String
tinyURI <- Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"1"
Maybe String
smallURI <- Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"1.5"
Maybe String
mediumURI <- Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"2"
Maybe String
largeURI <- Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"3"
Maybe String
hugeURI <- Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"4"
CheermoteData -> Parser CheermoteData
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return CheermoteData{Maybe String
tinyURI :: Maybe String
smallURI :: Maybe String
mediumURI :: Maybe String
largeURI :: Maybe String
hugeURI :: Maybe String
tinyURI :: Maybe String
smallURI :: Maybe String
mediumURI :: Maybe String
largeURI :: Maybe String
hugeURI :: 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
(CheermoteImages -> CheermoteImages -> Bool)
-> (CheermoteImages -> CheermoteImages -> Bool)
-> Eq CheermoteImages
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CheermoteImages -> CheermoteImages -> Bool
== :: CheermoteImages -> CheermoteImages -> Bool
$c/= :: CheermoteImages -> CheermoteImages -> Bool
/= :: CheermoteImages -> CheermoteImages -> Bool
Eq, Int -> CheermoteImages -> ShowS
[CheermoteImages] -> ShowS
CheermoteImages -> String
(Int -> CheermoteImages -> ShowS)
-> (CheermoteImages -> String)
-> ([CheermoteImages] -> ShowS)
-> Show CheermoteImages
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CheermoteImages -> ShowS
showsPrec :: Int -> CheermoteImages -> ShowS
$cshow :: CheermoteImages -> String
show :: CheermoteImages -> String
$cshowList :: [CheermoteImages] -> ShowS
showList :: [CheermoteImages] -> ShowS
Show )
instance FromJSON CheermoteImages where
parseJSON :: Value -> Parser CheermoteImages
parseJSON = String
-> (Object -> Parser CheermoteImages)
-> Value
-> Parser CheermoteImages
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CheermoteImages" ((Object -> Parser CheermoteImages)
-> Value -> Parser CheermoteImages)
-> (Object -> Parser CheermoteImages)
-> Value
-> Parser CheermoteImages
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Object
dark :: Object <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"dark"
Object
light :: Object <- Object
o Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"light"
CheermoteData
darkAnimated <- Object
dark Object -> Key -> Parser CheermoteData
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"animated"
CheermoteData
darkStatic <- Object
dark Object -> Key -> Parser CheermoteData
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"static"
CheermoteData
lightAnimated <- Object
light Object -> Key -> Parser CheermoteData
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"animated"
CheermoteData
lightStatic <- Object
light Object -> Key -> Parser CheermoteData
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"static"
CheermoteImages -> Parser CheermoteImages
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return CheermoteImages{CheermoteData
darkAnimated :: CheermoteData
darkStatic :: CheermoteData
lightAnimated :: CheermoteData
lightStatic :: CheermoteData
darkAnimated :: CheermoteData
darkStatic :: CheermoteData
lightAnimated :: CheermoteData
lightStatic :: 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
(CheermoteTier -> CheermoteTier -> Bool)
-> (CheermoteTier -> CheermoteTier -> Bool) -> Eq CheermoteTier
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CheermoteTier -> CheermoteTier -> Bool
== :: CheermoteTier -> CheermoteTier -> Bool
$c/= :: CheermoteTier -> CheermoteTier -> Bool
/= :: CheermoteTier -> CheermoteTier -> Bool
Eq, Int -> CheermoteTier -> ShowS
[CheermoteTier] -> ShowS
CheermoteTier -> String
(Int -> CheermoteTier -> ShowS)
-> (CheermoteTier -> String)
-> ([CheermoteTier] -> ShowS)
-> Show CheermoteTier
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CheermoteTier -> ShowS
showsPrec :: Int -> CheermoteTier -> ShowS
$cshow :: CheermoteTier -> String
show :: CheermoteTier -> String
$cshowList :: [CheermoteTier] -> ShowS
showList :: [CheermoteTier] -> ShowS
Show )
instance FromJSON CheermoteTier where
parseJSON :: Value -> Parser CheermoteTier
parseJSON = String
-> (Object -> Parser CheermoteTier)
-> Value
-> Parser CheermoteTier
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CheermoteTier" ((Object -> Parser CheermoteTier) -> Value -> Parser CheermoteTier)
-> (Object -> Parser CheermoteTier)
-> Value
-> Parser CheermoteTier
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Integer
minBits <- Object
o Object -> Key -> Parser Integer
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"min_bits"
Integer
cheermoteId <- Object
o Object -> Key -> Parser Integer
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
String
color <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"color"
CheermoteImages
images <- Object
o Object -> Key -> Parser CheermoteImages
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"images"
Bool
enabled <- Object
o Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"can_cheer"
Bool
visible <- Object
o Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"show_in_bits_card"
CheermoteTier -> Parser CheermoteTier
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return CheermoteTier{Bool
Integer
String
CheermoteImages
minBits :: Integer
cheermoteId :: Integer
color :: String
images :: CheermoteImages
enabled :: Bool
visible :: Bool
minBits :: Integer
cheermoteId :: Integer
color :: String
images :: CheermoteImages
enabled :: Bool
visible :: Bool
..}
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
(CheermotesResponse -> CheermotesResponse -> Bool)
-> (CheermotesResponse -> CheermotesResponse -> Bool)
-> Eq CheermotesResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CheermotesResponse -> CheermotesResponse -> Bool
== :: CheermotesResponse -> CheermotesResponse -> Bool
$c/= :: CheermotesResponse -> CheermotesResponse -> Bool
/= :: CheermotesResponse -> CheermotesResponse -> Bool
Eq, Int -> CheermotesResponse -> ShowS
[CheermotesResponse] -> ShowS
CheermotesResponse -> String
(Int -> CheermotesResponse -> ShowS)
-> (CheermotesResponse -> String)
-> ([CheermotesResponse] -> ShowS)
-> Show CheermotesResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CheermotesResponse -> ShowS
showsPrec :: Int -> CheermotesResponse -> ShowS
$cshow :: CheermotesResponse -> String
show :: CheermotesResponse -> String
$cshowList :: [CheermotesResponse] -> ShowS
showList :: [CheermotesResponse] -> ShowS
Show )
instance FromJSON CheermotesResponse where
parseJSON :: Value -> Parser CheermotesResponse
parseJSON = String
-> (Object -> Parser CheermotesResponse)
-> Value
-> Parser CheermotesResponse
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CheermotesResponse" ((Object -> Parser CheermotesResponse)
-> Value -> Parser CheermotesResponse)
-> (Object -> Parser CheermotesResponse)
-> Value
-> Parser CheermotesResponse
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
String
updated :: String <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"last_updated"
let lastUpdated :: Maybe UTCTime
lastUpdated = ZonedTime -> UTCTime
Time.zonedTimeToUTC (ZonedTime -> UTCTime) -> Maybe ZonedTime -> Maybe UTCTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> Maybe ZonedTime
forall t. TextualMonoid t => t -> Maybe ZonedTime
Time.parseTimeRFC3339 String
updated
String
prefix <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"prefix"
[CheermoteTier]
tiers <- Object
o Object -> Key -> Parser [CheermoteTier]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"tiers"
String
cheermoteType <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
Integer
order <- Object
o Object -> Key -> Parser Integer
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"order"
Bool
charitable <- Object
o Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"is_charitable"
CheermotesResponse -> Parser CheermotesResponse
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return CheermotesResponse{Bool
Integer
String
[CheermoteTier]
Maybe UTCTime
prefix :: String
tiers :: [CheermoteTier]
cheermoteType :: String
order :: Integer
lastUpdated :: Maybe UTCTime
charitable :: Bool
lastUpdated :: Maybe UTCTime
prefix :: String
tiers :: [CheermoteTier]
cheermoteType :: String
order :: Integer
charitable :: Bool
..}