{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}

-- |
-- Module      : Network.Reddit.Types.Widget
-- Copyright   : (c) 2021 Rory Tyler Hayford
-- License     : BSD-3-Clause
-- Maintainer  : rory.hayford@protonmail.com
-- Stability   : experimental
-- Portability : GHC
--
module Network.Reddit.Types.Widget
    ( SubredditWidgets(..)
    , Widget(..)
    , WidgetID(WidgetID)
    , WidgetSection(..)
    , ShortName
    , mkShortName
    , WidgetList
    , WidgetStyles(..)
      -- * Individual widget types
      -- | All of the widget types in this module have a @widgetID@ field
      -- with the type @Maybe WidgetID@. This field /should/ be present
      -- when fetching existing widgets, but should be left as @Nothing@
      -- if creating a new widget
    , ButtonWidget(..)
    , Button(..)
    , ButtonImage(..)
    , ButtonText(..)
    , ButtonHover(..)
    , ImageHover(..)
    , TextHover(..)
    , CalendarWidget(..)
    , CalendarConfig(..)
    , defaultCalendarConfig
    , CommunityListWidget(..)
    , CommunityInfo(..)
    , mkCommunityInfo
    , CustomWidget(..)
    , ImageData(..)
    , IDCardWidget(..)
    , ImageWidget(..)
    , Image(..)
    , MenuWidget(..)
    , MenuChild(..)
    , MenuLink(..)
    , Submenu(..)
    , ModeratorsWidget(..)
    , ModInfo(..)
    , PostFlairWidget(..)
    , mkPostFlairWidget
    , PostFlairInfo(..)
    , PostFlairWidgetDisplay(..)
    , RulesWidget(..)
    , RulesDisplay(..)
    , TextAreaWidget(..)
    , mkTextAreaWidget
    ) where

import           Control.Applicative            ( optional )
import           Control.Monad                  ( guard )
import           Control.Monad.Catch            ( MonadThrow(throwM) )

import           Data.Aeson
                 ( (.:)
                 , (.:?)
                 , FromJSON(..)
                 , GToJSON'
                 , KeyValue((.=))
                 , Object
                 , Options(..)
                 , SumEncoding(UntaggedValue)
                 , ToJSON
                 , ToJSON(..)
                 , Value(..)
                 , Zero
                 , defaultOptions
                 , genericParseJSON
                 , genericToJSON
                 , object
                 , withObject
                 , withText
                 )
import           Data.Aeson.Types               ( Parser )
import           Data.Coerce                    ( coerce )
import qualified Data.HashMap.Strict            as HM
import           Data.HashMap.Strict            ( HashMap )
import           Data.Maybe
                 ( catMaybes
                 , fromMaybe
                 , mapMaybe
                 )
import           Data.Sequence                  ( Seq )
import           Data.Text                      ( Text )
import qualified Data.Text                      as T

import           GHC.Exts                       ( IsList(fromList) )
import           GHC.Generics                   ( Generic(Rep) )

import           Lens.Micro

import           Network.Reddit.Types.Flair
import           Network.Reddit.Types.Internal
import           Network.Reddit.Types.Subreddit

import           Web.HttpApiData                ( ToHttpApiData(..)
                                                , showTextData
                                                )

-- | An organized collection of a subreddit\'s widgets
data SubredditWidgets = SubredditWidgets
    { SubredditWidgets -> IDCardWidget
idCard       :: IDCardWidget
    , SubredditWidgets -> ModeratorsWidget
moderators   :: ModeratorsWidget
    , SubredditWidgets -> Seq Widget
topbar       :: Seq Widget
    , SubredditWidgets -> Seq Widget
sidebar      :: Seq Widget
    , SubredditWidgets -> Seq WidgetID
topbarOrder  :: Seq WidgetID
    , SubredditWidgets -> Seq WidgetID
sidebarOrder :: Seq WidgetID
    }
    deriving stock ( Int -> SubredditWidgets -> ShowS
[SubredditWidgets] -> ShowS
SubredditWidgets -> String
(Int -> SubredditWidgets -> ShowS)
-> (SubredditWidgets -> String)
-> ([SubredditWidgets] -> ShowS)
-> Show SubredditWidgets
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubredditWidgets] -> ShowS
$cshowList :: [SubredditWidgets] -> ShowS
show :: SubredditWidgets -> String
$cshow :: SubredditWidgets -> String
showsPrec :: Int -> SubredditWidgets -> ShowS
$cshowsPrec :: Int -> SubredditWidgets -> ShowS
Show, SubredditWidgets -> SubredditWidgets -> Bool
(SubredditWidgets -> SubredditWidgets -> Bool)
-> (SubredditWidgets -> SubredditWidgets -> Bool)
-> Eq SubredditWidgets
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubredditWidgets -> SubredditWidgets -> Bool
$c/= :: SubredditWidgets -> SubredditWidgets -> Bool
== :: SubredditWidgets -> SubredditWidgets -> Bool
$c== :: SubredditWidgets -> SubredditWidgets -> Bool
Eq, (forall x. SubredditWidgets -> Rep SubredditWidgets x)
-> (forall x. Rep SubredditWidgets x -> SubredditWidgets)
-> Generic SubredditWidgets
forall x. Rep SubredditWidgets x -> SubredditWidgets
forall x. SubredditWidgets -> Rep SubredditWidgets x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SubredditWidgets x -> SubredditWidgets
$cfrom :: forall x. SubredditWidgets -> Rep SubredditWidgets x
Generic )

instance FromJSON SubredditWidgets where
    parseJSON :: Value -> Parser SubredditWidgets
parseJSON = String
-> (Object -> Parser SubredditWidgets)
-> Value
-> Parser SubredditWidgets
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"SubredditWidgets" ((Object -> Parser SubredditWidgets)
 -> Value -> Parser SubredditWidgets)
-> (Object -> Parser SubredditWidgets)
-> Value
-> Parser SubredditWidgets
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
        Object
items :: Object <- Object
o Object -> Text -> Parser Object
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"items"
        Object
layout <- Object
o Object -> Text -> Parser Object
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"layout"

        let lookupWidget :: FromJSON b => Text -> Parser b
            lookupWidget :: Text -> Parser b
lookupWidget Text
fld = Parser b -> (Value -> Parser b) -> Maybe Value -> Parser b
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Parser b
forall a. Monoid a => a
mempty Value -> Parser b
forall a. FromJSON a => Value -> Parser a
parseJSON (Maybe Value -> Parser b)
-> (Text -> Maybe Value) -> Text -> Parser b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Object -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
`HM.lookup` Object
items)
                (Text -> Parser b) -> Parser Text -> Parser b
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
layout Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
fld

            lookupWidgets :: Text -> Parser (Seq Widget)
lookupWidgets Text
fld = ([Widget] -> Seq Widget) -> Parser [Widget] -> Parser (Seq Widget)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Widget] -> Seq Widget
forall l. IsList l => [Item l] -> l
fromList
                (Parser [Widget] -> Parser (Seq Widget))
-> ([Text] -> Parser [Widget]) -> [Text] -> Parser (Seq Widget)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Value -> Parser Widget) -> [Value] -> Parser [Widget]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Value -> Parser Widget
forall a. FromJSON a => Value -> Parser a
parseJSON
                ([Value] -> Parser [Widget])
-> ([Text] -> [Value]) -> [Text] -> Parser [Widget]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Maybe Value) -> [Text] -> [Value]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Text -> Object -> Maybe Value
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
`HM.lookup` Object
items)
                ([Text] -> Parser (Seq Widget))
-> Parser [Text] -> Parser (Seq Widget)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (Object -> Text -> Parser [Text]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"order")
                (Object -> Parser [Text]) -> Parser Object -> Parser [Text]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
layout Object -> Text -> Parser Object
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
fld

        IDCardWidget
idCard <- Text -> Parser IDCardWidget
forall b. FromJSON b => Text -> Parser b
lookupWidget Text
"idCardWidget"
        ModeratorsWidget
moderators <- Text -> Parser ModeratorsWidget
forall b. FromJSON b => Text -> Parser b
lookupWidget Text
"moderatorWidget"
        Seq Widget
topbar <- Text -> Parser (Seq Widget)
lookupWidgets Text
"topbar"
        Seq Widget
sidebar <- Text -> Parser (Seq Widget)
lookupWidgets Text
"sidebar"
        Seq WidgetID
topbarOrder <- (Object -> Text -> Parser (Seq WidgetID)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"order") (Object -> Parser (Seq WidgetID))
-> Parser Object -> Parser (Seq WidgetID)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
layout Object -> Text -> Parser Object
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"topbar"
        Seq WidgetID
sidebarOrder <- (Object -> Text -> Parser (Seq WidgetID)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"order") (Object -> Parser (Seq WidgetID))
-> Parser Object -> Parser (Seq WidgetID)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
layout Object -> Text -> Parser Object
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"sidebar"
        SubredditWidgets -> Parser SubredditWidgets
forall (f :: * -> *) a. Applicative f => a -> f a
pure SubredditWidgets :: IDCardWidget
-> ModeratorsWidget
-> Seq Widget
-> Seq Widget
-> Seq WidgetID
-> Seq WidgetID
-> SubredditWidgets
SubredditWidgets { Seq WidgetID
Seq Widget
ModeratorsWidget
IDCardWidget
sidebarOrder :: Seq WidgetID
topbarOrder :: Seq WidgetID
sidebar :: Seq Widget
topbar :: Seq Widget
moderators :: ModeratorsWidget
idCard :: IDCardWidget
$sel:sidebarOrder:SubredditWidgets :: Seq WidgetID
$sel:topbarOrder:SubredditWidgets :: Seq WidgetID
$sel:sidebar:SubredditWidgets :: Seq Widget
$sel:topbar:SubredditWidgets :: Seq Widget
$sel:moderators:SubredditWidgets :: ModeratorsWidget
$sel:idCard:SubredditWidgets :: IDCardWidget
.. }

-- | Represents one of various kinds of widgets
data Widget
    = Buttons ButtonWidget
    | Calendar CalendarWidget
    | CommunityList CommunityListWidget
    | Custom CustomWidget
    | IDCard IDCardWidget
    | Images ImageWidget
    | Moderators ModeratorsWidget
    | Menu MenuWidget
    | PostFlair PostFlairWidget
    | Rules RulesWidget
    | TextArea TextAreaWidget
    deriving stock ( Int -> Widget -> ShowS
[Widget] -> ShowS
Widget -> String
(Int -> Widget -> ShowS)
-> (Widget -> String) -> ([Widget] -> ShowS) -> Show Widget
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Widget] -> ShowS
$cshowList :: [Widget] -> ShowS
show :: Widget -> String
$cshow :: Widget -> String
showsPrec :: Int -> Widget -> ShowS
$cshowsPrec :: Int -> Widget -> ShowS
Show, Widget -> Widget -> Bool
(Widget -> Widget -> Bool)
-> (Widget -> Widget -> Bool) -> Eq Widget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Widget -> Widget -> Bool
$c/= :: Widget -> Widget -> Bool
== :: Widget -> Widget -> Bool
$c== :: Widget -> Widget -> Bool
Eq, (forall x. Widget -> Rep Widget x)
-> (forall x. Rep Widget x -> Widget) -> Generic Widget
forall x. Rep Widget x -> Widget
forall x. Widget -> Rep Widget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Widget x -> Widget
$cfrom :: forall x. Widget -> Rep Widget x
Generic )

instance FromJSON Widget where
    parseJSON :: Value -> Parser Widget
parseJSON =
        Options -> Value -> Parser Widget
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions { sumEncoding :: SumEncoding
sumEncoding = SumEncoding
UntaggedValue }

instance ToJSON Widget where
    toJSON :: Widget -> Value
toJSON = Options -> Widget -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
defaultOptions { sumEncoding :: SumEncoding
sumEncoding = SumEncoding
UntaggedValue }

-- | A widget ID. These are usually prefixed with the type of widget it corresponds
-- to, e.g. @rules-2qh1i@ for a 'RulesWidget'
newtype WidgetID = WidgetID Text
    deriving stock ( Int -> WidgetID -> ShowS
[WidgetID] -> ShowS
WidgetID -> String
(Int -> WidgetID -> ShowS)
-> (WidgetID -> String) -> ([WidgetID] -> ShowS) -> Show WidgetID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WidgetID] -> ShowS
$cshowList :: [WidgetID] -> ShowS
show :: WidgetID -> String
$cshow :: WidgetID -> String
showsPrec :: Int -> WidgetID -> ShowS
$cshowsPrec :: Int -> WidgetID -> ShowS
Show, (forall x. WidgetID -> Rep WidgetID x)
-> (forall x. Rep WidgetID x -> WidgetID) -> Generic WidgetID
forall x. Rep WidgetID x -> WidgetID
forall x. WidgetID -> Rep WidgetID x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WidgetID x -> WidgetID
$cfrom :: forall x. WidgetID -> Rep WidgetID x
Generic )
    deriving ( WidgetID -> WidgetID -> Bool
(WidgetID -> WidgetID -> Bool)
-> (WidgetID -> WidgetID -> Bool) -> Eq WidgetID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WidgetID -> WidgetID -> Bool
$c/= :: WidgetID -> WidgetID -> Bool
== :: WidgetID -> WidgetID -> Bool
$c== :: WidgetID -> WidgetID -> Bool
Eq ) via CIText WidgetID

instance ToHttpApiData WidgetID where
    toQueryParam :: WidgetID -> Text
toQueryParam (WidgetID Text
wid) = Text
"widget_" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
wid

instance FromJSON WidgetID where
    parseJSON :: Value -> Parser WidgetID
parseJSON = String -> (Text -> Parser WidgetID) -> Value -> Parser WidgetID
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"WidgetID" (Text -> Text -> Parser WidgetID
forall a. Coercible a Text => Text -> Text -> Parser a
breakOnType Text
"widget")

instance ToJSON WidgetID where
    toJSON :: WidgetID -> Value
toJSON = Text -> Value
String (Text -> Value) -> (WidgetID -> Text) -> WidgetID -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WidgetID -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam

-- | The section in which certain 'Widget's appear
data WidgetSection
    = Topbar
    | Sidebar
    deriving stock ( Int -> WidgetSection -> ShowS
[WidgetSection] -> ShowS
WidgetSection -> String
(Int -> WidgetSection -> ShowS)
-> (WidgetSection -> String)
-> ([WidgetSection] -> ShowS)
-> Show WidgetSection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WidgetSection] -> ShowS
$cshowList :: [WidgetSection] -> ShowS
show :: WidgetSection -> String
$cshow :: WidgetSection -> String
showsPrec :: Int -> WidgetSection -> ShowS
$cshowsPrec :: Int -> WidgetSection -> ShowS
Show, WidgetSection -> WidgetSection -> Bool
(WidgetSection -> WidgetSection -> Bool)
-> (WidgetSection -> WidgetSection -> Bool) -> Eq WidgetSection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WidgetSection -> WidgetSection -> Bool
$c/= :: WidgetSection -> WidgetSection -> Bool
== :: WidgetSection -> WidgetSection -> Bool
$c== :: WidgetSection -> WidgetSection -> Bool
Eq, (forall x. WidgetSection -> Rep WidgetSection x)
-> (forall x. Rep WidgetSection x -> WidgetSection)
-> Generic WidgetSection
forall x. Rep WidgetSection x -> WidgetSection
forall x. WidgetSection -> Rep WidgetSection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WidgetSection x -> WidgetSection
$cfrom :: forall x. WidgetSection -> Rep WidgetSection x
Generic )

instance ToHttpApiData WidgetSection where
    toUrlPiece :: WidgetSection -> Text
toUrlPiece = WidgetSection -> Text
forall a. Show a => a -> Text
showTextData

-- | A \"short name\" for any widget. This name must be less than 30 characters
-- long
newtype ShortName = ShortName Text
    deriving stock ( Int -> ShortName -> ShowS
[ShortName] -> ShowS
ShortName -> String
(Int -> ShortName -> ShowS)
-> (ShortName -> String)
-> ([ShortName] -> ShowS)
-> Show ShortName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ShortName] -> ShowS
$cshowList :: [ShortName] -> ShowS
show :: ShortName -> String
$cshow :: ShortName -> String
showsPrec :: Int -> ShortName -> ShowS
$cshowsPrec :: Int -> ShortName -> ShowS
Show, (forall x. ShortName -> Rep ShortName x)
-> (forall x. Rep ShortName x -> ShortName) -> Generic ShortName
forall x. Rep ShortName x -> ShortName
forall x. ShortName -> Rep ShortName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ShortName x -> ShortName
$cfrom :: forall x. ShortName -> Rep ShortName x
Generic )
    deriving newtype ( ShortName -> ShortName -> Bool
(ShortName -> ShortName -> Bool)
-> (ShortName -> ShortName -> Bool) -> Eq ShortName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ShortName -> ShortName -> Bool
$c/= :: ShortName -> ShortName -> Bool
== :: ShortName -> ShortName -> Bool
$c== :: ShortName -> ShortName -> Bool
Eq, Value -> Parser [ShortName]
Value -> Parser ShortName
(Value -> Parser ShortName)
-> (Value -> Parser [ShortName]) -> FromJSON ShortName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ShortName]
$cparseJSONList :: Value -> Parser [ShortName]
parseJSON :: Value -> Parser ShortName
$cparseJSON :: Value -> Parser ShortName
FromJSON, [ShortName] -> Encoding
[ShortName] -> Value
ShortName -> Encoding
ShortName -> Value
(ShortName -> Value)
-> (ShortName -> Encoding)
-> ([ShortName] -> Value)
-> ([ShortName] -> Encoding)
-> ToJSON ShortName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ShortName] -> Encoding
$ctoEncodingList :: [ShortName] -> Encoding
toJSONList :: [ShortName] -> Value
$ctoJSONList :: [ShortName] -> Value
toEncoding :: ShortName -> Encoding
$ctoEncoding :: ShortName -> Encoding
toJSON :: ShortName -> Value
$ctoJSON :: ShortName -> Value
ToJSON )

-- | Smart constructor for 'ShortName's, which must be <= 30 characters long
mkShortName :: MonadThrow m => Text -> m ShortName
mkShortName :: Text -> m ShortName
mkShortName Text
t
    | Text -> Int
T.length Text
t Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
30 =
        ClientException -> m ShortName
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (ClientException -> m ShortName) -> ClientException -> m ShortName
forall a b. (a -> b) -> a -> b
$ Text -> ClientException
OtherError Text
"mkShortName: Name must be <= 30 characters long"
    | Bool
otherwise = ShortName -> m ShortName
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ShortName -> m ShortName) -> ShortName -> m ShortName
forall a b. (a -> b) -> a -> b
$ Text -> ShortName
coerce Text
t

-- | Wrapper to parse a @HashMap WidgetID Widget@, discarding the ID keys
newtype WidgetList = WidgetList (Seq Widget)
    deriving stock ( Int -> WidgetList -> ShowS
[WidgetList] -> ShowS
WidgetList -> String
(Int -> WidgetList -> ShowS)
-> (WidgetList -> String)
-> ([WidgetList] -> ShowS)
-> Show WidgetList
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WidgetList] -> ShowS
$cshowList :: [WidgetList] -> ShowS
show :: WidgetList -> String
$cshow :: WidgetList -> String
showsPrec :: Int -> WidgetList -> ShowS
$cshowsPrec :: Int -> WidgetList -> ShowS
Show, (forall x. WidgetList -> Rep WidgetList x)
-> (forall x. Rep WidgetList x -> WidgetList) -> Generic WidgetList
forall x. Rep WidgetList x -> WidgetList
forall x. WidgetList -> Rep WidgetList x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WidgetList x -> WidgetList
$cfrom :: forall x. WidgetList -> Rep WidgetList x
Generic )

instance FromJSON WidgetList where
    parseJSON :: Value -> Parser WidgetList
parseJSON = String
-> (Object -> Parser WidgetList) -> Value -> Parser WidgetList
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"WidgetList" ((Object -> Parser WidgetList) -> Value -> Parser WidgetList)
-> (Object -> Parser WidgetList) -> Value -> Parser WidgetList
forall a b. (a -> b) -> a -> b
$ \Object
o -> Seq Widget -> WidgetList
WidgetList
        (Seq Widget -> WidgetList)
-> Parser (Seq Widget) -> Parser WidgetList
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object -> Parser (Seq Widget)
forall b. FromJSON b => Object -> Parser (Seq b)
getVals (Object -> Parser (Seq Widget))
-> Parser Object -> Parser (Seq Widget)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Text -> Parser Object
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"items")

-- | Style options for an individual widget
data WidgetStyles = WidgetStyles
    { WidgetStyles -> Maybe Text
backgroundColor :: Maybe RGBText --
    , WidgetStyles -> Maybe Text
headerColor     :: Maybe RGBText
    }
    deriving stock ( Int -> WidgetStyles -> ShowS
[WidgetStyles] -> ShowS
WidgetStyles -> String
(Int -> WidgetStyles -> ShowS)
-> (WidgetStyles -> String)
-> ([WidgetStyles] -> ShowS)
-> Show WidgetStyles
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WidgetStyles] -> ShowS
$cshowList :: [WidgetStyles] -> ShowS
show :: WidgetStyles -> String
$cshow :: WidgetStyles -> String
showsPrec :: Int -> WidgetStyles -> ShowS
$cshowsPrec :: Int -> WidgetStyles -> ShowS
Show, WidgetStyles -> WidgetStyles -> Bool
(WidgetStyles -> WidgetStyles -> Bool)
-> (WidgetStyles -> WidgetStyles -> Bool) -> Eq WidgetStyles
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WidgetStyles -> WidgetStyles -> Bool
$c/= :: WidgetStyles -> WidgetStyles -> Bool
== :: WidgetStyles -> WidgetStyles -> Bool
$c== :: WidgetStyles -> WidgetStyles -> Bool
Eq, (forall x. WidgetStyles -> Rep WidgetStyles x)
-> (forall x. Rep WidgetStyles x -> WidgetStyles)
-> Generic WidgetStyles
forall x. Rep WidgetStyles x -> WidgetStyles
forall x. WidgetStyles -> Rep WidgetStyles x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WidgetStyles x -> WidgetStyles
$cfrom :: forall x. WidgetStyles -> Rep WidgetStyles x
Generic )

instance FromJSON WidgetStyles where
    parseJSON :: Value -> Parser WidgetStyles
parseJSON = String
-> (Object -> Parser WidgetStyles) -> Value -> Parser WidgetStyles
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"WidgetStyles" ((Object -> Parser WidgetStyles) -> Value -> Parser WidgetStyles)
-> (Object -> Parser WidgetStyles) -> Value -> Parser WidgetStyles
forall a b. (a -> b) -> a -> b
$ \Object
o -> Maybe Text -> Maybe Text -> WidgetStyles
WidgetStyles
        (Maybe Text -> Maybe Text -> WidgetStyles)
-> Parser (Maybe Text) -> Parser (Maybe Text -> WidgetStyles)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser (Maybe Text)
-> (Text -> Parser (Maybe Text))
-> Maybe Text
-> Parser (Maybe Text)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Maybe Text -> Parser (Maybe Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Text
forall a. Maybe a
Nothing) Text -> Parser (Maybe Text)
forall a. FromJSON a => Text -> Parser (Maybe a)
nothingTxtNull (Maybe Text -> Parser (Maybe Text))
-> Parser (Maybe Text) -> Parser (Maybe Text)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"backgroundColor")
        Parser (Maybe Text -> WidgetStyles)
-> Parser (Maybe Text) -> Parser WidgetStyles
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Parser (Maybe Text)
-> (Text -> Parser (Maybe Text))
-> Maybe Text
-> Parser (Maybe Text)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Maybe Text -> Parser (Maybe Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Text
forall a. Maybe a
Nothing) Text -> Parser (Maybe Text)
forall a. FromJSON a => Text -> Parser (Maybe a)
nothingTxtNull (Maybe Text -> Parser (Maybe Text))
-> Parser (Maybe Text) -> Parser (Maybe Text)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"headerColor")

instance ToJSON WidgetStyles where
    toJSON :: WidgetStyles -> Value
toJSON = Options -> WidgetStyles -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
defaultOptions

-- | A widget containing buttons
data ButtonWidget = ButtonWidget
    { ButtonWidget -> Maybe WidgetID
widgetID        :: Maybe WidgetID
    , ButtonWidget -> ShortName
shortName       :: ShortName
    , ButtonWidget -> Seq Button
buttons         :: Seq Button
    , ButtonWidget -> Text
description     :: Body
    , ButtonWidget -> Maybe Text
descriptionHTML :: Maybe Body
    , ButtonWidget -> Maybe WidgetStyles
styles          :: Maybe WidgetStyles
    }
    deriving stock ( Int -> ButtonWidget -> ShowS
[ButtonWidget] -> ShowS
ButtonWidget -> String
(Int -> ButtonWidget -> ShowS)
-> (ButtonWidget -> String)
-> ([ButtonWidget] -> ShowS)
-> Show ButtonWidget
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ButtonWidget] -> ShowS
$cshowList :: [ButtonWidget] -> ShowS
show :: ButtonWidget -> String
$cshow :: ButtonWidget -> String
showsPrec :: Int -> ButtonWidget -> ShowS
$cshowsPrec :: Int -> ButtonWidget -> ShowS
Show, ButtonWidget -> ButtonWidget -> Bool
(ButtonWidget -> ButtonWidget -> Bool)
-> (ButtonWidget -> ButtonWidget -> Bool) -> Eq ButtonWidget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ButtonWidget -> ButtonWidget -> Bool
$c/= :: ButtonWidget -> ButtonWidget -> Bool
== :: ButtonWidget -> ButtonWidget -> Bool
$c== :: ButtonWidget -> ButtonWidget -> Bool
Eq, (forall x. ButtonWidget -> Rep ButtonWidget x)
-> (forall x. Rep ButtonWidget x -> ButtonWidget)
-> Generic ButtonWidget
forall x. Rep ButtonWidget x -> ButtonWidget
forall x. ButtonWidget -> Rep ButtonWidget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ButtonWidget x -> ButtonWidget
$cfrom :: forall x. ButtonWidget -> Rep ButtonWidget x
Generic )

instance FromJSON ButtonWidget where
    parseJSON :: Value -> Parser ButtonWidget
parseJSON = WidgetType
-> String
-> (Value -> Parser ButtonWidget)
-> Value
-> Parser ButtonWidget
forall a.
WidgetType -> String -> (Value -> Parser a) -> Value -> Parser a
withWidgetKind WidgetType
ButtonType String
"ButtonWidget"
        ((Value -> Parser ButtonWidget) -> Value -> Parser ButtonWidget)
-> (Value -> Parser ButtonWidget) -> Value -> Parser ButtonWidget
forall a b. (a -> b) -> a -> b
$ Options -> Value -> Parser ButtonWidget
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions
                           { fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
buttonWidgetModifier }

instance ToJSON ButtonWidget where
    toJSON :: ButtonWidget -> Value
toJSON = ShowS -> WidgetType -> ButtonWidget -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
ShowS -> WidgetType -> a -> Value
widgetToJSON ShowS
buttonWidgetModifier WidgetType
ButtonType

buttonWidgetModifier :: Modifier
buttonWidgetModifier :: ShowS
buttonWidgetModifier = \case
    String
"descriptionHTML" -> String
"descriptionHtml"
    String
s                 -> ShowS
defaultWidgetModifier String
s

-- | An individual button in a 'ButtonWidget'
data Button
    = ImageButton ButtonImage
    | TextButton ButtonText
    deriving stock ( Int -> Button -> ShowS
[Button] -> ShowS
Button -> String
(Int -> Button -> ShowS)
-> (Button -> String) -> ([Button] -> ShowS) -> Show Button
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Button] -> ShowS
$cshowList :: [Button] -> ShowS
show :: Button -> String
$cshow :: Button -> String
showsPrec :: Int -> Button -> ShowS
$cshowsPrec :: Int -> Button -> ShowS
Show, Button -> Button -> Bool
(Button -> Button -> Bool)
-> (Button -> Button -> Bool) -> Eq Button
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Button -> Button -> Bool
$c/= :: Button -> Button -> Bool
== :: Button -> Button -> Bool
$c== :: Button -> Button -> Bool
Eq, (forall x. Button -> Rep Button x)
-> (forall x. Rep Button x -> Button) -> Generic Button
forall x. Rep Button x -> Button
forall x. Button -> Rep Button x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Button x -> Button
$cfrom :: forall x. Button -> Rep Button x
Generic )

instance FromJSON Button where
    parseJSON :: Value -> Parser Button
parseJSON =
        Options -> Value -> Parser Button
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions { sumEncoding :: SumEncoding
sumEncoding = SumEncoding
UntaggedValue }

instance ToJSON Button where
    toJSON :: Button -> Value
toJSON Button
b = ShowS -> WidgetType -> Button -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
ShowS -> WidgetType -> a -> Value
widgetToJSON ShowS
defaultWidgetModifier WidgetType
buttonType Button
b
      where
        buttonType :: WidgetType
buttonType = case Button
b of
            ImageButton ButtonImage
_ -> WidgetType
ImageType
            TextButton ButtonText
_  -> WidgetType
TextType

-- | Data for an 'ImageButton'
data ButtonImage = ButtonImage
    { ButtonImage -> ShortName
text       :: ShortName
    , ButtonImage -> UploadURL
url        :: UploadURL
    , ButtonImage -> Text
linkURL    :: URL
    , ButtonImage -> Int
height     :: Int
    , ButtonImage -> Int
width      :: Int
    , ButtonImage -> Maybe ButtonHover
hoverState :: Maybe ButtonHover
    }
    deriving stock ( Int -> ButtonImage -> ShowS
[ButtonImage] -> ShowS
ButtonImage -> String
(Int -> ButtonImage -> ShowS)
-> (ButtonImage -> String)
-> ([ButtonImage] -> ShowS)
-> Show ButtonImage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ButtonImage] -> ShowS
$cshowList :: [ButtonImage] -> ShowS
show :: ButtonImage -> String
$cshow :: ButtonImage -> String
showsPrec :: Int -> ButtonImage -> ShowS
$cshowsPrec :: Int -> ButtonImage -> ShowS
Show, ButtonImage -> ButtonImage -> Bool
(ButtonImage -> ButtonImage -> Bool)
-> (ButtonImage -> ButtonImage -> Bool) -> Eq ButtonImage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ButtonImage -> ButtonImage -> Bool
$c/= :: ButtonImage -> ButtonImage -> Bool
== :: ButtonImage -> ButtonImage -> Bool
$c== :: ButtonImage -> ButtonImage -> Bool
Eq, (forall x. ButtonImage -> Rep ButtonImage x)
-> (forall x. Rep ButtonImage x -> ButtonImage)
-> Generic ButtonImage
forall x. Rep ButtonImage x -> ButtonImage
forall x. ButtonImage -> Rep ButtonImage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ButtonImage x -> ButtonImage
$cfrom :: forall x. ButtonImage -> Rep ButtonImage x
Generic )

instance FromJSON ButtonImage where
    parseJSON :: Value -> Parser ButtonImage
parseJSON =
        Options -> Value -> Parser ButtonImage
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions
                         { fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
imageButtonDataModifier }

instance ToJSON ButtonImage where
    toJSON :: ButtonImage -> Value
toJSON = Options -> ButtonImage -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
defaultOptions
                           { fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
imageButtonDataModifier
                           , omitNothingFields :: Bool
omitNothingFields  = Bool
True
                           }

imageButtonDataModifier :: Modifier
imageButtonDataModifier :: ShowS
imageButtonDataModifier = \case
    String
"linkURL" -> String
"linkUrl"
    String
s         -> String
s

-- | Data for a 'TextButton'
data ButtonText = ButtonText
    { ButtonText -> ShortName
text       :: ShortName
    , ButtonText -> Text
url        :: URL
    , ButtonText -> Text
color      :: RGBText
    , ButtonText -> Maybe Text
fillColor  :: Maybe RGBText
    , ButtonText -> Maybe Text
textColor  :: Maybe RGBText
    , ButtonText -> Maybe ButtonHover
hoverState :: Maybe ButtonHover
    }
    deriving stock ( Int -> ButtonText -> ShowS
[ButtonText] -> ShowS
ButtonText -> String
(Int -> ButtonText -> ShowS)
-> (ButtonText -> String)
-> ([ButtonText] -> ShowS)
-> Show ButtonText
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ButtonText] -> ShowS
$cshowList :: [ButtonText] -> ShowS
show :: ButtonText -> String
$cshow :: ButtonText -> String
showsPrec :: Int -> ButtonText -> ShowS
$cshowsPrec :: Int -> ButtonText -> ShowS
Show, ButtonText -> ButtonText -> Bool
(ButtonText -> ButtonText -> Bool)
-> (ButtonText -> ButtonText -> Bool) -> Eq ButtonText
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ButtonText -> ButtonText -> Bool
$c/= :: ButtonText -> ButtonText -> Bool
== :: ButtonText -> ButtonText -> Bool
$c== :: ButtonText -> ButtonText -> Bool
Eq, (forall x. ButtonText -> Rep ButtonText x)
-> (forall x. Rep ButtonText x -> ButtonText) -> Generic ButtonText
forall x. Rep ButtonText x -> ButtonText
forall x. ButtonText -> Rep ButtonText x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ButtonText x -> ButtonText
$cfrom :: forall x. ButtonText -> Rep ButtonText x
Generic )

instance FromJSON ButtonText

instance ToJSON ButtonText where
    toJSON :: ButtonText -> Value
toJSON = Options -> ButtonText -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
defaultOptions { omitNothingFields :: Bool
omitNothingFields = Bool
True }

-- | The state of the 'Button' when hovering over it
data ButtonHover
    = ImageButtonHover ImageHover
    | TextButtonHover TextHover
    deriving stock ( Int -> ButtonHover -> ShowS
[ButtonHover] -> ShowS
ButtonHover -> String
(Int -> ButtonHover -> ShowS)
-> (ButtonHover -> String)
-> ([ButtonHover] -> ShowS)
-> Show ButtonHover
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ButtonHover] -> ShowS
$cshowList :: [ButtonHover] -> ShowS
show :: ButtonHover -> String
$cshow :: ButtonHover -> String
showsPrec :: Int -> ButtonHover -> ShowS
$cshowsPrec :: Int -> ButtonHover -> ShowS
Show, ButtonHover -> ButtonHover -> Bool
(ButtonHover -> ButtonHover -> Bool)
-> (ButtonHover -> ButtonHover -> Bool) -> Eq ButtonHover
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ButtonHover -> ButtonHover -> Bool
$c/= :: ButtonHover -> ButtonHover -> Bool
== :: ButtonHover -> ButtonHover -> Bool
$c== :: ButtonHover -> ButtonHover -> Bool
Eq, (forall x. ButtonHover -> Rep ButtonHover x)
-> (forall x. Rep ButtonHover x -> ButtonHover)
-> Generic ButtonHover
forall x. Rep ButtonHover x -> ButtonHover
forall x. ButtonHover -> Rep ButtonHover x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ButtonHover x -> ButtonHover
$cfrom :: forall x. ButtonHover -> Rep ButtonHover x
Generic )

instance FromJSON ButtonHover where
    parseJSON :: Value -> Parser ButtonHover
parseJSON =
        Options -> Value -> Parser ButtonHover
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions { sumEncoding :: SumEncoding
sumEncoding = SumEncoding
UntaggedValue }

instance ToJSON ButtonHover where
    toJSON :: ButtonHover -> Value
toJSON = Options -> ButtonHover -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
defaultOptions { sumEncoding :: SumEncoding
sumEncoding = SumEncoding
UntaggedValue }

-- | The state of an 'ImageButton' when hovering over it
data ImageHover = ImageHover
    { ImageHover -> UploadURL
url :: UploadURL, ImageHover -> Maybe Integer
height :: Maybe Integer, ImageHover -> Maybe Integer
width :: Maybe Integer }
    deriving stock ( Int -> ImageHover -> ShowS
[ImageHover] -> ShowS
ImageHover -> String
(Int -> ImageHover -> ShowS)
-> (ImageHover -> String)
-> ([ImageHover] -> ShowS)
-> Show ImageHover
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImageHover] -> ShowS
$cshowList :: [ImageHover] -> ShowS
show :: ImageHover -> String
$cshow :: ImageHover -> String
showsPrec :: Int -> ImageHover -> ShowS
$cshowsPrec :: Int -> ImageHover -> ShowS
Show, ImageHover -> ImageHover -> Bool
(ImageHover -> ImageHover -> Bool)
-> (ImageHover -> ImageHover -> Bool) -> Eq ImageHover
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageHover -> ImageHover -> Bool
$c/= :: ImageHover -> ImageHover -> Bool
== :: ImageHover -> ImageHover -> Bool
$c== :: ImageHover -> ImageHover -> Bool
Eq, (forall x. ImageHover -> Rep ImageHover x)
-> (forall x. Rep ImageHover x -> ImageHover) -> Generic ImageHover
forall x. Rep ImageHover x -> ImageHover
forall x. ImageHover -> Rep ImageHover x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImageHover x -> ImageHover
$cfrom :: forall x. ImageHover -> Rep ImageHover x
Generic )

instance FromJSON ImageHover

instance ToJSON ImageHover where
    toJSON :: ImageHover -> Value
toJSON = ShowS -> WidgetType -> ImageHover -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
ShowS -> WidgetType -> a -> Value
widgetToJSON ShowS
forall a. a -> a
id WidgetType
ImageType

-- | The state of a 'TextButton' when hovering over it
data TextHover = TextHover
    { TextHover -> ShortName
text      :: ShortName
    , TextHover -> Maybe Text
color     :: Maybe RGBText
    , TextHover -> Maybe Text
fillColor :: Maybe RGBText
    , TextHover -> Maybe Text
textColor :: Maybe RGBText
    }
    deriving stock ( Int -> TextHover -> ShowS
[TextHover] -> ShowS
TextHover -> String
(Int -> TextHover -> ShowS)
-> (TextHover -> String)
-> ([TextHover] -> ShowS)
-> Show TextHover
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextHover] -> ShowS
$cshowList :: [TextHover] -> ShowS
show :: TextHover -> String
$cshow :: TextHover -> String
showsPrec :: Int -> TextHover -> ShowS
$cshowsPrec :: Int -> TextHover -> ShowS
Show, TextHover -> TextHover -> Bool
(TextHover -> TextHover -> Bool)
-> (TextHover -> TextHover -> Bool) -> Eq TextHover
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextHover -> TextHover -> Bool
$c/= :: TextHover -> TextHover -> Bool
== :: TextHover -> TextHover -> Bool
$c== :: TextHover -> TextHover -> Bool
Eq, (forall x. TextHover -> Rep TextHover x)
-> (forall x. Rep TextHover x -> TextHover) -> Generic TextHover
forall x. Rep TextHover x -> TextHover
forall x. TextHover -> Rep TextHover x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TextHover x -> TextHover
$cfrom :: forall x. TextHover -> Rep TextHover x
Generic )

instance FromJSON TextHover

instance ToJSON TextHover where
    toJSON :: TextHover -> Value
toJSON = ShowS -> WidgetType -> TextHover -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
ShowS -> WidgetType -> a -> Value
widgetToJSON ShowS
forall a. a -> a
id WidgetType
TextType

-- | A widget representing a calendar
data CalendarWidget = CalendarWidget
    { CalendarWidget -> Maybe WidgetID
widgetID         :: Maybe WidgetID
    , CalendarWidget -> ShortName
shortName        :: ShortName
    , CalendarWidget -> Text
googleCalendarID :: Text
    , CalendarWidget -> CalendarConfig
configuration    :: CalendarConfig
    , CalendarWidget -> Bool
requiresSync     :: Bool
    , CalendarWidget -> Maybe WidgetStyles
styles           :: Maybe WidgetStyles
    }
    deriving stock ( Int -> CalendarWidget -> ShowS
[CalendarWidget] -> ShowS
CalendarWidget -> String
(Int -> CalendarWidget -> ShowS)
-> (CalendarWidget -> String)
-> ([CalendarWidget] -> ShowS)
-> Show CalendarWidget
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CalendarWidget] -> ShowS
$cshowList :: [CalendarWidget] -> ShowS
show :: CalendarWidget -> String
$cshow :: CalendarWidget -> String
showsPrec :: Int -> CalendarWidget -> ShowS
$cshowsPrec :: Int -> CalendarWidget -> ShowS
Show, CalendarWidget -> CalendarWidget -> Bool
(CalendarWidget -> CalendarWidget -> Bool)
-> (CalendarWidget -> CalendarWidget -> Bool) -> Eq CalendarWidget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CalendarWidget -> CalendarWidget -> Bool
$c/= :: CalendarWidget -> CalendarWidget -> Bool
== :: CalendarWidget -> CalendarWidget -> Bool
$c== :: CalendarWidget -> CalendarWidget -> Bool
Eq, (forall x. CalendarWidget -> Rep CalendarWidget x)
-> (forall x. Rep CalendarWidget x -> CalendarWidget)
-> Generic CalendarWidget
forall x. Rep CalendarWidget x -> CalendarWidget
forall x. CalendarWidget -> Rep CalendarWidget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CalendarWidget x -> CalendarWidget
$cfrom :: forall x. CalendarWidget -> Rep CalendarWidget x
Generic )

instance FromJSON CalendarWidget where
    parseJSON :: Value -> Parser CalendarWidget
parseJSON = WidgetType
-> String
-> (Value -> Parser CalendarWidget)
-> Value
-> Parser CalendarWidget
forall a.
WidgetType -> String -> (Value -> Parser a) -> Value -> Parser a
withWidgetKind WidgetType
CalendarType String
"CalendarWidget"
        ((Value -> Parser CalendarWidget)
 -> Value -> Parser CalendarWidget)
-> (Value -> Parser CalendarWidget)
-> Value
-> Parser CalendarWidget
forall a b. (a -> b) -> a -> b
$ Options -> Value -> Parser CalendarWidget
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions
                           { fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
calendarModifier }

instance ToJSON CalendarWidget where
    toJSON :: CalendarWidget -> Value
toJSON = ShowS -> WidgetType -> CalendarWidget -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
ShowS -> WidgetType -> a -> Value
widgetToJSON ShowS
calendarModifier WidgetType
CalendarType

calendarModifier :: Modifier
calendarModifier :: ShowS
calendarModifier = \case
    String
"googleCalendarID" -> String
"googleCalendarId"
    String
s                  -> ShowS
defaultWidgetModifier String
s

-- | Configuration options for a 'CalendarWidget'
data CalendarConfig = CalendarConfig
    { -- | Between 1 and 50, defaulting to 10
      CalendarConfig -> Word
numEvents       :: Word
    , CalendarConfig -> Bool
showDate        :: Bool
    , CalendarConfig -> Bool
showDescription :: Bool
    , CalendarConfig -> Bool
showLocation    :: Bool
    , CalendarConfig -> Bool
showTime        :: Bool
    , CalendarConfig -> Bool
showTitle       :: Bool
    }
    deriving stock ( Int -> CalendarConfig -> ShowS
[CalendarConfig] -> ShowS
CalendarConfig -> String
(Int -> CalendarConfig -> ShowS)
-> (CalendarConfig -> String)
-> ([CalendarConfig] -> ShowS)
-> Show CalendarConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CalendarConfig] -> ShowS
$cshowList :: [CalendarConfig] -> ShowS
show :: CalendarConfig -> String
$cshow :: CalendarConfig -> String
showsPrec :: Int -> CalendarConfig -> ShowS
$cshowsPrec :: Int -> CalendarConfig -> ShowS
Show, CalendarConfig -> CalendarConfig -> Bool
(CalendarConfig -> CalendarConfig -> Bool)
-> (CalendarConfig -> CalendarConfig -> Bool) -> Eq CalendarConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CalendarConfig -> CalendarConfig -> Bool
$c/= :: CalendarConfig -> CalendarConfig -> Bool
== :: CalendarConfig -> CalendarConfig -> Bool
$c== :: CalendarConfig -> CalendarConfig -> Bool
Eq, (forall x. CalendarConfig -> Rep CalendarConfig x)
-> (forall x. Rep CalendarConfig x -> CalendarConfig)
-> Generic CalendarConfig
forall x. Rep CalendarConfig x -> CalendarConfig
forall x. CalendarConfig -> Rep CalendarConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CalendarConfig x -> CalendarConfig
$cfrom :: forall x. CalendarConfig -> Rep CalendarConfig x
Generic )

instance FromJSON CalendarConfig

instance ToJSON CalendarConfig

-- | A calendar config with default values
defaultCalendarConfig :: CalendarConfig
defaultCalendarConfig :: CalendarConfig
defaultCalendarConfig = CalendarConfig :: Word -> Bool -> Bool -> Bool -> Bool -> Bool -> CalendarConfig
CalendarConfig
    { $sel:numEvents:CalendarConfig :: Word
numEvents       = Word
10
    , $sel:showDate:CalendarConfig :: Bool
showDate        = Bool
False
    , $sel:showDescription:CalendarConfig :: Bool
showDescription = Bool
False
    , $sel:showLocation:CalendarConfig :: Bool
showLocation    = Bool
False
    , $sel:showTime:CalendarConfig :: Bool
showTime        = Bool
False
    , $sel:showTitle:CalendarConfig :: Bool
showTitle       = Bool
False
    }

-- | A widget listing related subreddits
data CommunityListWidget = CommunityListWidget
    { CommunityListWidget -> Maybe WidgetID
widgetID    :: Maybe WidgetID
    , CommunityListWidget -> ShortName
shortName   :: ShortName
    , CommunityListWidget -> Seq CommunityInfo
communities :: Seq CommunityInfo
    , CommunityListWidget -> Maybe WidgetStyles
styles      :: Maybe WidgetStyles
    }
    deriving stock ( Int -> CommunityListWidget -> ShowS
[CommunityListWidget] -> ShowS
CommunityListWidget -> String
(Int -> CommunityListWidget -> ShowS)
-> (CommunityListWidget -> String)
-> ([CommunityListWidget] -> ShowS)
-> Show CommunityListWidget
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommunityListWidget] -> ShowS
$cshowList :: [CommunityListWidget] -> ShowS
show :: CommunityListWidget -> String
$cshow :: CommunityListWidget -> String
showsPrec :: Int -> CommunityListWidget -> ShowS
$cshowsPrec :: Int -> CommunityListWidget -> ShowS
Show, CommunityListWidget -> CommunityListWidget -> Bool
(CommunityListWidget -> CommunityListWidget -> Bool)
-> (CommunityListWidget -> CommunityListWidget -> Bool)
-> Eq CommunityListWidget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommunityListWidget -> CommunityListWidget -> Bool
$c/= :: CommunityListWidget -> CommunityListWidget -> Bool
== :: CommunityListWidget -> CommunityListWidget -> Bool
$c== :: CommunityListWidget -> CommunityListWidget -> Bool
Eq, (forall x. CommunityListWidget -> Rep CommunityListWidget x)
-> (forall x. Rep CommunityListWidget x -> CommunityListWidget)
-> Generic CommunityListWidget
forall x. Rep CommunityListWidget x -> CommunityListWidget
forall x. CommunityListWidget -> Rep CommunityListWidget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CommunityListWidget x -> CommunityListWidget
$cfrom :: forall x. CommunityListWidget -> Rep CommunityListWidget x
Generic )

instance FromJSON CommunityListWidget where
    parseJSON :: Value -> Parser CommunityListWidget
parseJSON = WidgetType
-> String
-> (Value -> Parser CommunityListWidget)
-> Value
-> Parser CommunityListWidget
forall a.
WidgetType -> String -> (Value -> Parser a) -> Value -> Parser a
withWidgetKind WidgetType
CommunityListType String
"CommunityListWidget"
        ((Value -> Parser CommunityListWidget)
 -> Value -> Parser CommunityListWidget)
-> (Value -> Parser CommunityListWidget)
-> Value
-> Parser CommunityListWidget
forall a b. (a -> b) -> a -> b
$ Options -> Value -> Parser CommunityListWidget
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions { ShowS
fieldLabelModifier :: ShowS
fieldLabelModifier :: ShowS
fieldLabelModifier }
      where
        fieldLabelModifier :: ShowS
fieldLabelModifier = \case
            String
"communities" -> String
"data"
            String
s             -> ShowS
defaultWidgetModifier String
s

instance ToJSON CommunityListWidget where
    toJSON :: CommunityListWidget -> Value
toJSON CommunityListWidget { Maybe WidgetStyles
Maybe WidgetID
Seq CommunityInfo
ShortName
styles :: Maybe WidgetStyles
communities :: Seq CommunityInfo
shortName :: ShortName
widgetID :: Maybe WidgetID
$sel:styles:CommunityListWidget :: CommunityListWidget -> Maybe WidgetStyles
$sel:communities:CommunityListWidget :: CommunityListWidget -> Seq CommunityInfo
$sel:shortName:CommunityListWidget :: CommunityListWidget -> ShortName
$sel:widgetID:CommunityListWidget :: CommunityListWidget -> Maybe WidgetID
.. } = [Pair] -> Value
object
        ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [ Text
"shortName" Text -> ShortName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ShortName
shortName
            -- The @data@ field is not accepted in the same format as it is sent
          , Text
"data" Text -> Seq SubredditName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (Seq CommunityInfo
communities Seq CommunityInfo
-> (CommunityInfo -> SubredditName) -> Seq SubredditName
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \CommunityInfo { SubredditName
$sel:name:CommunityInfo :: CommunityInfo -> SubredditName
name :: SubredditName
name } -> SubredditName
name)
          , Text
"kind" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (Text
"community-list" :: Text)
          ]
        [Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> (Pair -> [Pair]) -> Maybe Pair -> [Pair]
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pair -> [Pair]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Text
"styles" Text -> WidgetStyles -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.=) (WidgetStyles -> Pair) -> Maybe WidgetStyles -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe WidgetStyles
styles)

-- | Information about a single subreddit in a 'CommunityListWidget'. When
-- creating a new widget, only the @name@ field will be serialized
data CommunityInfo = CommunityInfo
    { CommunityInfo -> SubredditName
name          :: SubredditName
    , CommunityInfo -> Maybe Integer
subscribers   :: Maybe Integer
    , CommunityInfo -> Maybe Text
primaryColor  :: Maybe RGBText
    , CommunityInfo -> Maybe Text
iconURL       :: Maybe URL
    , CommunityInfo -> Maybe Text
communityIcon :: Maybe URL
      -- | If the authenticated user is subscribed to the subreddit
    , CommunityInfo -> Maybe Bool
isSubscribed  :: Maybe Bool
    , CommunityInfo -> Maybe Bool
isNSFW        :: Maybe Bool
    }
    deriving stock ( Int -> CommunityInfo -> ShowS
[CommunityInfo] -> ShowS
CommunityInfo -> String
(Int -> CommunityInfo -> ShowS)
-> (CommunityInfo -> String)
-> ([CommunityInfo] -> ShowS)
-> Show CommunityInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommunityInfo] -> ShowS
$cshowList :: [CommunityInfo] -> ShowS
show :: CommunityInfo -> String
$cshow :: CommunityInfo -> String
showsPrec :: Int -> CommunityInfo -> ShowS
$cshowsPrec :: Int -> CommunityInfo -> ShowS
Show, CommunityInfo -> CommunityInfo -> Bool
(CommunityInfo -> CommunityInfo -> Bool)
-> (CommunityInfo -> CommunityInfo -> Bool) -> Eq CommunityInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommunityInfo -> CommunityInfo -> Bool
$c/= :: CommunityInfo -> CommunityInfo -> Bool
== :: CommunityInfo -> CommunityInfo -> Bool
$c== :: CommunityInfo -> CommunityInfo -> Bool
Eq, (forall x. CommunityInfo -> Rep CommunityInfo x)
-> (forall x. Rep CommunityInfo x -> CommunityInfo)
-> Generic CommunityInfo
forall x. Rep CommunityInfo x -> CommunityInfo
forall x. CommunityInfo -> Rep CommunityInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CommunityInfo x -> CommunityInfo
$cfrom :: forall x. CommunityInfo -> Rep CommunityInfo x
Generic )

instance FromJSON CommunityInfo where
    parseJSON :: Value -> Parser CommunityInfo
parseJSON = String
-> (Object -> Parser CommunityInfo)
-> Value
-> Parser CommunityInfo
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CommunityInfo" ((Object -> Parser CommunityInfo) -> Value -> Parser CommunityInfo)
-> (Object -> Parser CommunityInfo)
-> Value
-> Parser CommunityInfo
forall a b. (a -> b) -> a -> b
$ \Object
o -> SubredditName
-> Maybe Integer
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe Bool
-> CommunityInfo
CommunityInfo
        (SubredditName
 -> Maybe Integer
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Bool
 -> Maybe Bool
 -> CommunityInfo)
-> Parser SubredditName
-> Parser
     (Maybe Integer
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Bool
      -> CommunityInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser SubredditName
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"name"
        Parser
  (Maybe Integer
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Bool
   -> CommunityInfo)
-> Parser (Maybe Integer)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Bool
      -> CommunityInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe Integer)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"subscribers"
        Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Bool
   -> CommunityInfo)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text -> Maybe Bool -> Maybe Bool -> CommunityInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Text -> Parser (Maybe Text)
forall a. FromJSON a => Text -> Parser (Maybe a)
nothingTxtNull (Text -> Parser (Maybe Text)) -> Parser Text -> Parser (Maybe Text)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"primaryColor")
        Parser
  (Maybe Text
   -> Maybe Text -> Maybe Bool -> Maybe Bool -> CommunityInfo)
-> Parser (Maybe Text)
-> Parser (Maybe Text -> Maybe Bool -> Maybe Bool -> CommunityInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Text -> Parser (Maybe Text)
forall a. FromJSON a => Text -> Parser (Maybe a)
nothingTxtNull (Text -> Parser (Maybe Text)) -> Parser Text -> Parser (Maybe Text)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"iconUrl")
        Parser (Maybe Text -> Maybe Bool -> Maybe Bool -> CommunityInfo)
-> Parser (Maybe Text)
-> Parser (Maybe Bool -> Maybe Bool -> CommunityInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Text -> Parser (Maybe Text)
forall a. FromJSON a => Text -> Parser (Maybe a)
nothingTxtNull (Text -> Parser (Maybe Text)) -> Parser Text -> Parser (Maybe Text)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"communityIcon")
        Parser (Maybe Bool -> Maybe Bool -> CommunityInfo)
-> Parser (Maybe Bool) -> Parser (Maybe Bool -> CommunityInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"isSubscribed"
        Parser (Maybe Bool -> CommunityInfo)
-> Parser (Maybe Bool) -> Parser CommunityInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"isNSFW"

instance ToJSON CommunityInfo where
    toJSON :: CommunityInfo -> Value
toJSON CommunityInfo { SubredditName
name :: SubredditName
$sel:name:CommunityInfo :: CommunityInfo -> SubredditName
name } = [Pair] -> Value
object [ Text
"name" Text -> SubredditName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= SubredditName
name ]

-- | Convenience function for creating a new 'CommunityInfo', where
-- all but one of the fields should be @Nothing@
mkCommunityInfo :: SubredditName -> CommunityInfo
mkCommunityInfo :: SubredditName -> CommunityInfo
mkCommunityInfo SubredditName
name = CommunityInfo :: SubredditName
-> Maybe Integer
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe Bool
-> CommunityInfo
CommunityInfo
    { SubredditName
name :: SubredditName
$sel:name:CommunityInfo :: SubredditName
name
    , $sel:subscribers:CommunityInfo :: Maybe Integer
subscribers   = Maybe Integer
forall a. Maybe a
Nothing
    , $sel:primaryColor:CommunityInfo :: Maybe Text
primaryColor  = Maybe Text
forall a. Maybe a
Nothing
    , $sel:iconURL:CommunityInfo :: Maybe Text
iconURL       = Maybe Text
forall a. Maybe a
Nothing
    , $sel:communityIcon:CommunityInfo :: Maybe Text
communityIcon = Maybe Text
forall a. Maybe a
Nothing
    , $sel:isSubscribed:CommunityInfo :: Maybe Bool
isSubscribed  = Maybe Bool
forall a. Maybe a
Nothing
    , $sel:isNSFW:CommunityInfo :: Maybe Bool
isNSFW        = Maybe Bool
forall a. Maybe a
Nothing
    }

-- | A custom widget
data CustomWidget = CustomWidget
    { CustomWidget -> Maybe WidgetID
widgetID      :: Maybe WidgetID
    , CustomWidget -> ShortName
shortName     :: ShortName
    , CustomWidget -> Text
text          :: Body
    , CustomWidget -> Seq ImageData
imageData     :: Seq ImageData
      -- | Should be between 50 and 500
    , CustomWidget -> Int
height        :: Int
      -- | Should be @Nothing@ when creating a new widget
    , CustomWidget -> Maybe Text
textHTML      :: Maybe Body
    , CustomWidget -> Maybe Text
css           :: Maybe Text
    , CustomWidget -> Maybe Text
stylesheetURL :: Maybe URL
    , CustomWidget -> Maybe WidgetStyles
styles        :: Maybe WidgetStyles
    }
    deriving stock ( Int -> CustomWidget -> ShowS
[CustomWidget] -> ShowS
CustomWidget -> String
(Int -> CustomWidget -> ShowS)
-> (CustomWidget -> String)
-> ([CustomWidget] -> ShowS)
-> Show CustomWidget
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CustomWidget] -> ShowS
$cshowList :: [CustomWidget] -> ShowS
show :: CustomWidget -> String
$cshow :: CustomWidget -> String
showsPrec :: Int -> CustomWidget -> ShowS
$cshowsPrec :: Int -> CustomWidget -> ShowS
Show, CustomWidget -> CustomWidget -> Bool
(CustomWidget -> CustomWidget -> Bool)
-> (CustomWidget -> CustomWidget -> Bool) -> Eq CustomWidget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CustomWidget -> CustomWidget -> Bool
$c/= :: CustomWidget -> CustomWidget -> Bool
== :: CustomWidget -> CustomWidget -> Bool
$c== :: CustomWidget -> CustomWidget -> Bool
Eq, (forall x. CustomWidget -> Rep CustomWidget x)
-> (forall x. Rep CustomWidget x -> CustomWidget)
-> Generic CustomWidget
forall x. Rep CustomWidget x -> CustomWidget
forall x. CustomWidget -> Rep CustomWidget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CustomWidget x -> CustomWidget
$cfrom :: forall x. CustomWidget -> Rep CustomWidget x
Generic )

instance FromJSON CustomWidget where
    parseJSON :: Value -> Parser CustomWidget
parseJSON = WidgetType
-> String
-> (Value -> Parser CustomWidget)
-> Value
-> Parser CustomWidget
forall a.
WidgetType -> String -> (Value -> Parser a) -> Value -> Parser a
withWidgetKind WidgetType
CustomType String
"CustomWidget" Value -> Parser CustomWidget
customP
      where
        customP :: Value -> Parser CustomWidget
customP (Object Object
o) = Maybe WidgetID
-> ShortName
-> Text
-> Seq ImageData
-> Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe WidgetStyles
-> CustomWidget
CustomWidget (Maybe WidgetID
 -> ShortName
 -> Text
 -> Seq ImageData
 -> Int
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe WidgetStyles
 -> CustomWidget)
-> Parser (Maybe WidgetID)
-> Parser
     (ShortName
      -> Text
      -> Seq ImageData
      -> Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe WidgetStyles
      -> CustomWidget)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser (Maybe WidgetID)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id"
            Parser
  (ShortName
   -> Text
   -> Seq ImageData
   -> Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe WidgetStyles
   -> CustomWidget)
-> Parser ShortName
-> Parser
     (Text
      -> Seq ImageData
      -> Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe WidgetStyles
      -> CustomWidget)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser ShortName
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"shortName"
            Parser
  (Text
   -> Seq ImageData
   -> Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe WidgetStyles
   -> CustomWidget)
-> Parser Text
-> Parser
     (Seq ImageData
      -> Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe WidgetStyles
      -> CustomWidget)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"text"
            Parser
  (Seq ImageData
   -> Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe WidgetStyles
   -> CustomWidget)
-> Parser (Seq ImageData)
-> Parser
     (Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe WidgetStyles
      -> CustomWidget)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Seq ImageData)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"imageData"
            Parser
  (Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe WidgetStyles
   -> CustomWidget)
-> Parser Int
-> Parser
     (Maybe Text
      -> Maybe Text -> Maybe Text -> Maybe WidgetStyles -> CustomWidget)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"height"
            Parser
  (Maybe Text
   -> Maybe Text -> Maybe Text -> Maybe WidgetStyles -> CustomWidget)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text -> Maybe Text -> Maybe WidgetStyles -> CustomWidget)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"textHtml"
            Parser
  (Maybe Text -> Maybe Text -> Maybe WidgetStyles -> CustomWidget)
-> Parser (Maybe Text)
-> Parser (Maybe Text -> Maybe WidgetStyles -> CustomWidget)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Text -> Parser (Maybe Text)
forall a. FromJSON a => Text -> Parser (Maybe a)
nothingTxtNull (Text -> Parser (Maybe Text)) -> Parser Text -> Parser (Maybe Text)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"css")
            Parser (Maybe Text -> Maybe WidgetStyles -> CustomWidget)
-> Parser (Maybe Text)
-> Parser (Maybe WidgetStyles -> CustomWidget)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"stylesheetUrl"
            Parser (Maybe WidgetStyles -> CustomWidget)
-> Parser (Maybe WidgetStyles) -> Parser CustomWidget
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe WidgetStyles)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"styles"
        customP Value
_          = Parser CustomWidget
forall a. Monoid a => a
mempty

instance ToJSON CustomWidget where
    toJSON :: CustomWidget -> Value
toJSON CustomWidget { Int
Maybe Text
Maybe WidgetStyles
Maybe WidgetID
Text
Seq ImageData
ShortName
styles :: Maybe WidgetStyles
stylesheetURL :: Maybe Text
css :: Maybe Text
textHTML :: Maybe Text
height :: Int
imageData :: Seq ImageData
text :: Text
shortName :: ShortName
widgetID :: Maybe WidgetID
$sel:styles:CustomWidget :: CustomWidget -> Maybe WidgetStyles
$sel:stylesheetURL:CustomWidget :: CustomWidget -> Maybe Text
$sel:css:CustomWidget :: CustomWidget -> Maybe Text
$sel:textHTML:CustomWidget :: CustomWidget -> Maybe Text
$sel:height:CustomWidget :: CustomWidget -> Int
$sel:imageData:CustomWidget :: CustomWidget -> Seq ImageData
$sel:text:CustomWidget :: CustomWidget -> Text
$sel:shortName:CustomWidget :: CustomWidget -> ShortName
$sel:widgetID:CustomWidget :: CustomWidget -> Maybe WidgetID
.. } = [Pair] -> Value
object
        ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [ Text
"shortName" Text -> ShortName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ShortName
shortName
          , Text
"text" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
text
          , Text
"imageData" Text -> Seq ImageData -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Seq ImageData
imageData
          , Text
"height" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Int
height
            -- Reddit won't accept empty CSS, so this will prevent an error
            -- in case the @css@ field is empty
          , Text
"css" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"/**/" Maybe Text
css
          , Text
"kind" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (Text
"custom" :: Text)
          ]
        [Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> [Maybe Pair] -> [Pair]
forall a. [Maybe a] -> [a]
catMaybes [ (Text
"stylesheetUrl" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.=) (Text -> Pair) -> Maybe Text -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
stylesheetURL
                     , (Text
"styles" Text -> WidgetStyles -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.=) (WidgetStyles -> Pair) -> Maybe WidgetStyles -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe WidgetStyles
styles
                     ]

-- | Image data that belongs to a 'CustomWidget'
data ImageData = ImageData
    { ImageData -> Text
name   :: Name
    , ImageData -> Int
height :: Int
    , ImageData -> Int
width  :: Int
      -- | This url must point to an image hosted by Reddit
    , ImageData -> UploadURL
url    :: UploadURL
    }
    deriving stock ( Int -> ImageData -> ShowS
[ImageData] -> ShowS
ImageData -> String
(Int -> ImageData -> ShowS)
-> (ImageData -> String)
-> ([ImageData] -> ShowS)
-> Show ImageData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImageData] -> ShowS
$cshowList :: [ImageData] -> ShowS
show :: ImageData -> String
$cshow :: ImageData -> String
showsPrec :: Int -> ImageData -> ShowS
$cshowsPrec :: Int -> ImageData -> ShowS
Show, ImageData -> ImageData -> Bool
(ImageData -> ImageData -> Bool)
-> (ImageData -> ImageData -> Bool) -> Eq ImageData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageData -> ImageData -> Bool
$c/= :: ImageData -> ImageData -> Bool
== :: ImageData -> ImageData -> Bool
$c== :: ImageData -> ImageData -> Bool
Eq, (forall x. ImageData -> Rep ImageData x)
-> (forall x. Rep ImageData x -> ImageData) -> Generic ImageData
forall x. Rep ImageData x -> ImageData
forall x. ImageData -> Rep ImageData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImageData x -> ImageData
$cfrom :: forall x. ImageData -> Rep ImageData x
Generic )

instance FromJSON ImageData

instance ToJSON ImageData

-- | An ID card displaying information about the subreddit
data IDCardWidget = IDCardWidget
    { IDCardWidget -> Maybe WidgetID
widgetID              :: Maybe WidgetID
    , IDCardWidget -> ShortName
shortName             :: ShortName
    , IDCardWidget -> Text
description           :: Body
    , IDCardWidget -> Text
subscribersText       :: Text
    , IDCardWidget -> Text
currentlyViewingText  :: Text
    , IDCardWidget -> Maybe Integer
subscribersCount      :: Maybe Integer
    , IDCardWidget -> Maybe Integer
currentlyViewingCount :: Maybe Integer
    , IDCardWidget -> Maybe WidgetStyles
styles                :: Maybe WidgetStyles
    }
    deriving stock ( Int -> IDCardWidget -> ShowS
[IDCardWidget] -> ShowS
IDCardWidget -> String
(Int -> IDCardWidget -> ShowS)
-> (IDCardWidget -> String)
-> ([IDCardWidget] -> ShowS)
-> Show IDCardWidget
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IDCardWidget] -> ShowS
$cshowList :: [IDCardWidget] -> ShowS
show :: IDCardWidget -> String
$cshow :: IDCardWidget -> String
showsPrec :: Int -> IDCardWidget -> ShowS
$cshowsPrec :: Int -> IDCardWidget -> ShowS
Show, IDCardWidget -> IDCardWidget -> Bool
(IDCardWidget -> IDCardWidget -> Bool)
-> (IDCardWidget -> IDCardWidget -> Bool) -> Eq IDCardWidget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IDCardWidget -> IDCardWidget -> Bool
$c/= :: IDCardWidget -> IDCardWidget -> Bool
== :: IDCardWidget -> IDCardWidget -> Bool
$c== :: IDCardWidget -> IDCardWidget -> Bool
Eq, (forall x. IDCardWidget -> Rep IDCardWidget x)
-> (forall x. Rep IDCardWidget x -> IDCardWidget)
-> Generic IDCardWidget
forall x. Rep IDCardWidget x -> IDCardWidget
forall x. IDCardWidget -> Rep IDCardWidget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IDCardWidget x -> IDCardWidget
$cfrom :: forall x. IDCardWidget -> Rep IDCardWidget x
Generic )

instance FromJSON IDCardWidget where
    parseJSON :: Value -> Parser IDCardWidget
parseJSON = WidgetType
-> String
-> (Value -> Parser IDCardWidget)
-> Value
-> Parser IDCardWidget
forall a.
WidgetType -> String -> (Value -> Parser a) -> Value -> Parser a
withWidgetKind WidgetType
IDCardType String
"IDCardWidget" Value -> Parser IDCardWidget
idCardP
      where
        idCardP :: Value -> Parser IDCardWidget
idCardP (Object Object
o) = Maybe WidgetID
-> ShortName
-> Text
-> Text
-> Text
-> Maybe Integer
-> Maybe Integer
-> Maybe WidgetStyles
-> IDCardWidget
IDCardWidget (Maybe WidgetID
 -> ShortName
 -> Text
 -> Text
 -> Text
 -> Maybe Integer
 -> Maybe Integer
 -> Maybe WidgetStyles
 -> IDCardWidget)
-> Parser (Maybe WidgetID)
-> Parser
     (ShortName
      -> Text
      -> Text
      -> Text
      -> Maybe Integer
      -> Maybe Integer
      -> Maybe WidgetStyles
      -> IDCardWidget)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser (Maybe WidgetID)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id"
            Parser
  (ShortName
   -> Text
   -> Text
   -> Text
   -> Maybe Integer
   -> Maybe Integer
   -> Maybe WidgetStyles
   -> IDCardWidget)
-> Parser ShortName
-> Parser
     (Text
      -> Text
      -> Text
      -> Maybe Integer
      -> Maybe Integer
      -> Maybe WidgetStyles
      -> IDCardWidget)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser ShortName
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"shortName"
            -- This field is missing after updates
            Parser
  (Text
   -> Text
   -> Text
   -> Maybe Integer
   -> Maybe Integer
   -> Maybe WidgetStyles
   -> IDCardWidget)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Maybe Integer
      -> Maybe Integer
      -> Maybe WidgetStyles
      -> IDCardWidget)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
forall a. Monoid a => a
mempty (Maybe Text -> Text) -> Parser (Maybe Text) -> Parser Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text -> Parser (Maybe Text)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"description"))
            Parser
  (Text
   -> Text
   -> Maybe Integer
   -> Maybe Integer
   -> Maybe WidgetStyles
   -> IDCardWidget)
-> Parser Text
-> Parser
     (Text
      -> Maybe Integer
      -> Maybe Integer
      -> Maybe WidgetStyles
      -> IDCardWidget)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"subscribersText"
            Parser
  (Text
   -> Maybe Integer
   -> Maybe Integer
   -> Maybe WidgetStyles
   -> IDCardWidget)
-> Parser Text
-> Parser
     (Maybe Integer
      -> Maybe Integer -> Maybe WidgetStyles -> IDCardWidget)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"currentlyViewingText"
            Parser
  (Maybe Integer
   -> Maybe Integer -> Maybe WidgetStyles -> IDCardWidget)
-> Parser (Maybe Integer)
-> Parser (Maybe Integer -> Maybe WidgetStyles -> IDCardWidget)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe Integer)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"subscribersCount"
            Parser (Maybe Integer -> Maybe WidgetStyles -> IDCardWidget)
-> Parser (Maybe Integer)
-> Parser (Maybe WidgetStyles -> IDCardWidget)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe Integer)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"currentlyViewingCount"
            Parser (Maybe WidgetStyles -> IDCardWidget)
-> Parser (Maybe WidgetStyles) -> Parser IDCardWidget
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe WidgetStyles)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"styles"
        idCardP Value
_          = Parser IDCardWidget
forall a. Monoid a => a
mempty

instance ToJSON IDCardWidget where
    toJSON :: IDCardWidget -> Value
toJSON = ShowS -> WidgetType -> IDCardWidget -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
ShowS -> WidgetType -> a -> Value
widgetToJSON ShowS
defaultWidgetModifier WidgetType
IDCardType

-- | A widget composed of various 'Image's
data ImageWidget = ImageWidget
    { ImageWidget -> Maybe WidgetID
widgetID  :: Maybe WidgetID
    , ImageWidget -> ShortName
shortName :: ShortName
    , ImageWidget -> Seq Image
images    :: Seq Image
    , ImageWidget -> Maybe WidgetStyles
styles    :: Maybe WidgetStyles
    }
    deriving stock ( Int -> ImageWidget -> ShowS
[ImageWidget] -> ShowS
ImageWidget -> String
(Int -> ImageWidget -> ShowS)
-> (ImageWidget -> String)
-> ([ImageWidget] -> ShowS)
-> Show ImageWidget
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImageWidget] -> ShowS
$cshowList :: [ImageWidget] -> ShowS
show :: ImageWidget -> String
$cshow :: ImageWidget -> String
showsPrec :: Int -> ImageWidget -> ShowS
$cshowsPrec :: Int -> ImageWidget -> ShowS
Show, ImageWidget -> ImageWidget -> Bool
(ImageWidget -> ImageWidget -> Bool)
-> (ImageWidget -> ImageWidget -> Bool) -> Eq ImageWidget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageWidget -> ImageWidget -> Bool
$c/= :: ImageWidget -> ImageWidget -> Bool
== :: ImageWidget -> ImageWidget -> Bool
$c== :: ImageWidget -> ImageWidget -> Bool
Eq, (forall x. ImageWidget -> Rep ImageWidget x)
-> (forall x. Rep ImageWidget x -> ImageWidget)
-> Generic ImageWidget
forall x. Rep ImageWidget x -> ImageWidget
forall x. ImageWidget -> Rep ImageWidget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImageWidget x -> ImageWidget
$cfrom :: forall x. ImageWidget -> Rep ImageWidget x
Generic )

instance FromJSON ImageWidget where
    parseJSON :: Value -> Parser ImageWidget
parseJSON = WidgetType
-> String
-> (Value -> Parser ImageWidget)
-> Value
-> Parser ImageWidget
forall a.
WidgetType -> String -> (Value -> Parser a) -> Value -> Parser a
withWidgetKind WidgetType
ImageType String
"ImageWidget"
        ((Value -> Parser ImageWidget) -> Value -> Parser ImageWidget)
-> (Value -> Parser ImageWidget) -> Value -> Parser ImageWidget
forall a b. (a -> b) -> a -> b
$ Options -> Value -> Parser ImageWidget
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions
                           { fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
imageWidgetModifier }

instance ToJSON ImageWidget where
    toJSON :: ImageWidget -> Value
toJSON = ShowS -> WidgetType -> ImageWidget -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
ShowS -> WidgetType -> a -> Value
widgetToJSON ShowS
imageWidgetModifier WidgetType
ImageType

imageWidgetModifier :: Modifier
imageWidgetModifier :: ShowS
imageWidgetModifier = \case
    String
"images" -> String
"data"
    String
s        -> ShowS
defaultWidgetModifier String
s

-- | An individual image in an 'ImageWidget'
data Image = Image
    { Image -> Integer
width   :: Integer
    , Image -> Integer
height  :: Integer
      -- | The reddit-hosted image URL
    , Image -> UploadURL
url     :: UploadURL
      -- | The link that is followed when clicking on the image
    , Image -> Maybe Text
linkURL :: Maybe URL
    }
    deriving stock ( Int -> Image -> ShowS
[Image] -> ShowS
Image -> String
(Int -> Image -> ShowS)
-> (Image -> String) -> ([Image] -> ShowS) -> Show Image
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Image] -> ShowS
$cshowList :: [Image] -> ShowS
show :: Image -> String
$cshow :: Image -> String
showsPrec :: Int -> Image -> ShowS
$cshowsPrec :: Int -> Image -> ShowS
Show, Image -> Image -> Bool
(Image -> Image -> Bool) -> (Image -> Image -> Bool) -> Eq Image
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Image -> Image -> Bool
$c/= :: Image -> Image -> Bool
== :: Image -> Image -> Bool
$c== :: Image -> Image -> Bool
Eq, (forall x. Image -> Rep Image x)
-> (forall x. Rep Image x -> Image) -> Generic Image
forall x. Rep Image x -> Image
forall x. Image -> Rep Image x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Image x -> Image
$cfrom :: forall x. Image -> Rep Image x
Generic )

instance FromJSON Image where
    parseJSON :: Value -> Parser Image
parseJSON = Options -> Value -> Parser Image
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON --
        Options
defaultOptions { fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
imageModifier }

instance ToJSON Image where
    toJSON :: Image -> Value
toJSON =
        Options -> Image -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
defaultOptions { fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
imageModifier }

imageModifier :: Modifier
imageModifier :: ShowS
imageModifier = \case
    String
"linkURL" -> String
"linkUrl"
    String
s         -> String
s

-- | A widget representing a menu
data MenuWidget =
    MenuWidget { MenuWidget -> Maybe WidgetID
widgetID :: Maybe WidgetID, MenuWidget -> Seq MenuChild
children :: Seq MenuChild }
    deriving stock ( Int -> MenuWidget -> ShowS
[MenuWidget] -> ShowS
MenuWidget -> String
(Int -> MenuWidget -> ShowS)
-> (MenuWidget -> String)
-> ([MenuWidget] -> ShowS)
-> Show MenuWidget
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MenuWidget] -> ShowS
$cshowList :: [MenuWidget] -> ShowS
show :: MenuWidget -> String
$cshow :: MenuWidget -> String
showsPrec :: Int -> MenuWidget -> ShowS
$cshowsPrec :: Int -> MenuWidget -> ShowS
Show, MenuWidget -> MenuWidget -> Bool
(MenuWidget -> MenuWidget -> Bool)
-> (MenuWidget -> MenuWidget -> Bool) -> Eq MenuWidget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MenuWidget -> MenuWidget -> Bool
$c/= :: MenuWidget -> MenuWidget -> Bool
== :: MenuWidget -> MenuWidget -> Bool
$c== :: MenuWidget -> MenuWidget -> Bool
Eq, (forall x. MenuWidget -> Rep MenuWidget x)
-> (forall x. Rep MenuWidget x -> MenuWidget) -> Generic MenuWidget
forall x. Rep MenuWidget x -> MenuWidget
forall x. MenuWidget -> Rep MenuWidget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MenuWidget x -> MenuWidget
$cfrom :: forall x. MenuWidget -> Rep MenuWidget x
Generic )

instance FromJSON MenuWidget where
    parseJSON :: Value -> Parser MenuWidget
parseJSON = WidgetType
-> String
-> (Value -> Parser MenuWidget)
-> Value
-> Parser MenuWidget
forall a.
WidgetType -> String -> (Value -> Parser a) -> Value -> Parser a
withWidgetKind WidgetType
MenuType String
"MenuWidget"
        ((Value -> Parser MenuWidget) -> Value -> Parser MenuWidget)
-> (Value -> Parser MenuWidget) -> Value -> Parser MenuWidget
forall a b. (a -> b) -> a -> b
$ Options -> Value -> Parser MenuWidget
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions
                           { fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
menuWidgetModifier }

instance ToJSON MenuWidget where
    toJSON :: MenuWidget -> Value
toJSON = ShowS -> WidgetType -> MenuWidget -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
ShowS -> WidgetType -> a -> Value
widgetToJSON ShowS
menuWidgetModifier WidgetType
MenuType

menuWidgetModifier :: Modifier
menuWidgetModifier :: ShowS
menuWidgetModifier = \case
    String
"children" -> String
"data"
    String
s          -> ShowS
defaultWidgetModifier String
s

-- | A child widget in a 'MenuWidget'
data MenuChild
    = SubmenuChild Submenu
    | MenuLinkChild MenuLink
    deriving stock ( Int -> MenuChild -> ShowS
[MenuChild] -> ShowS
MenuChild -> String
(Int -> MenuChild -> ShowS)
-> (MenuChild -> String)
-> ([MenuChild] -> ShowS)
-> Show MenuChild
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MenuChild] -> ShowS
$cshowList :: [MenuChild] -> ShowS
show :: MenuChild -> String
$cshow :: MenuChild -> String
showsPrec :: Int -> MenuChild -> ShowS
$cshowsPrec :: Int -> MenuChild -> ShowS
Show, MenuChild -> MenuChild -> Bool
(MenuChild -> MenuChild -> Bool)
-> (MenuChild -> MenuChild -> Bool) -> Eq MenuChild
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MenuChild -> MenuChild -> Bool
$c/= :: MenuChild -> MenuChild -> Bool
== :: MenuChild -> MenuChild -> Bool
$c== :: MenuChild -> MenuChild -> Bool
Eq, (forall x. MenuChild -> Rep MenuChild x)
-> (forall x. Rep MenuChild x -> MenuChild) -> Generic MenuChild
forall x. Rep MenuChild x -> MenuChild
forall x. MenuChild -> Rep MenuChild x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MenuChild x -> MenuChild
$cfrom :: forall x. MenuChild -> Rep MenuChild x
Generic )

instance FromJSON MenuChild where
    parseJSON :: Value -> Parser MenuChild
parseJSON =
        Options -> Value -> Parser MenuChild
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions { sumEncoding :: SumEncoding
sumEncoding = SumEncoding
UntaggedValue }

instance ToJSON MenuChild where
    toJSON :: MenuChild -> Value
toJSON = Options -> MenuChild -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
defaultOptions { sumEncoding :: SumEncoding
sumEncoding = SumEncoding
UntaggedValue }

-- | A submenu child in a 'MenuWidget' which contains 'MenuLink's
data Submenu = Submenu { Submenu -> Seq MenuLink
children :: Seq MenuLink, Submenu -> Text
text :: Text }
    deriving stock ( Int -> Submenu -> ShowS
[Submenu] -> ShowS
Submenu -> String
(Int -> Submenu -> ShowS)
-> (Submenu -> String) -> ([Submenu] -> ShowS) -> Show Submenu
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Submenu] -> ShowS
$cshowList :: [Submenu] -> ShowS
show :: Submenu -> String
$cshow :: Submenu -> String
showsPrec :: Int -> Submenu -> ShowS
$cshowsPrec :: Int -> Submenu -> ShowS
Show, Submenu -> Submenu -> Bool
(Submenu -> Submenu -> Bool)
-> (Submenu -> Submenu -> Bool) -> Eq Submenu
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Submenu -> Submenu -> Bool
$c/= :: Submenu -> Submenu -> Bool
== :: Submenu -> Submenu -> Bool
$c== :: Submenu -> Submenu -> Bool
Eq, (forall x. Submenu -> Rep Submenu x)
-> (forall x. Rep Submenu x -> Submenu) -> Generic Submenu
forall x. Rep Submenu x -> Submenu
forall x. Submenu -> Rep Submenu x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Submenu x -> Submenu
$cfrom :: forall x. Submenu -> Rep Submenu x
Generic )

instance FromJSON Submenu

instance ToJSON Submenu

-- | A link in a 'MenuWidget' or 'Submenu'
data MenuLink = MenuLink { MenuLink -> Text
text :: Text, MenuLink -> Text
url :: URL }
    deriving stock ( Int -> MenuLink -> ShowS
[MenuLink] -> ShowS
MenuLink -> String
(Int -> MenuLink -> ShowS)
-> (MenuLink -> String) -> ([MenuLink] -> ShowS) -> Show MenuLink
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MenuLink] -> ShowS
$cshowList :: [MenuLink] -> ShowS
show :: MenuLink -> String
$cshow :: MenuLink -> String
showsPrec :: Int -> MenuLink -> ShowS
$cshowsPrec :: Int -> MenuLink -> ShowS
Show, MenuLink -> MenuLink -> Bool
(MenuLink -> MenuLink -> Bool)
-> (MenuLink -> MenuLink -> Bool) -> Eq MenuLink
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MenuLink -> MenuLink -> Bool
$c/= :: MenuLink -> MenuLink -> Bool
== :: MenuLink -> MenuLink -> Bool
$c== :: MenuLink -> MenuLink -> Bool
Eq, (forall x. MenuLink -> Rep MenuLink x)
-> (forall x. Rep MenuLink x -> MenuLink) -> Generic MenuLink
forall x. Rep MenuLink x -> MenuLink
forall x. MenuLink -> Rep MenuLink x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MenuLink x -> MenuLink
$cfrom :: forall x. MenuLink -> Rep MenuLink x
Generic )

instance FromJSON MenuLink

instance ToJSON MenuLink

-- | A widget listing the moderators of the subreddit. This widget cannot be
-- created. It can be updated by modifying the @styles@ field only
data ModeratorsWidget = ModeratorsWidget
    { ModeratorsWidget -> Maybe WidgetID
widgetID  :: Maybe WidgetID
    , ModeratorsWidget -> Seq ModInfo
mods      :: Seq ModInfo
    , ModeratorsWidget -> Maybe Int
totalMods :: Maybe Int
    , ModeratorsWidget -> Maybe WidgetStyles
styles    :: Maybe WidgetStyles
    }
    deriving stock ( Int -> ModeratorsWidget -> ShowS
[ModeratorsWidget] -> ShowS
ModeratorsWidget -> String
(Int -> ModeratorsWidget -> ShowS)
-> (ModeratorsWidget -> String)
-> ([ModeratorsWidget] -> ShowS)
-> Show ModeratorsWidget
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModeratorsWidget] -> ShowS
$cshowList :: [ModeratorsWidget] -> ShowS
show :: ModeratorsWidget -> String
$cshow :: ModeratorsWidget -> String
showsPrec :: Int -> ModeratorsWidget -> ShowS
$cshowsPrec :: Int -> ModeratorsWidget -> ShowS
Show, ModeratorsWidget -> ModeratorsWidget -> Bool
(ModeratorsWidget -> ModeratorsWidget -> Bool)
-> (ModeratorsWidget -> ModeratorsWidget -> Bool)
-> Eq ModeratorsWidget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModeratorsWidget -> ModeratorsWidget -> Bool
$c/= :: ModeratorsWidget -> ModeratorsWidget -> Bool
== :: ModeratorsWidget -> ModeratorsWidget -> Bool
$c== :: ModeratorsWidget -> ModeratorsWidget -> Bool
Eq, (forall x. ModeratorsWidget -> Rep ModeratorsWidget x)
-> (forall x. Rep ModeratorsWidget x -> ModeratorsWidget)
-> Generic ModeratorsWidget
forall x. Rep ModeratorsWidget x -> ModeratorsWidget
forall x. ModeratorsWidget -> Rep ModeratorsWidget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ModeratorsWidget x -> ModeratorsWidget
$cfrom :: forall x. ModeratorsWidget -> Rep ModeratorsWidget x
Generic )

instance FromJSON ModeratorsWidget where
    parseJSON :: Value -> Parser ModeratorsWidget
parseJSON = WidgetType
-> String
-> (Value -> Parser ModeratorsWidget)
-> Value
-> Parser ModeratorsWidget
forall a.
WidgetType -> String -> (Value -> Parser a) -> Value -> Parser a
withWidgetKind WidgetType
ModeratorsType String
"ModeratorsWidget" Value -> Parser ModeratorsWidget
modsP
      where
        modsP :: Value -> Parser ModeratorsWidget
modsP (Object Object
o) = Maybe WidgetID
-> Seq ModInfo
-> Maybe Int
-> Maybe WidgetStyles
-> ModeratorsWidget
ModeratorsWidget (Maybe WidgetID
 -> Seq ModInfo
 -> Maybe Int
 -> Maybe WidgetStyles
 -> ModeratorsWidget)
-> Parser (Maybe WidgetID)
-> Parser
     (Seq ModInfo
      -> Maybe Int -> Maybe WidgetStyles -> ModeratorsWidget)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser (Maybe WidgetID)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id"
            -- Apparently this field is occasionally missing from updated
            -- @ModeratorsWidget@s
            Parser
  (Seq ModInfo
   -> Maybe Int -> Maybe WidgetStyles -> ModeratorsWidget)
-> Parser (Seq ModInfo)
-> Parser (Maybe Int -> Maybe WidgetStyles -> ModeratorsWidget)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object -> Text -> Parser (Seq ModInfo)
forall b.
(FromJSON (Item b), IsList b, Monoid b) =>
Object -> Text -> Parser b
fromOptional Object
o Text
"mods"
            -- This one too
            Parser (Maybe Int -> Maybe WidgetStyles -> ModeratorsWidget)
-> Parser (Maybe Int)
-> Parser (Maybe WidgetStyles -> ModeratorsWidget)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Int -> Parser (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"totalMods")
            Parser (Maybe WidgetStyles -> ModeratorsWidget)
-> Parser (Maybe WidgetStyles) -> Parser ModeratorsWidget
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe WidgetStyles)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"styles"
        modsP Value
_          = Parser ModeratorsWidget
forall a. Monoid a => a
mempty

instance ToJSON ModeratorsWidget where
    toJSON :: ModeratorsWidget -> Value
toJSON ModeratorsWidget { Maybe Int
Maybe WidgetStyles
Maybe WidgetID
Seq ModInfo
styles :: Maybe WidgetStyles
totalMods :: Maybe Int
mods :: Seq ModInfo
widgetID :: Maybe WidgetID
$sel:styles:ModeratorsWidget :: ModeratorsWidget -> Maybe WidgetStyles
$sel:totalMods:ModeratorsWidget :: ModeratorsWidget -> Maybe Int
$sel:mods:ModeratorsWidget :: ModeratorsWidget -> Seq ModInfo
$sel:widgetID:ModeratorsWidget :: ModeratorsWidget -> Maybe WidgetID
.. } = [Pair] -> Value
object
        ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [ Text
"kind" Text -> WidgetType -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= WidgetType
ModeratorsType ]
        [Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> (Pair -> [Pair]) -> Maybe Pair -> [Pair]
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pair -> [Pair]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Text
"styles" Text -> WidgetStyles -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.=) (WidgetStyles -> Pair) -> Maybe WidgetStyles -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe WidgetStyles
styles)

-- | Information about a moderator as displayed in a 'ModeratorsWidget'
data ModInfo = ModInfo
    { ModInfo -> Username
name                 :: Username
    , ModInfo -> Maybe FlairText
flairText            :: Maybe FlairText
    , ModInfo -> Maybe ForegroundColor
flairTextColor       :: Maybe ForegroundColor
    , ModInfo -> Maybe Text
flairBackgroundColor :: Maybe RGBText
    }
    deriving stock ( Int -> ModInfo -> ShowS
[ModInfo] -> ShowS
ModInfo -> String
(Int -> ModInfo -> ShowS)
-> (ModInfo -> String) -> ([ModInfo] -> ShowS) -> Show ModInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModInfo] -> ShowS
$cshowList :: [ModInfo] -> ShowS
show :: ModInfo -> String
$cshow :: ModInfo -> String
showsPrec :: Int -> ModInfo -> ShowS
$cshowsPrec :: Int -> ModInfo -> ShowS
Show, ModInfo -> ModInfo -> Bool
(ModInfo -> ModInfo -> Bool)
-> (ModInfo -> ModInfo -> Bool) -> Eq ModInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModInfo -> ModInfo -> Bool
$c/= :: ModInfo -> ModInfo -> Bool
== :: ModInfo -> ModInfo -> Bool
$c== :: ModInfo -> ModInfo -> Bool
Eq, (forall x. ModInfo -> Rep ModInfo x)
-> (forall x. Rep ModInfo x -> ModInfo) -> Generic ModInfo
forall x. Rep ModInfo x -> ModInfo
forall x. ModInfo -> Rep ModInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ModInfo x -> ModInfo
$cfrom :: forall x. ModInfo -> Rep ModInfo x
Generic )

instance FromJSON ModInfo where
    parseJSON :: Value -> Parser ModInfo
parseJSON = String -> (Object -> Parser ModInfo) -> Value -> Parser ModInfo
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ModInfo" ((Object -> Parser ModInfo) -> Value -> Parser ModInfo)
-> (Object -> Parser ModInfo) -> Value -> Parser ModInfo
forall a b. (a -> b) -> a -> b
$ \Object
o -> Username
-> Maybe FlairText
-> Maybe ForegroundColor
-> Maybe Text
-> ModInfo
ModInfo (Username
 -> Maybe FlairText
 -> Maybe ForegroundColor
 -> Maybe Text
 -> ModInfo)
-> Parser Username
-> Parser
     (Maybe FlairText -> Maybe ForegroundColor -> Maybe Text -> ModInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Username
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"name"
        Parser
  (Maybe FlairText -> Maybe ForegroundColor -> Maybe Text -> ModInfo)
-> Parser (Maybe FlairText)
-> Parser (Maybe ForegroundColor -> Maybe Text -> ModInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Parser (Maybe FlairText)
-> (Text -> Parser (Maybe FlairText))
-> Maybe Text
-> Parser (Maybe FlairText)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Maybe FlairText -> Parser (Maybe FlairText)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe FlairText
forall a. Maybe a
Nothing) Text -> Parser (Maybe FlairText)
forall a. FromJSON a => Text -> Parser (Maybe a)
nothingTxtNull (Maybe Text -> Parser (Maybe FlairText))
-> Parser (Maybe Text) -> Parser (Maybe FlairText)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"authorFlairText")
        Parser (Maybe ForegroundColor -> Maybe Text -> ModInfo)
-> Parser (Maybe ForegroundColor) -> Parser (Maybe Text -> ModInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Parser (Maybe ForegroundColor)
-> (Text -> Parser (Maybe ForegroundColor))
-> Maybe Text
-> Parser (Maybe ForegroundColor)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Maybe ForegroundColor -> Parser (Maybe ForegroundColor)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe ForegroundColor
forall a. Maybe a
Nothing) Text -> Parser (Maybe ForegroundColor)
forall a. FromJSON a => Text -> Parser (Maybe a)
nothingTxtNull
             (Maybe Text -> Parser (Maybe ForegroundColor))
-> Parser (Maybe Text) -> Parser (Maybe ForegroundColor)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"authorFlairTextColor")
        Parser (Maybe Text -> ModInfo)
-> Parser (Maybe Text) -> Parser ModInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Parser (Maybe Text)
-> (Text -> Parser (Maybe Text))
-> Maybe Text
-> Parser (Maybe Text)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Maybe Text -> Parser (Maybe Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Text
forall a. Maybe a
Nothing) Text -> Parser (Maybe Text)
forall a. FromJSON a => Text -> Parser (Maybe a)
nothingTxtNull
             (Maybe Text -> Parser (Maybe Text))
-> Parser (Maybe Text) -> Parser (Maybe Text)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"authorFlairBackgroundColor")

instance ToJSON ModInfo where
    toJSON :: ModInfo -> Value
toJSON = Options -> ModInfo -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
defaultOptions
                           { ShowS
fieldLabelModifier :: ShowS
fieldLabelModifier :: ShowS
fieldLabelModifier --
                           , omitNothingFields :: Bool
omitNothingFields  = Bool
True
                           }
      where
        fieldLabelModifier :: ShowS
fieldLabelModifier = \case
            String
"flairText" -> String
"authorFlairText"
            String
"flairTextColor" -> String
"authorFlairTextColor"
            String
"flairBackgroundColor" -> String
"authorFlairBackgroundColor"
            String
s -> String
s

-- | A widget listing flair choices for submissions. When creating a new widget,
-- the 'FlairID's in the @order@ field must be valid template IDs for the given
-- subreddit. Existing flair templates can be obtained with
-- 'Network.Reddit.Subreddit.getSubmissionFlairTemplates', which can
-- then be mapped over to obtain the IDs. Once the flair IDs have been obtained,
-- 'mkPostFlairWidget' can be used to construct a widget with default values for
-- most fields
data PostFlairWidget = PostFlairWidget
    { PostFlairWidget -> Maybe WidgetID
widgetID  :: Maybe WidgetID
    , PostFlairWidget -> ShortName
shortName :: ShortName
      -- | A container of 'FlairID's corresponding to the flair
      -- templates listed in the widget. Use this field when
      -- updating or creating 'PostFlairWidget's
    , PostFlairWidget -> Seq Text
order     :: Seq FlairID
      -- | A mapping of submission flair template IDs to
      -- brief information on each one. This field is /not/
      -- serialized when creating a new 'PostFlairWidget' or
      -- when updating an existing one, and can be left empty
      -- in those cases
    , PostFlairWidget -> HashMap Text PostFlairInfo
templates :: HashMap FlairID PostFlairInfo
    , PostFlairWidget -> PostFlairWidgetDisplay
display   :: PostFlairWidgetDisplay
    , PostFlairWidget -> Maybe WidgetStyles
styles    :: Maybe WidgetStyles
    }
    deriving stock ( Int -> PostFlairWidget -> ShowS
[PostFlairWidget] -> ShowS
PostFlairWidget -> String
(Int -> PostFlairWidget -> ShowS)
-> (PostFlairWidget -> String)
-> ([PostFlairWidget] -> ShowS)
-> Show PostFlairWidget
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostFlairWidget] -> ShowS
$cshowList :: [PostFlairWidget] -> ShowS
show :: PostFlairWidget -> String
$cshow :: PostFlairWidget -> String
showsPrec :: Int -> PostFlairWidget -> ShowS
$cshowsPrec :: Int -> PostFlairWidget -> ShowS
Show, PostFlairWidget -> PostFlairWidget -> Bool
(PostFlairWidget -> PostFlairWidget -> Bool)
-> (PostFlairWidget -> PostFlairWidget -> Bool)
-> Eq PostFlairWidget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostFlairWidget -> PostFlairWidget -> Bool
$c/= :: PostFlairWidget -> PostFlairWidget -> Bool
== :: PostFlairWidget -> PostFlairWidget -> Bool
$c== :: PostFlairWidget -> PostFlairWidget -> Bool
Eq, (forall x. PostFlairWidget -> Rep PostFlairWidget x)
-> (forall x. Rep PostFlairWidget x -> PostFlairWidget)
-> Generic PostFlairWidget
forall x. Rep PostFlairWidget x -> PostFlairWidget
forall x. PostFlairWidget -> Rep PostFlairWidget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PostFlairWidget x -> PostFlairWidget
$cfrom :: forall x. PostFlairWidget -> Rep PostFlairWidget x
Generic )

instance FromJSON PostFlairWidget where
    parseJSON :: Value -> Parser PostFlairWidget
parseJSON = WidgetType
-> String
-> (Value -> Parser PostFlairWidget)
-> Value
-> Parser PostFlairWidget
forall a.
WidgetType -> String -> (Value -> Parser a) -> Value -> Parser a
withWidgetKind WidgetType
PostFlairType String
"PostFlairWidget"
        ((Value -> Parser PostFlairWidget)
 -> Value -> Parser PostFlairWidget)
-> (Value -> Parser PostFlairWidget)
-> Value
-> Parser PostFlairWidget
forall a b. (a -> b) -> a -> b
$ Options -> Value -> Parser PostFlairWidget
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions
                           { fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
defaultWidgetModifier }

instance ToJSON PostFlairWidget where
    toJSON :: PostFlairWidget -> Value
toJSON PostFlairWidget { Maybe WidgetStyles
Maybe WidgetID
HashMap Text PostFlairInfo
Seq Text
PostFlairWidgetDisplay
ShortName
styles :: Maybe WidgetStyles
display :: PostFlairWidgetDisplay
templates :: HashMap Text PostFlairInfo
order :: Seq Text
shortName :: ShortName
widgetID :: Maybe WidgetID
$sel:styles:PostFlairWidget :: PostFlairWidget -> Maybe WidgetStyles
$sel:display:PostFlairWidget :: PostFlairWidget -> PostFlairWidgetDisplay
$sel:templates:PostFlairWidget :: PostFlairWidget -> HashMap Text PostFlairInfo
$sel:order:PostFlairWidget :: PostFlairWidget -> Seq Text
$sel:shortName:PostFlairWidget :: PostFlairWidget -> ShortName
$sel:widgetID:PostFlairWidget :: PostFlairWidget -> Maybe WidgetID
.. } = [Pair] -> Value
object
        ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [ Text
"id" Text -> Maybe WidgetID -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Maybe WidgetID
widgetID
          , Text
"shortName" Text -> ShortName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ShortName
shortName
          , Text
"order" Text -> Seq Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Seq Text
order
          , Text
"display" Text -> PostFlairWidgetDisplay -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= PostFlairWidgetDisplay
display
          , Text
"kind" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (Text
"post-flair" :: Text)
          ]
        [Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> (Pair -> [Pair]) -> Maybe Pair -> [Pair]
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pair -> [Pair]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Text
"styles" Text -> WidgetStyles -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.=) (WidgetStyles -> Pair) -> Maybe WidgetStyles -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe WidgetStyles
styles)

-- | Make a new 'PostFlairWidget' with default values for most fields
mkPostFlairWidget :: ShortName -> Seq FlairID -> PostFlairWidget
mkPostFlairWidget :: ShortName -> Seq Text -> PostFlairWidget
mkPostFlairWidget ShortName
shortName Seq Text
order = PostFlairWidget :: Maybe WidgetID
-> ShortName
-> Seq Text
-> HashMap Text PostFlairInfo
-> PostFlairWidgetDisplay
-> Maybe WidgetStyles
-> PostFlairWidget
PostFlairWidget
    { $sel:widgetID:PostFlairWidget :: Maybe WidgetID
widgetID  = Maybe WidgetID
forall a. Maybe a
Nothing
    , $sel:templates:PostFlairWidget :: HashMap Text PostFlairInfo
templates = HashMap Text PostFlairInfo
forall a. Monoid a => a
mempty
    , $sel:display:PostFlairWidget :: PostFlairWidgetDisplay
display   = PostFlairWidgetDisplay
ListDisplay
    , $sel:styles:PostFlairWidget :: Maybe WidgetStyles
styles    = Maybe WidgetStyles
forall a. Maybe a
Nothing
    , Seq Text
ShortName
order :: Seq Text
shortName :: ShortName
$sel:order:PostFlairWidget :: Seq Text
$sel:shortName:PostFlairWidget :: ShortName
..
    }

-- | Information about submission flair templates in a 'PostFlairWidget'
data PostFlairInfo = PostFlairInfo
    { PostFlairInfo -> Text
templateID      :: FlairID
    , PostFlairInfo -> Text
text            :: Text
    , PostFlairInfo -> ForegroundColor
textColor       :: ForegroundColor
    , PostFlairInfo -> Text
backgroundColor :: RGBText
    }
    deriving stock ( Int -> PostFlairInfo -> ShowS
[PostFlairInfo] -> ShowS
PostFlairInfo -> String
(Int -> PostFlairInfo -> ShowS)
-> (PostFlairInfo -> String)
-> ([PostFlairInfo] -> ShowS)
-> Show PostFlairInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostFlairInfo] -> ShowS
$cshowList :: [PostFlairInfo] -> ShowS
show :: PostFlairInfo -> String
$cshow :: PostFlairInfo -> String
showsPrec :: Int -> PostFlairInfo -> ShowS
$cshowsPrec :: Int -> PostFlairInfo -> ShowS
Show, PostFlairInfo -> PostFlairInfo -> Bool
(PostFlairInfo -> PostFlairInfo -> Bool)
-> (PostFlairInfo -> PostFlairInfo -> Bool) -> Eq PostFlairInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostFlairInfo -> PostFlairInfo -> Bool
$c/= :: PostFlairInfo -> PostFlairInfo -> Bool
== :: PostFlairInfo -> PostFlairInfo -> Bool
$c== :: PostFlairInfo -> PostFlairInfo -> Bool
Eq, (forall x. PostFlairInfo -> Rep PostFlairInfo x)
-> (forall x. Rep PostFlairInfo x -> PostFlairInfo)
-> Generic PostFlairInfo
forall x. Rep PostFlairInfo x -> PostFlairInfo
forall x. PostFlairInfo -> Rep PostFlairInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PostFlairInfo x -> PostFlairInfo
$cfrom :: forall x. PostFlairInfo -> Rep PostFlairInfo x
Generic )

instance FromJSON PostFlairInfo where
    parseJSON :: Value -> Parser PostFlairInfo
parseJSON =
        Options -> Value -> Parser PostFlairInfo
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions
                         { fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
postFlairInfoModifier }

postFlairInfoModifier :: Modifier
postFlairInfoModifier :: ShowS
postFlairInfoModifier = \case
    String
"templateID" -> String
"templateId"
    String
s            -> String
s

-- | The display orientation for 'PostFlairWidget's
data PostFlairWidgetDisplay
    = CloudDisplay
    | ListDisplay
    deriving stock ( Int -> PostFlairWidgetDisplay -> ShowS
[PostFlairWidgetDisplay] -> ShowS
PostFlairWidgetDisplay -> String
(Int -> PostFlairWidgetDisplay -> ShowS)
-> (PostFlairWidgetDisplay -> String)
-> ([PostFlairWidgetDisplay] -> ShowS)
-> Show PostFlairWidgetDisplay
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostFlairWidgetDisplay] -> ShowS
$cshowList :: [PostFlairWidgetDisplay] -> ShowS
show :: PostFlairWidgetDisplay -> String
$cshow :: PostFlairWidgetDisplay -> String
showsPrec :: Int -> PostFlairWidgetDisplay -> ShowS
$cshowsPrec :: Int -> PostFlairWidgetDisplay -> ShowS
Show, PostFlairWidgetDisplay -> PostFlairWidgetDisplay -> Bool
(PostFlairWidgetDisplay -> PostFlairWidgetDisplay -> Bool)
-> (PostFlairWidgetDisplay -> PostFlairWidgetDisplay -> Bool)
-> Eq PostFlairWidgetDisplay
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostFlairWidgetDisplay -> PostFlairWidgetDisplay -> Bool
$c/= :: PostFlairWidgetDisplay -> PostFlairWidgetDisplay -> Bool
== :: PostFlairWidgetDisplay -> PostFlairWidgetDisplay -> Bool
$c== :: PostFlairWidgetDisplay -> PostFlairWidgetDisplay -> Bool
Eq, (forall x. PostFlairWidgetDisplay -> Rep PostFlairWidgetDisplay x)
-> (forall x.
    Rep PostFlairWidgetDisplay x -> PostFlairWidgetDisplay)
-> Generic PostFlairWidgetDisplay
forall x. Rep PostFlairWidgetDisplay x -> PostFlairWidgetDisplay
forall x. PostFlairWidgetDisplay -> Rep PostFlairWidgetDisplay x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PostFlairWidgetDisplay x -> PostFlairWidgetDisplay
$cfrom :: forall x. PostFlairWidgetDisplay -> Rep PostFlairWidgetDisplay x
Generic )

instance FromJSON PostFlairWidgetDisplay where
    parseJSON :: Value -> Parser PostFlairWidgetDisplay
parseJSON = Options -> Value -> Parser PostFlairWidgetDisplay
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON --
        Options
defaultOptions { constructorTagModifier :: ShowS
constructorTagModifier = ShowS
postFlairWidgetModifier }

instance ToJSON PostFlairWidgetDisplay where
    toJSON :: PostFlairWidgetDisplay -> Value
toJSON = Options -> PostFlairWidgetDisplay -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON --
        Options
defaultOptions { constructorTagModifier :: ShowS
constructorTagModifier = ShowS
postFlairWidgetModifier }

postFlairWidgetModifier :: Modifier
postFlairWidgetModifier :: ShowS
postFlairWidgetModifier = \case
    String
"CloudDisplay" -> String
"cloud"
    String
"ListDisplay"  -> String
"list"
    String
_              -> String
forall a. Monoid a => a
mempty

-- | A widget listing subreddit 'SubredditRule's. The @rules@ field cannot be
-- updated through widget endpoints, and are excluded during serialization
data RulesWidget = RulesWidget
    { RulesWidget -> Maybe WidgetID
widgetID  :: Maybe WidgetID
    , RulesWidget -> ShortName
shortName :: ShortName
    , RulesWidget -> Seq SubredditRule
rules     :: Seq SubredditRule
    , RulesWidget -> RulesDisplay
display   :: RulesDisplay
    , RulesWidget -> Maybe WidgetStyles
styles    :: Maybe WidgetStyles
    }
    deriving stock ( Int -> RulesWidget -> ShowS
[RulesWidget] -> ShowS
RulesWidget -> String
(Int -> RulesWidget -> ShowS)
-> (RulesWidget -> String)
-> ([RulesWidget] -> ShowS)
-> Show RulesWidget
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RulesWidget] -> ShowS
$cshowList :: [RulesWidget] -> ShowS
show :: RulesWidget -> String
$cshow :: RulesWidget -> String
showsPrec :: Int -> RulesWidget -> ShowS
$cshowsPrec :: Int -> RulesWidget -> ShowS
Show, RulesWidget -> RulesWidget -> Bool
(RulesWidget -> RulesWidget -> Bool)
-> (RulesWidget -> RulesWidget -> Bool) -> Eq RulesWidget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RulesWidget -> RulesWidget -> Bool
$c/= :: RulesWidget -> RulesWidget -> Bool
== :: RulesWidget -> RulesWidget -> Bool
$c== :: RulesWidget -> RulesWidget -> Bool
Eq, (forall x. RulesWidget -> Rep RulesWidget x)
-> (forall x. Rep RulesWidget x -> RulesWidget)
-> Generic RulesWidget
forall x. Rep RulesWidget x -> RulesWidget
forall x. RulesWidget -> Rep RulesWidget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RulesWidget x -> RulesWidget
$cfrom :: forall x. RulesWidget -> Rep RulesWidget x
Generic )

instance FromJSON RulesWidget where
    parseJSON :: Value -> Parser RulesWidget
parseJSON = WidgetType
-> String
-> (Value -> Parser RulesWidget)
-> Value
-> Parser RulesWidget
forall a.
WidgetType -> String -> (Value -> Parser a) -> Value -> Parser a
withWidgetKind WidgetType
RulesType String
"RulesWidget" Value -> Parser RulesWidget
rulesP
      where
        rulesP :: Value -> Parser RulesWidget
rulesP (Object Object
o) = Maybe WidgetID
-> ShortName
-> Seq SubredditRule
-> RulesDisplay
-> Maybe WidgetStyles
-> RulesWidget
RulesWidget (Maybe WidgetID
 -> ShortName
 -> Seq SubredditRule
 -> RulesDisplay
 -> Maybe WidgetStyles
 -> RulesWidget)
-> Parser (Maybe WidgetID)
-> Parser
     (ShortName
      -> Seq SubredditRule
      -> RulesDisplay
      -> Maybe WidgetStyles
      -> RulesWidget)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser (Maybe WidgetID)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id"
            Parser
  (ShortName
   -> Seq SubredditRule
   -> RulesDisplay
   -> Maybe WidgetStyles
   -> RulesWidget)
-> Parser ShortName
-> Parser
     (Seq SubredditRule
      -> RulesDisplay -> Maybe WidgetStyles -> RulesWidget)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser ShortName
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"shortName"
            -- This field may be missing after updating the widget
            Parser
  (Seq SubredditRule
   -> RulesDisplay -> Maybe WidgetStyles -> RulesWidget)
-> Parser (Seq SubredditRule)
-> Parser (RulesDisplay -> Maybe WidgetStyles -> RulesWidget)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object -> Text -> Parser (Seq SubredditRule)
forall b.
(FromJSON (Item b), IsList b, Monoid b) =>
Object -> Text -> Parser b
fromOptional Object
o Text
"data"
            Parser (RulesDisplay -> Maybe WidgetStyles -> RulesWidget)
-> Parser RulesDisplay
-> Parser (Maybe WidgetStyles -> RulesWidget)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser RulesDisplay
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"display"
            Parser (Maybe WidgetStyles -> RulesWidget)
-> Parser (Maybe WidgetStyles) -> Parser RulesWidget
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe WidgetStyles)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"styles"
        rulesP Value
_          = Parser RulesWidget
forall a. Monoid a => a
mempty

instance ToJSON RulesWidget where
    toJSON :: RulesWidget -> Value
toJSON RulesWidget { Maybe WidgetStyles
Maybe WidgetID
Seq SubredditRule
RulesDisplay
ShortName
styles :: Maybe WidgetStyles
display :: RulesDisplay
rules :: Seq SubredditRule
shortName :: ShortName
widgetID :: Maybe WidgetID
$sel:styles:RulesWidget :: RulesWidget -> Maybe WidgetStyles
$sel:display:RulesWidget :: RulesWidget -> RulesDisplay
$sel:rules:RulesWidget :: RulesWidget -> Seq SubredditRule
$sel:shortName:RulesWidget :: RulesWidget -> ShortName
$sel:widgetID:RulesWidget :: RulesWidget -> Maybe WidgetID
.. } =
        [Pair] -> Value
object [ Text
"id" Text -> Maybe WidgetID -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Maybe WidgetID
widgetID
               , Text
"shortName" Text -> ShortName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= ShortName
shortName
               , Text
"display" Text -> RulesDisplay -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= RulesDisplay
display
               , Text
"styles" Text -> Maybe WidgetStyles -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Maybe WidgetStyles
styles
               , Text
"kind" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (Text
"subreddit-rules" :: Text)
               ]

-- | Display style for a 'RulesWidget'
data RulesDisplay
    = FullDisplay
    | CompactDisplay
    deriving stock ( Int -> RulesDisplay -> ShowS
[RulesDisplay] -> ShowS
RulesDisplay -> String
(Int -> RulesDisplay -> ShowS)
-> (RulesDisplay -> String)
-> ([RulesDisplay] -> ShowS)
-> Show RulesDisplay
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RulesDisplay] -> ShowS
$cshowList :: [RulesDisplay] -> ShowS
show :: RulesDisplay -> String
$cshow :: RulesDisplay -> String
showsPrec :: Int -> RulesDisplay -> ShowS
$cshowsPrec :: Int -> RulesDisplay -> ShowS
Show, RulesDisplay -> RulesDisplay -> Bool
(RulesDisplay -> RulesDisplay -> Bool)
-> (RulesDisplay -> RulesDisplay -> Bool) -> Eq RulesDisplay
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RulesDisplay -> RulesDisplay -> Bool
$c/= :: RulesDisplay -> RulesDisplay -> Bool
== :: RulesDisplay -> RulesDisplay -> Bool
$c== :: RulesDisplay -> RulesDisplay -> Bool
Eq, (forall x. RulesDisplay -> Rep RulesDisplay x)
-> (forall x. Rep RulesDisplay x -> RulesDisplay)
-> Generic RulesDisplay
forall x. Rep RulesDisplay x -> RulesDisplay
forall x. RulesDisplay -> Rep RulesDisplay x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RulesDisplay x -> RulesDisplay
$cfrom :: forall x. RulesDisplay -> Rep RulesDisplay x
Generic )

instance FromJSON RulesDisplay where
    parseJSON :: Value -> Parser RulesDisplay
parseJSON = Options -> Value -> Parser RulesDisplay
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON --
        Options
defaultOptions { constructorTagModifier :: ShowS
constructorTagModifier = ShowS
rulesDisplayModifier }

instance ToJSON RulesDisplay where
    toJSON :: RulesDisplay -> Value
toJSON = Options -> RulesDisplay -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON --
        Options
defaultOptions { constructorTagModifier :: ShowS
constructorTagModifier = ShowS
rulesDisplayModifier }

rulesDisplayModifier :: Modifier
rulesDisplayModifier :: ShowS
rulesDisplayModifier = \case
    String
"FullDisplay"    -> String
"full"
    String
"CompactDisplay" -> String
"compact"
    String
_                -> String
forall a. Monoid a => a
mempty

-- | A widget composed of text. See 'mkTextAreaWidget' for constructing a new
-- widget
data TextAreaWidget = TextAreaWidget
    { TextAreaWidget -> Maybe WidgetID
widgetID  :: Maybe WidgetID
    , TextAreaWidget -> ShortName
shortName :: ShortName
      -- | Markdown-formatted
    , TextAreaWidget -> Text
text      :: Body
      -- | This is present in existing widgets, but should be
      -- left blank when creating a new one
    , TextAreaWidget -> Maybe Text
textHTML  :: Maybe Body
    , TextAreaWidget -> Maybe WidgetStyles
styles    :: Maybe WidgetStyles
    }
    deriving stock ( Int -> TextAreaWidget -> ShowS
[TextAreaWidget] -> ShowS
TextAreaWidget -> String
(Int -> TextAreaWidget -> ShowS)
-> (TextAreaWidget -> String)
-> ([TextAreaWidget] -> ShowS)
-> Show TextAreaWidget
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextAreaWidget] -> ShowS
$cshowList :: [TextAreaWidget] -> ShowS
show :: TextAreaWidget -> String
$cshow :: TextAreaWidget -> String
showsPrec :: Int -> TextAreaWidget -> ShowS
$cshowsPrec :: Int -> TextAreaWidget -> ShowS
Show, TextAreaWidget -> TextAreaWidget -> Bool
(TextAreaWidget -> TextAreaWidget -> Bool)
-> (TextAreaWidget -> TextAreaWidget -> Bool) -> Eq TextAreaWidget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextAreaWidget -> TextAreaWidget -> Bool
$c/= :: TextAreaWidget -> TextAreaWidget -> Bool
== :: TextAreaWidget -> TextAreaWidget -> Bool
$c== :: TextAreaWidget -> TextAreaWidget -> Bool
Eq, (forall x. TextAreaWidget -> Rep TextAreaWidget x)
-> (forall x. Rep TextAreaWidget x -> TextAreaWidget)
-> Generic TextAreaWidget
forall x. Rep TextAreaWidget x -> TextAreaWidget
forall x. TextAreaWidget -> Rep TextAreaWidget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TextAreaWidget x -> TextAreaWidget
$cfrom :: forall x. TextAreaWidget -> Rep TextAreaWidget x
Generic )

instance FromJSON TextAreaWidget where
    parseJSON :: Value -> Parser TextAreaWidget
parseJSON = WidgetType
-> String
-> (Value -> Parser TextAreaWidget)
-> Value
-> Parser TextAreaWidget
forall a.
WidgetType -> String -> (Value -> Parser a) -> Value -> Parser a
withWidgetKind WidgetType
TextAreaType String
"TextAreaWidget"
        ((Value -> Parser TextAreaWidget)
 -> Value -> Parser TextAreaWidget)
-> (Value -> Parser TextAreaWidget)
-> Value
-> Parser TextAreaWidget
forall a b. (a -> b) -> a -> b
$ Options -> Value -> Parser TextAreaWidget
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions
                           { fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
textWidgetModifier }

instance ToJSON TextAreaWidget where
    toJSON :: TextAreaWidget -> Value
toJSON = ShowS -> WidgetType -> TextAreaWidget -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
ShowS -> WidgetType -> a -> Value
widgetToJSON ShowS
textWidgetModifier WidgetType
TextAreaType

-- | Create a new 'TextAreaWidget', with default values for most fields
mkTextAreaWidget :: ShortName -> Body -> TextAreaWidget
mkTextAreaWidget :: ShortName -> Text -> TextAreaWidget
mkTextAreaWidget ShortName
shortName Text
text = TextAreaWidget :: Maybe WidgetID
-> ShortName
-> Text
-> Maybe Text
-> Maybe WidgetStyles
-> TextAreaWidget
TextAreaWidget
    { $sel:widgetID:TextAreaWidget :: Maybe WidgetID
widgetID = Maybe WidgetID
forall a. Maybe a
Nothing --
    , $sel:textHTML:TextAreaWidget :: Maybe Text
textHTML = Maybe Text
forall a. Maybe a
Nothing
    , $sel:styles:TextAreaWidget :: Maybe WidgetStyles
styles   = Maybe WidgetStyles
forall a. Maybe a
Nothing
    , Text
ShortName
text :: Text
shortName :: ShortName
$sel:text:TextAreaWidget :: Text
$sel:shortName:TextAreaWidget :: ShortName
..
    }

textWidgetModifier :: Modifier
textWidgetModifier :: ShowS
textWidgetModifier = \case
    String
"textHTML" -> String
"textHtml"
    String
s          -> ShowS
defaultWidgetModifier String
s

-- Insert the @kind@ field into some JSON widget, while taking advantage of generic
-- @ToJSON@ deriving. An alternative would be to retain the field during encoding/
-- decoding . However, the user can only choose a single kind in each case
-- (e.g. a @ButtonWidget@ will always have the kind \"button\"), so that is perhaps
-- not the best choice as it would allow the construction of invalid widget values
widgetToJSON :: (Generic a, GToJSON' Value Zero (Rep a))
             => Modifier
             -> WidgetType
             -> a
             -> Value
widgetToJSON :: ShowS -> WidgetType -> a -> Value
widgetToJSON ShowS
fieldLabelModifier WidgetType
ty a
x = case a -> Value
genericTo a
x of
    Object Object
o -> Object -> Value
Object (Object -> Value) -> Object -> Value
forall a b. (a -> b) -> a -> b
$ Text -> Value -> Object -> Object
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
HM.insert Text
"kind" (WidgetType -> Value
forall a. ToJSON a => a -> Value
toJSON WidgetType
ty) Object
o
    Value
v        -> Value
v
  where
    genericTo :: a -> Value
genericTo = Options -> a -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
defaultOptions
                              { ShowS
fieldLabelModifier :: ShowS
fieldLabelModifier :: ShowS
fieldLabelModifier
                              , omitNothingFields :: Bool
omitNothingFields  = Bool
True
                              , sumEncoding :: SumEncoding
sumEncoding        = SumEncoding
UntaggedValue
                              }

defaultWidgetModifier :: Modifier
defaultWidgetModifier :: ShowS
defaultWidgetModifier = \case
    String
"widgetID" -> String
"id"
    String
s          -> String
s

withWidgetKind
    :: WidgetType -> [Char] -> (Value -> Parser a) -> Value -> Parser a
withWidgetKind :: WidgetType -> String -> (Value -> Parser a) -> Value -> Parser a
withWidgetKind WidgetType
ty String
name Value -> Parser a
f = String -> (Object -> Parser a) -> Value -> Parser a
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
name ((Object -> Parser a) -> Value -> Parser a)
-> (Object -> Parser a) -> Value -> Parser a
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
    Bool -> Parser ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Parser ())
-> (WidgetType -> Bool) -> WidgetType -> Parser ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (WidgetType -> WidgetType -> Bool
forall a. Eq a => a -> a -> Bool
== WidgetType
ty) (WidgetType -> Parser ()) -> Parser WidgetType -> Parser ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
o Object -> Text -> Parser WidgetType
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"kind"
    Value -> Parser a
f (Value -> Parser a) -> Value -> Parser a
forall a b. (a -> b) -> a -> b
$ Object -> Value
Object Object
o

data WidgetType
    = ImageType
    | TextType
    | ButtonType
    | CalendarType
    | CommunityListType
    | CustomType
    | IDCardType
    | MenuType
    | ModeratorsType
    | PostFlairType
    | RulesType
    | TextAreaType
    deriving stock ( WidgetType -> WidgetType -> Bool
(WidgetType -> WidgetType -> Bool)
-> (WidgetType -> WidgetType -> Bool) -> Eq WidgetType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WidgetType -> WidgetType -> Bool
$c/= :: WidgetType -> WidgetType -> Bool
== :: WidgetType -> WidgetType -> Bool
$c== :: WidgetType -> WidgetType -> Bool
Eq )

instance ToJSON WidgetType where
    toJSON :: WidgetType -> Value
toJSON = Text -> Value
String (Text -> Value) -> (WidgetType -> Text) -> WidgetType -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WidgetType -> Text
typeTag
      where
        typeTag :: WidgetType -> Text
typeTag = \case
            WidgetType
ImageType         -> Text
"image"
            WidgetType
TextType          -> Text
"text"
            WidgetType
ButtonType        -> Text
"button"
            WidgetType
CalendarType      -> Text
"calendar"
            WidgetType
CommunityListType -> Text
"community-list"
            WidgetType
CustomType        -> Text
"custom"
            WidgetType
IDCardType        -> Text
"id-card"
            WidgetType
MenuType          -> Text
"menu"
            WidgetType
ModeratorsType    -> Text
"moderators"
            WidgetType
PostFlairType     -> Text
"post-flair"
            WidgetType
RulesType         -> Text
"subreddit-rules"
            WidgetType
TextAreaType      -> Text
"textarea"

instance FromJSON WidgetType where
    parseJSON :: Value -> Parser WidgetType
parseJSON = String -> (Text -> Parser WidgetType) -> Value -> Parser WidgetType
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"WidgetType" ((Text -> Parser WidgetType) -> Value -> Parser WidgetType)
-> (Text -> Parser WidgetType) -> Value -> Parser WidgetType
forall a b. (a -> b) -> a -> b
$ \case
        Text
"image"           -> WidgetType -> Parser WidgetType
forall (f :: * -> *) a. Applicative f => a -> f a
pure WidgetType
ImageType
        Text
"text"            -> WidgetType -> Parser WidgetType
forall (f :: * -> *) a. Applicative f => a -> f a
pure WidgetType
TextType
        Text
"button"          -> WidgetType -> Parser WidgetType
forall (f :: * -> *) a. Applicative f => a -> f a
pure WidgetType
ButtonType
        Text
"calendar"        -> WidgetType -> Parser WidgetType
forall (f :: * -> *) a. Applicative f => a -> f a
pure WidgetType
CalendarType
        Text
"community-list"  -> WidgetType -> Parser WidgetType
forall (f :: * -> *) a. Applicative f => a -> f a
pure WidgetType
CommunityListType
        Text
"custom"          -> WidgetType -> Parser WidgetType
forall (f :: * -> *) a. Applicative f => a -> f a
pure WidgetType
CustomType
        Text
"id-card"         -> WidgetType -> Parser WidgetType
forall (f :: * -> *) a. Applicative f => a -> f a
pure WidgetType
IDCardType
        Text
"menu"            -> WidgetType -> Parser WidgetType
forall (f :: * -> *) a. Applicative f => a -> f a
pure WidgetType
MenuType
        Text
"moderators"      -> WidgetType -> Parser WidgetType
forall (f :: * -> *) a. Applicative f => a -> f a
pure WidgetType
ModeratorsType
        Text
"post-flair"      -> WidgetType -> Parser WidgetType
forall (f :: * -> *) a. Applicative f => a -> f a
pure WidgetType
PostFlairType
        Text
"subreddit-rules" -> WidgetType -> Parser WidgetType
forall (f :: * -> *) a. Applicative f => a -> f a
pure WidgetType
RulesType
        Text
"textarea"        -> WidgetType -> Parser WidgetType
forall (f :: * -> *) a. Applicative f => a -> f a
pure WidgetType
TextAreaType
        Text
_                 -> Parser WidgetType
forall a. Monoid a => a
mempty