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

-- | Data structures pertaining to Discord User
module Discord.Internal.Types.User where

import Data.Aeson
import Data.Text (Text)
import qualified Data.Text as T
import Discord.Internal.Types.Prelude

-- | Represents information about a user.
data User = User
  { User -> UserId
userId       :: UserId       -- ^ The user's id.
  , User -> Text
userName     :: T.Text       -- ^ The user's username (not unique)
  , User -> Text
userDiscrim  :: T.Text       -- ^ The user's 4-digit discord-tag.
  , User -> Maybe Text
userAvatar   :: Maybe T.Text -- ^ The user's avatar hash.
  , User -> Bool
userIsBot    :: Bool         -- ^ User is an OAuth2 application.
  , User -> Bool
userIsWebhook:: Bool         -- ^ User is a webhook
  , User -> Maybe Bool
userMfa      :: Maybe Bool   -- ^ User has two factor authentication enabled on the account.
  , User -> Maybe Bool
userVerified :: Maybe Bool   -- ^ Whether the email has been verified.
  , User -> Maybe Text
userEmail    :: Maybe T.Text -- ^ The user's email.
  } deriving (Int -> User -> ShowS
[User] -> ShowS
User -> String
(Int -> User -> ShowS)
-> (User -> String) -> ([User] -> ShowS) -> Show User
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [User] -> ShowS
$cshowList :: [User] -> ShowS
show :: User -> String
$cshow :: User -> String
showsPrec :: Int -> User -> ShowS
$cshowsPrec :: Int -> User -> ShowS
Show, User -> User -> Bool
(User -> User -> Bool) -> (User -> User -> Bool) -> Eq User
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: User -> User -> Bool
$c/= :: User -> User -> Bool
== :: User -> User -> Bool
$c== :: User -> User -> Bool
Eq, Eq User
Eq User
-> (User -> User -> Ordering)
-> (User -> User -> Bool)
-> (User -> User -> Bool)
-> (User -> User -> Bool)
-> (User -> User -> Bool)
-> (User -> User -> User)
-> (User -> User -> User)
-> Ord User
User -> User -> Bool
User -> User -> Ordering
User -> User -> User
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: User -> User -> User
$cmin :: User -> User -> User
max :: User -> User -> User
$cmax :: User -> User -> User
>= :: User -> User -> Bool
$c>= :: User -> User -> Bool
> :: User -> User -> Bool
$c> :: User -> User -> Bool
<= :: User -> User -> Bool
$c<= :: User -> User -> Bool
< :: User -> User -> Bool
$c< :: User -> User -> Bool
compare :: User -> User -> Ordering
$ccompare :: User -> User -> Ordering
$cp1Ord :: Eq User
Ord)

instance FromJSON User where
  parseJSON :: Value -> Parser User
parseJSON = String -> (Object -> Parser User) -> Value -> Parser User
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"User" ((Object -> Parser User) -> Value -> Parser User)
-> (Object -> Parser User) -> Value -> Parser User
forall a b. (a -> b) -> a -> b
$ \Object
o ->
    UserId
-> Text
-> Text
-> Maybe Text
-> Bool
-> Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> User
User (UserId
 -> Text
 -> Text
 -> Maybe Text
 -> Bool
 -> Bool
 -> Maybe Bool
 -> Maybe Bool
 -> Maybe Text
 -> User)
-> Parser UserId
-> Parser
     (Text
      -> Text
      -> Maybe Text
      -> Bool
      -> Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Text
      -> User)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser UserId
forall a. FromJSON a => Object -> Text -> Parser a
.:  Text
"id"
         Parser
  (Text
   -> Text
   -> Maybe Text
   -> Bool
   -> Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Text
   -> User)
-> Parser Text
-> Parser
     (Text
      -> Maybe Text
      -> Bool
      -> Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Text
      -> User)
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
"username"
         Parser
  (Text
   -> Maybe Text
   -> Bool
   -> Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Text
   -> User)
-> Parser Text
-> Parser
     (Maybe Text
      -> Bool -> Bool -> Maybe Bool -> Maybe Bool -> Maybe Text -> User)
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
"discriminator"
         Parser
  (Maybe Text
   -> Bool -> Bool -> Maybe Bool -> Maybe Bool -> Maybe Text -> User)
-> Parser (Maybe Text)
-> Parser
     (Bool -> Bool -> Maybe Bool -> Maybe Bool -> Maybe Text -> User)
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 (Maybe a)
.:? Text
"avatar"
         Parser
  (Bool -> Bool -> Maybe Bool -> Maybe Bool -> Maybe Text -> User)
-> Parser Bool
-> Parser (Bool -> Maybe Bool -> Maybe Bool -> Maybe Text -> User)
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
"bot" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
         Parser (Bool -> Maybe Bool -> Maybe Bool -> Maybe Text -> User)
-> Parser Bool
-> Parser (Maybe Bool -> Maybe Bool -> Maybe Text -> User)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Bool -> Parser Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False -- webhook
         Parser (Maybe Bool -> Maybe Bool -> Maybe Text -> User)
-> Parser (Maybe Bool) -> Parser (Maybe Bool -> Maybe Text -> User)
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
"mfa_enabled"
         Parser (Maybe Bool -> Maybe Text -> User)
-> Parser (Maybe Bool) -> Parser (Maybe Text -> User)
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
"verified"
         Parser (Maybe Text -> User) -> Parser (Maybe Text) -> Parser User
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 (Maybe a)
.:? Text
"email"

instance ToJSON User where
  toJSON :: User -> Value
toJSON User{Bool
Maybe Bool
Maybe Text
Text
UserId
userEmail :: Maybe Text
userVerified :: Maybe Bool
userMfa :: Maybe Bool
userIsWebhook :: Bool
userIsBot :: Bool
userAvatar :: Maybe Text
userDiscrim :: Text
userName :: Text
userId :: UserId
userEmail :: User -> Maybe Text
userVerified :: User -> Maybe Bool
userMfa :: User -> Maybe Bool
userIsWebhook :: User -> Bool
userIsBot :: User -> Bool
userAvatar :: User -> Maybe Text
userDiscrim :: User -> Text
userName :: User -> Text
userId :: User -> UserId
..} = [Pair] -> Value
object [(Text
name,Value
value) | (Text
name, Just Value
value) <-
              [ (Text
"id",            UserId -> Value
forall a. ToJSON a => a -> Value
toJSON (UserId -> Value) -> Maybe UserId -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> UserId -> Maybe UserId
forall (f :: * -> *) a. Applicative f => a -> f a
pure UserId
userId)
              , (Text
"username",      Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value) -> Maybe Text -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Maybe Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
userName)
              , (Text
"discriminator", Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value) -> Maybe Text -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Maybe Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
userDiscrim)
              , (Text
"avatar",        Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value) -> Maybe Text -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>      Maybe Text
userAvatar)
              , (Text
"bot",           Bool -> Value
forall a. ToJSON a => a -> Value
toJSON (Bool -> Value) -> Maybe Bool -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bool -> Maybe Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
userIsBot)
              , (Text
"webhook",       Bool -> Value
forall a. ToJSON a => a -> Value
toJSON (Bool -> Value) -> Maybe Bool -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bool -> Maybe Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
userIsWebhook)
              , (Text
"mfa_enabled",   Bool -> Value
forall a. ToJSON a => a -> Value
toJSON (Bool -> Value) -> Maybe Bool -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>      Maybe Bool
userMfa)
              , (Text
"verified",      Bool -> Value
forall a. ToJSON a => a -> Value
toJSON (Bool -> Value) -> Maybe Bool -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>      Maybe Bool
userVerified)
              , (Text
"email",         Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value) -> Maybe Text -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>      Maybe Text
userEmail)
              ] ]

data Webhook = Webhook
  { Webhook -> UserId
webhookId :: WebhookId
  , Webhook -> Text
webhookToken :: Text
  , Webhook -> UserId
webhookChannelId :: ChannelId
  } deriving (Int -> Webhook -> ShowS
[Webhook] -> ShowS
Webhook -> String
(Int -> Webhook -> ShowS)
-> (Webhook -> String) -> ([Webhook] -> ShowS) -> Show Webhook
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Webhook] -> ShowS
$cshowList :: [Webhook] -> ShowS
show :: Webhook -> String
$cshow :: Webhook -> String
showsPrec :: Int -> Webhook -> ShowS
$cshowsPrec :: Int -> Webhook -> ShowS
Show, Webhook -> Webhook -> Bool
(Webhook -> Webhook -> Bool)
-> (Webhook -> Webhook -> Bool) -> Eq Webhook
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Webhook -> Webhook -> Bool
$c/= :: Webhook -> Webhook -> Bool
== :: Webhook -> Webhook -> Bool
$c== :: Webhook -> Webhook -> Bool
Eq, Eq Webhook
Eq Webhook
-> (Webhook -> Webhook -> Ordering)
-> (Webhook -> Webhook -> Bool)
-> (Webhook -> Webhook -> Bool)
-> (Webhook -> Webhook -> Bool)
-> (Webhook -> Webhook -> Bool)
-> (Webhook -> Webhook -> Webhook)
-> (Webhook -> Webhook -> Webhook)
-> Ord Webhook
Webhook -> Webhook -> Bool
Webhook -> Webhook -> Ordering
Webhook -> Webhook -> Webhook
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Webhook -> Webhook -> Webhook
$cmin :: Webhook -> Webhook -> Webhook
max :: Webhook -> Webhook -> Webhook
$cmax :: Webhook -> Webhook -> Webhook
>= :: Webhook -> Webhook -> Bool
$c>= :: Webhook -> Webhook -> Bool
> :: Webhook -> Webhook -> Bool
$c> :: Webhook -> Webhook -> Bool
<= :: Webhook -> Webhook -> Bool
$c<= :: Webhook -> Webhook -> Bool
< :: Webhook -> Webhook -> Bool
$c< :: Webhook -> Webhook -> Bool
compare :: Webhook -> Webhook -> Ordering
$ccompare :: Webhook -> Webhook -> Ordering
$cp1Ord :: Eq Webhook
Ord)

instance FromJSON Webhook where
  parseJSON :: Value -> Parser Webhook
parseJSON = String -> (Object -> Parser Webhook) -> Value -> Parser Webhook
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Webhook" ((Object -> Parser Webhook) -> Value -> Parser Webhook)
-> (Object -> Parser Webhook) -> Value -> Parser Webhook
forall a b. (a -> b) -> a -> b
$ \Object
o ->
    UserId -> Text -> UserId -> Webhook
Webhook (UserId -> Text -> UserId -> Webhook)
-> Parser UserId -> Parser (Text -> UserId -> Webhook)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser UserId
forall a. FromJSON a => Object -> Text -> Parser a
.:  Text
"id"
            Parser (Text -> UserId -> Webhook)
-> Parser Text -> Parser (UserId -> Webhook)
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
"token"
            Parser (UserId -> Webhook) -> Parser UserId -> Parser Webhook
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser UserId
forall a. FromJSON a => Object -> Text -> Parser a
.:  Text
"channel_id"

data ConnectionObject = ConnectionObject
  { ConnectionObject -> Text
connectionObjectId :: Text
  , ConnectionObject -> Text
connectionObjectName :: Text
  , ConnectionObject -> Text
connectionObjectType :: Text
  , ConnectionObject -> Bool
connectionObjectRevoked :: Bool
  , ConnectionObject -> [UserId]
connectionObjectIntegrations :: [IntegrationId]
  , ConnectionObject -> Bool
connectionObjectVerified :: Bool
  , ConnectionObject -> Bool
connectionObjectFriendSyncOn :: Bool
  , ConnectionObject -> Bool
connectionObjectShownInPresenceUpdates :: Bool
  , ConnectionObject -> Bool
connectionObjectVisibleToOthers :: Bool
  } deriving (Int -> ConnectionObject -> ShowS
[ConnectionObject] -> ShowS
ConnectionObject -> String
(Int -> ConnectionObject -> ShowS)
-> (ConnectionObject -> String)
-> ([ConnectionObject] -> ShowS)
-> Show ConnectionObject
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConnectionObject] -> ShowS
$cshowList :: [ConnectionObject] -> ShowS
show :: ConnectionObject -> String
$cshow :: ConnectionObject -> String
showsPrec :: Int -> ConnectionObject -> ShowS
$cshowsPrec :: Int -> ConnectionObject -> ShowS
Show, ConnectionObject -> ConnectionObject -> Bool
(ConnectionObject -> ConnectionObject -> Bool)
-> (ConnectionObject -> ConnectionObject -> Bool)
-> Eq ConnectionObject
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConnectionObject -> ConnectionObject -> Bool
$c/= :: ConnectionObject -> ConnectionObject -> Bool
== :: ConnectionObject -> ConnectionObject -> Bool
$c== :: ConnectionObject -> ConnectionObject -> Bool
Eq, Eq ConnectionObject
Eq ConnectionObject
-> (ConnectionObject -> ConnectionObject -> Ordering)
-> (ConnectionObject -> ConnectionObject -> Bool)
-> (ConnectionObject -> ConnectionObject -> Bool)
-> (ConnectionObject -> ConnectionObject -> Bool)
-> (ConnectionObject -> ConnectionObject -> Bool)
-> (ConnectionObject -> ConnectionObject -> ConnectionObject)
-> (ConnectionObject -> ConnectionObject -> ConnectionObject)
-> Ord ConnectionObject
ConnectionObject -> ConnectionObject -> Bool
ConnectionObject -> ConnectionObject -> Ordering
ConnectionObject -> ConnectionObject -> ConnectionObject
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConnectionObject -> ConnectionObject -> ConnectionObject
$cmin :: ConnectionObject -> ConnectionObject -> ConnectionObject
max :: ConnectionObject -> ConnectionObject -> ConnectionObject
$cmax :: ConnectionObject -> ConnectionObject -> ConnectionObject
>= :: ConnectionObject -> ConnectionObject -> Bool
$c>= :: ConnectionObject -> ConnectionObject -> Bool
> :: ConnectionObject -> ConnectionObject -> Bool
$c> :: ConnectionObject -> ConnectionObject -> Bool
<= :: ConnectionObject -> ConnectionObject -> Bool
$c<= :: ConnectionObject -> ConnectionObject -> Bool
< :: ConnectionObject -> ConnectionObject -> Bool
$c< :: ConnectionObject -> ConnectionObject -> Bool
compare :: ConnectionObject -> ConnectionObject -> Ordering
$ccompare :: ConnectionObject -> ConnectionObject -> Ordering
$cp1Ord :: Eq ConnectionObject
Ord)

instance FromJSON ConnectionObject where
  parseJSON :: Value -> Parser ConnectionObject
parseJSON = String
-> (Object -> Parser ConnectionObject)
-> Value
-> Parser ConnectionObject
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ConnectionObject" ((Object -> Parser ConnectionObject)
 -> Value -> Parser ConnectionObject)
-> (Object -> Parser ConnectionObject)
-> Value
-> Parser ConnectionObject
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
    [Object]
integrations <- Object
o Object -> Text -> Parser [Object]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"integrations"
    Text
-> Text
-> Text
-> Bool
-> [UserId]
-> Bool
-> Bool
-> Bool
-> Bool
-> ConnectionObject
ConnectionObject (Text
 -> Text
 -> Text
 -> Bool
 -> [UserId]
 -> Bool
 -> Bool
 -> Bool
 -> Bool
 -> ConnectionObject)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Bool
      -> [UserId]
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> ConnectionObject)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id"
               Parser
  (Text
   -> Text
   -> Bool
   -> [UserId]
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> ConnectionObject)
-> Parser Text
-> Parser
     (Text
      -> Bool
      -> [UserId]
      -> Bool
      -> Bool
      -> Bool
      -> Bool
      -> ConnectionObject)
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
"name"
               Parser
  (Text
   -> Bool
   -> [UserId]
   -> Bool
   -> Bool
   -> Bool
   -> Bool
   -> ConnectionObject)
-> Parser Text
-> Parser
     (Bool
      -> [UserId] -> Bool -> Bool -> Bool -> Bool -> ConnectionObject)
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
"type"
               Parser
  (Bool
   -> [UserId] -> Bool -> Bool -> Bool -> Bool -> ConnectionObject)
-> Parser Bool
-> Parser
     ([UserId] -> Bool -> Bool -> Bool -> Bool -> ConnectionObject)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"revoked"
               Parser
  ([UserId] -> Bool -> Bool -> Bool -> Bool -> ConnectionObject)
-> Parser [UserId]
-> Parser (Bool -> Bool -> Bool -> Bool -> ConnectionObject)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Parser UserId] -> Parser [UserId]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence ((Object -> Parser UserId) -> [Object] -> [Parser UserId]
forall a b. (a -> b) -> [a] -> [b]
map (Object -> Text -> Parser UserId
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id") [Object]
integrations)
               Parser (Bool -> Bool -> Bool -> Bool -> ConnectionObject)
-> Parser Bool -> Parser (Bool -> Bool -> Bool -> ConnectionObject)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"verified"
               Parser (Bool -> Bool -> Bool -> ConnectionObject)
-> Parser Bool -> Parser (Bool -> Bool -> ConnectionObject)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"friend_sync"
               Parser (Bool -> Bool -> ConnectionObject)
-> Parser Bool -> Parser (Bool -> ConnectionObject)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"show_activity"
               Parser (Bool -> ConnectionObject)
-> Parser Bool -> Parser ConnectionObject
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ( Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
(==) (Int
1::Int) (Int -> Bool) -> Parser Int -> Parser Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"visibility")