{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE ExtendedDefaultRules #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StandaloneDeriving #-}
module Line.Bot.Webhook.Events
( Events(..)
, Event(..)
, Message(..)
, ContentProvider(..)
, EpochMilli(..)
, Source(..)
, MessageSource(..)
, Members(..)
, Postback(..)
, Beacon(..)
, BeaconEvent(..)
, Things(..)
, ThingsEvent(..)
, AccountLink(..)
, AccountLinkResult(..)
)
where
import Control.Arrow ((>>>))
import Data.Aeson
import Data.Char
import Data.Foldable
import Data.List as L (stripPrefix)
import Data.Text as T hiding (drop, toLower)
import Data.Time (UTCTime)
import Data.Time.Calendar (Day)
import Data.Time.Clock.POSIX
import Data.Time.Format
import Data.Time.LocalTime
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import Line.Bot.Types hiding (Message)
data Events = Events
{ Events -> Id 'User
destination :: Id 'User
, Events -> [Event]
events :: [Event]
}
deriving (Int -> Events -> ShowS
[Events] -> ShowS
Events -> String
(Int -> Events -> ShowS)
-> (Events -> String) -> ([Events] -> ShowS) -> Show Events
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Events] -> ShowS
$cshowList :: [Events] -> ShowS
show :: Events -> String
$cshow :: Events -> String
showsPrec :: Int -> Events -> ShowS
$cshowsPrec :: Int -> Events -> ShowS
Show, (forall x. Events -> Rep Events x)
-> (forall x. Rep Events x -> Events) -> Generic Events
forall x. Rep Events x -> Events
forall x. Events -> Rep Events x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Events x -> Events
$cfrom :: forall x. Events -> Rep Events x
Generic)
instance FromJSON Events
data Event =
EventMessage { Event -> ReplyToken
replyToken :: ReplyToken
, Event -> Message
message :: Message
, Event -> MessageSource
messageSource :: MessageSource
, Event -> EpochMilli
timestamp :: EpochMilli
}
| EventFollow { replyToken :: ReplyToken
, Event -> Source
source :: Source
, timestamp :: EpochMilli
}
| EventUnfollow { source :: Source
, timestamp :: EpochMilli
}
| EventJoin { replyToken :: ReplyToken
, source :: Source
, timestamp :: EpochMilli
}
| EventLeave { source :: Source
, timestamp :: EpochMilli
}
| EventMemberJoined { replyToken :: ReplyToken
, source :: Source
, timestamp :: EpochMilli
, Event -> Members
joined :: Members
}
| EventMemberLeft { source :: Source
, timestamp :: EpochMilli
, Event -> Members
left :: Members
}
| EventPostback { replyToken :: ReplyToken
, source :: Source
, timestamp :: EpochMilli
, Event -> Postback
postback :: Postback
}
| EventBeacon { replyToken :: ReplyToken
, source :: Source
, timestamp :: EpochMilli
, Event -> Beacon
beacon :: Beacon
}
| EventAccountLink { replyToken :: ReplyToken
, source :: Source
, timestamp :: EpochMilli
, Event -> AccountLink
link :: AccountLink
}
| EventThings { replyToken :: ReplyToken
, source :: Source
, timestamp :: EpochMilli
, Event -> Things
things :: Things
}
deriving (Int -> Event -> ShowS
[Event] -> ShowS
Event -> String
(Int -> Event -> ShowS)
-> (Event -> String) -> ([Event] -> ShowS) -> Show Event
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Event] -> ShowS
$cshowList :: [Event] -> ShowS
show :: Event -> String
$cshow :: Event -> String
showsPrec :: Int -> Event -> ShowS
$cshowsPrec :: Int -> Event -> ShowS
Show, (forall x. Event -> Rep Event x)
-> (forall x. Rep Event x -> Event) -> Generic Event
forall x. Rep Event x -> Event
forall x. Event -> Rep Event x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Event x -> Event
$cfrom :: forall x. Event -> Rep Event x
Generic)
instance FromJSON Event where
parseJSON :: Value -> Parser Event
parseJSON = Options -> Value -> Parser Event
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions
{ sumEncoding :: SumEncoding
sumEncoding = TaggedObject :: String -> String -> SumEncoding
TaggedObject
{ tagFieldName :: String
tagFieldName = String
"type"
, contentsFieldName :: String
contentsFieldName = String
forall a. HasCallStack => a
undefined
}
, constructorTagModifier :: ShowS
constructorTagModifier = Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
5 ShowS -> ShowS -> ShowS
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> \(Char
x:String
xs) -> Char -> Char
toLower Char
x Char -> ShowS
forall a. a -> [a] -> [a]
: String
xs
, fieldLabelModifier :: ShowS
fieldLabelModifier = \String
s -> if String
s String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"messageSource" then String
"source" else String
s
}
data Message =
MessageText { Message -> MessageId
messageId :: MessageId
, Message -> MessageId
text :: Text
}
| MessageImage { messageId :: MessageId
, Message -> ContentProvider
contentProvider :: ContentProvider
}
| MessageVideo { messageId :: MessageId
, Message -> Int
duration :: Int
, contentProvider :: ContentProvider
}
| MessageAudio { messageId :: MessageId
, duration :: Int
, contentProvider :: ContentProvider
}
| MessageFile { messageId :: MessageId
, Message -> Int
fileSize :: Int
, Message -> MessageId
fileName :: Text
}
| MessageLocation { messageId :: MessageId
, Message -> Maybe MessageId
title :: Maybe Text
, Message -> MessageId
address :: Text
, Message -> Double
latitude :: Double
, Message -> Double
longitude :: Double
}
| MessageSticker { messageId :: MessageId
, Message -> MessageId
packageId :: Text
, Message -> MessageId
stickerId :: Text
}
deriving (Message -> Message -> Bool
(Message -> Message -> Bool)
-> (Message -> Message -> Bool) -> Eq Message
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Message -> Message -> Bool
$c/= :: Message -> Message -> Bool
== :: Message -> Message -> Bool
$c== :: Message -> Message -> Bool
Eq, Int -> Message -> ShowS
[Message] -> ShowS
Message -> String
(Int -> Message -> ShowS)
-> (Message -> String) -> ([Message] -> ShowS) -> Show Message
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Message] -> ShowS
$cshowList :: [Message] -> ShowS
show :: Message -> String
$cshow :: Message -> String
showsPrec :: Int -> Message -> ShowS
$cshowsPrec :: Int -> Message -> ShowS
Show, (forall x. Message -> Rep Message x)
-> (forall x. Rep Message x -> Message) -> Generic Message
forall x. Rep Message x -> Message
forall x. Message -> Rep Message x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Message x -> Message
$cfrom :: forall x. Message -> Rep Message x
Generic)
messageJSONOptions :: Options
messageJSONOptions :: Options
messageJSONOptions = Options
defaultOptions
{ sumEncoding :: SumEncoding
sumEncoding = TaggedObject :: String -> String -> SumEncoding
TaggedObject
{ tagFieldName :: String
tagFieldName = String
"type"
, contentsFieldName :: String
contentsFieldName = String
forall a. HasCallStack => a
undefined
}
, constructorTagModifier :: ShowS
constructorTagModifier = (Char -> Char) -> ShowS
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Char -> Char
toLower ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
7
, fieldLabelModifier :: ShowS
fieldLabelModifier = \String
x -> String -> ShowS -> Maybe String -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
x ((Char -> Char) -> ShowS
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Char -> Char
toLower) (Maybe String -> String) -> Maybe String -> String
forall a b. (a -> b) -> a -> b
$ String -> String -> Maybe String
forall a. Eq a => [a] -> [a] -> Maybe [a]
L.stripPrefix String
"message" String
x
, omitNothingFields :: Bool
omitNothingFields = Bool
True
}
instance FromJSON Message where
parseJSON :: Value -> Parser Message
parseJSON = Options -> Value -> Parser Message
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
messageJSONOptions
data ContentProvider = ContentProvider
{ ContentProvider -> Maybe URL
originalContentUrl :: Maybe URL
, ContentProvider -> Maybe URL
previewImageUrl :: Maybe URL
}
deriving (ContentProvider -> ContentProvider -> Bool
(ContentProvider -> ContentProvider -> Bool)
-> (ContentProvider -> ContentProvider -> Bool)
-> Eq ContentProvider
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ContentProvider -> ContentProvider -> Bool
$c/= :: ContentProvider -> ContentProvider -> Bool
== :: ContentProvider -> ContentProvider -> Bool
$c== :: ContentProvider -> ContentProvider -> Bool
Eq, Int -> ContentProvider -> ShowS
[ContentProvider] -> ShowS
ContentProvider -> String
(Int -> ContentProvider -> ShowS)
-> (ContentProvider -> String)
-> ([ContentProvider] -> ShowS)
-> Show ContentProvider
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ContentProvider] -> ShowS
$cshowList :: [ContentProvider] -> ShowS
show :: ContentProvider -> String
$cshow :: ContentProvider -> String
showsPrec :: Int -> ContentProvider -> ShowS
$cshowsPrec :: Int -> ContentProvider -> ShowS
Show, (forall x. ContentProvider -> Rep ContentProvider x)
-> (forall x. Rep ContentProvider x -> ContentProvider)
-> Generic ContentProvider
forall x. Rep ContentProvider x -> ContentProvider
forall x. ContentProvider -> Rep ContentProvider x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ContentProvider x -> ContentProvider
$cfrom :: forall x. ContentProvider -> Rep ContentProvider x
Generic)
instance FromJSON ContentProvider
newtype EpochMilli = EpochMilli {
EpochMilli -> UTCTime
fromEpochMilli :: UTCTime
} deriving (EpochMilli -> EpochMilli -> Bool
(EpochMilli -> EpochMilli -> Bool)
-> (EpochMilli -> EpochMilli -> Bool) -> Eq EpochMilli
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EpochMilli -> EpochMilli -> Bool
$c/= :: EpochMilli -> EpochMilli -> Bool
== :: EpochMilli -> EpochMilli -> Bool
$c== :: EpochMilli -> EpochMilli -> Bool
Eq, Eq EpochMilli
Eq EpochMilli
-> (EpochMilli -> EpochMilli -> Ordering)
-> (EpochMilli -> EpochMilli -> Bool)
-> (EpochMilli -> EpochMilli -> Bool)
-> (EpochMilli -> EpochMilli -> Bool)
-> (EpochMilli -> EpochMilli -> Bool)
-> (EpochMilli -> EpochMilli -> EpochMilli)
-> (EpochMilli -> EpochMilli -> EpochMilli)
-> Ord EpochMilli
EpochMilli -> EpochMilli -> Bool
EpochMilli -> EpochMilli -> Ordering
EpochMilli -> EpochMilli -> EpochMilli
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 :: EpochMilli -> EpochMilli -> EpochMilli
$cmin :: EpochMilli -> EpochMilli -> EpochMilli
max :: EpochMilli -> EpochMilli -> EpochMilli
$cmax :: EpochMilli -> EpochMilli -> EpochMilli
>= :: EpochMilli -> EpochMilli -> Bool
$c>= :: EpochMilli -> EpochMilli -> Bool
> :: EpochMilli -> EpochMilli -> Bool
$c> :: EpochMilli -> EpochMilli -> Bool
<= :: EpochMilli -> EpochMilli -> Bool
$c<= :: EpochMilli -> EpochMilli -> Bool
< :: EpochMilli -> EpochMilli -> Bool
$c< :: EpochMilli -> EpochMilli -> Bool
compare :: EpochMilli -> EpochMilli -> Ordering
$ccompare :: EpochMilli -> EpochMilli -> Ordering
$cp1Ord :: Eq EpochMilli
Ord, ReadPrec [EpochMilli]
ReadPrec EpochMilli
Int -> ReadS EpochMilli
ReadS [EpochMilli]
(Int -> ReadS EpochMilli)
-> ReadS [EpochMilli]
-> ReadPrec EpochMilli
-> ReadPrec [EpochMilli]
-> Read EpochMilli
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EpochMilli]
$creadListPrec :: ReadPrec [EpochMilli]
readPrec :: ReadPrec EpochMilli
$creadPrec :: ReadPrec EpochMilli
readList :: ReadS [EpochMilli]
$creadList :: ReadS [EpochMilli]
readsPrec :: Int -> ReadS EpochMilli
$creadsPrec :: Int -> ReadS EpochMilli
Read, Int -> EpochMilli -> ShowS
[EpochMilli] -> ShowS
EpochMilli -> String
(Int -> EpochMilli -> ShowS)
-> (EpochMilli -> String)
-> ([EpochMilli] -> ShowS)
-> Show EpochMilli
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EpochMilli] -> ShowS
$cshowList :: [EpochMilli] -> ShowS
show :: EpochMilli -> String
$cshow :: EpochMilli -> String
showsPrec :: Int -> EpochMilli -> ShowS
$cshowsPrec :: Int -> EpochMilli -> ShowS
Show, Bool -> Char -> Maybe (FormatOptions -> EpochMilli -> String)
(Bool -> Char -> Maybe (FormatOptions -> EpochMilli -> String))
-> FormatTime EpochMilli
forall t.
(Bool -> Char -> Maybe (FormatOptions -> t -> String))
-> FormatTime t
formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> EpochMilli -> String)
$cformatCharacter :: Bool -> Char -> Maybe (FormatOptions -> EpochMilli -> String)
FormatTime)
instance FromJSON EpochMilli where
parseJSON :: Value -> Parser EpochMilli
parseJSON = String
-> (Scientific -> Parser EpochMilli) -> Value -> Parser EpochMilli
forall a. String -> (Scientific -> Parser a) -> Value -> Parser a
withScientific String
"EpochMilli" ((Scientific -> Parser EpochMilli) -> Value -> Parser EpochMilli)
-> (Scientific -> Parser EpochMilli) -> Value -> Parser EpochMilli
forall a b. (a -> b) -> a -> b
$ \Scientific
t ->
EpochMilli -> Parser EpochMilli
forall (f :: * -> *) a. Applicative f => a -> f a
pure (EpochMilli -> Parser EpochMilli)
-> EpochMilli -> Parser EpochMilli
forall a b. (a -> b) -> a -> b
$ Scientific -> EpochMilli
millis Scientific
t
where
millis :: Scientific -> EpochMilli
millis = UTCTime -> EpochMilli
EpochMilli
(UTCTime -> EpochMilli)
-> (Scientific -> UTCTime) -> Scientific -> EpochMilli
forall b c a. (b -> c) -> (a -> b) -> a -> c
. POSIXTime -> UTCTime
posixSecondsToUTCTime
(POSIXTime -> UTCTime)
-> (Scientific -> POSIXTime) -> Scientific -> UTCTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rational -> POSIXTime
forall a. Fractional a => Rational -> a
fromRational
(Rational -> POSIXTime)
-> (Scientific -> Rational) -> Scientific -> POSIXTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Scientific -> Rational
forall a. Real a => a -> Rational
toRational
(Scientific -> Rational)
-> (Scientific -> Scientific) -> Scientific -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Scientific -> Scientific -> Scientific
forall a. Fractional a => a -> a -> a
/ Scientific
1000)
data Source = forall a. Source (Id a)
deriving instance Show Source
deriving instance Typeable Source
instance FromJSON Source where
parseJSON :: Value -> Parser Source
parseJSON = String -> (Object -> Parser Source) -> Value -> Parser Source
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Source" ((Object -> Parser Source) -> Value -> Parser Source)
-> (Object -> Parser Source) -> Value -> Parser Source
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
String
messageType <- Object
o Object -> MessageId -> Parser String
forall a. FromJSON a => Object -> MessageId -> Parser a
.: MessageId
"type"
case String
messageType of
String
"user" -> Id 'User -> Source
forall (a :: ChatType). Id a -> Source
Source (Id 'User -> Source)
-> (MessageId -> Id 'User) -> MessageId -> Source
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MessageId -> Id 'User
UserId (MessageId -> Source) -> Parser MessageId -> Parser Source
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> MessageId -> Parser MessageId
forall a. FromJSON a => Object -> MessageId -> Parser a
.: MessageId
"userId"
String
"group" -> Id 'Group -> Source
forall (a :: ChatType). Id a -> Source
Source (Id 'Group -> Source)
-> (MessageId -> Id 'Group) -> MessageId -> Source
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MessageId -> Id 'Group
GroupId (MessageId -> Source) -> Parser MessageId -> Parser Source
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> MessageId -> Parser MessageId
forall a. FromJSON a => Object -> MessageId -> Parser a
.: MessageId
"groupId"
String
"room" -> Id 'Room -> Source
forall (a :: ChatType). Id a -> Source
Source (Id 'Room -> Source)
-> (MessageId -> Id 'Room) -> MessageId -> Source
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MessageId -> Id 'Room
RoomId (MessageId -> Source) -> Parser MessageId -> Parser Source
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> MessageId -> Parser MessageId
forall a. FromJSON a => Object -> MessageId -> Parser a
.: MessageId
"roomId"
String
_ -> String -> Parser Source
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"unknown source: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
messageType)
instance ToJSON Source where
toJSON :: Source -> Value
toJSON (Source (UserId MessageId
a)) = [Pair] -> Value
object [MessageId
"type" MessageId -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => MessageId -> v -> kv
.= MessageId -> Value
String MessageId
"user", MessageId
"userId" MessageId -> MessageId -> Pair
forall kv v. (KeyValue kv, ToJSON v) => MessageId -> v -> kv
.= MessageId
a]
toJSON (Source (GroupId MessageId
a)) = [Pair] -> Value
object [MessageId
"type" MessageId -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => MessageId -> v -> kv
.= MessageId -> Value
String MessageId
"group", MessageId
"groupId" MessageId -> MessageId -> Pair
forall kv v. (KeyValue kv, ToJSON v) => MessageId -> v -> kv
.= MessageId
a]
toJSON (Source (RoomId MessageId
a)) = [Pair] -> Value
object [MessageId
"type" MessageId -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => MessageId -> v -> kv
.= MessageId -> Value
String MessageId
"room", MessageId
"roomId" MessageId -> MessageId -> Pair
forall kv v. (KeyValue kv, ToJSON v) => MessageId -> v -> kv
.= MessageId
a]
data MessageSource
= MessageSourceUser (Id 'User)
| MessageSourceGroup (Id 'Group) (Id 'User)
| MessageSourceRoom (Id 'Room) (Id 'User)
deriving instance Show MessageSource
deriving instance Typeable MessageSource
instance FromJSON MessageSource where
parseJSON :: Value -> Parser MessageSource
parseJSON = String
-> (Object -> Parser MessageSource)
-> Value
-> Parser MessageSource
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"MessageSource" ((Object -> Parser MessageSource) -> Value -> Parser MessageSource)
-> (Object -> Parser MessageSource)
-> Value
-> Parser MessageSource
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
String
messageType <- Object
o Object -> MessageId -> Parser String
forall a. FromJSON a => Object -> MessageId -> Parser a
.: MessageId
"type"
case String
messageType of
String
"user" -> Id 'User -> MessageSource
MessageSourceUser (Id 'User -> MessageSource)
-> (MessageId -> Id 'User) -> MessageId -> MessageSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MessageId -> Id 'User
UserId (MessageId -> MessageSource)
-> Parser MessageId -> Parser MessageSource
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> MessageId -> Parser MessageId
forall a. FromJSON a => Object -> MessageId -> Parser a
.: MessageId
"userId"
String
"group" -> Id 'Group -> Id 'User -> MessageSource
MessageSourceGroup (Id 'Group -> Id 'User -> MessageSource)
-> Parser (Id 'Group) -> Parser (Id 'User -> MessageSource)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (MessageId -> Id 'Group
GroupId (MessageId -> Id 'Group) -> Parser MessageId -> Parser (Id 'Group)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> MessageId -> Parser MessageId
forall a. FromJSON a => Object -> MessageId -> Parser a
.: MessageId
"groupId") Parser (Id 'User -> MessageSource)
-> Parser (Id 'User) -> Parser MessageSource
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (MessageId -> Id 'User
UserId (MessageId -> Id 'User) -> Parser MessageId -> Parser (Id 'User)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> MessageId -> Parser MessageId
forall a. FromJSON a => Object -> MessageId -> Parser a
.: MessageId
"userId")
String
"room" -> Id 'Room -> Id 'User -> MessageSource
MessageSourceRoom (Id 'Room -> Id 'User -> MessageSource)
-> Parser (Id 'Room) -> Parser (Id 'User -> MessageSource)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (MessageId -> Id 'Room
RoomId (MessageId -> Id 'Room) -> Parser MessageId -> Parser (Id 'Room)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> MessageId -> Parser MessageId
forall a. FromJSON a => Object -> MessageId -> Parser a
.: MessageId
"roomId") Parser (Id 'User -> MessageSource)
-> Parser (Id 'User) -> Parser MessageSource
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (MessageId -> Id 'User
UserId (MessageId -> Id 'User) -> Parser MessageId -> Parser (Id 'User)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> MessageId -> Parser MessageId
forall a. FromJSON a => Object -> MessageId -> Parser a
.: MessageId
"userId")
String
_ -> String -> Parser MessageSource
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"unknown message source: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
messageType)
instance ToJSON MessageSource where
toJSON :: MessageSource -> Value
toJSON (MessageSourceUser (UserId MessageId
a)) = [Pair] -> Value
object [MessageId
"type" MessageId -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => MessageId -> v -> kv
.= MessageId -> Value
String MessageId
"user", MessageId
"userId" MessageId -> MessageId -> Pair
forall kv v. (KeyValue kv, ToJSON v) => MessageId -> v -> kv
.= MessageId
a]
toJSON (MessageSourceGroup (GroupId MessageId
a) (UserId MessageId
b)) = [Pair] -> Value
object [MessageId
"type" MessageId -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => MessageId -> v -> kv
.= MessageId -> Value
String MessageId
"group", MessageId
"groupId" MessageId -> MessageId -> Pair
forall kv v. (KeyValue kv, ToJSON v) => MessageId -> v -> kv
.= MessageId
a, MessageId
"userId" MessageId -> MessageId -> Pair
forall kv v. (KeyValue kv, ToJSON v) => MessageId -> v -> kv
.= MessageId
b]
toJSON (MessageSourceRoom (RoomId MessageId
a) (UserId MessageId
b)) = [Pair] -> Value
object [MessageId
"type" MessageId -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => MessageId -> v -> kv
.= MessageId -> Value
String MessageId
"room", MessageId
"roomId" MessageId -> MessageId -> Pair
forall kv v. (KeyValue kv, ToJSON v) => MessageId -> v -> kv
.= MessageId
a, MessageId
"userId" MessageId -> MessageId -> Pair
forall kv v. (KeyValue kv, ToJSON v) => MessageId -> v -> kv
.= MessageId
b]
newtype Members = Members { Members -> [Source]
members :: [Source] }
deriving (Int -> Members -> ShowS
[Members] -> ShowS
Members -> String
(Int -> Members -> ShowS)
-> (Members -> String) -> ([Members] -> ShowS) -> Show Members
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Members] -> ShowS
$cshowList :: [Members] -> ShowS
show :: Members -> String
$cshow :: Members -> String
showsPrec :: Int -> Members -> ShowS
$cshowsPrec :: Int -> Members -> ShowS
Show, (forall x. Members -> Rep Members x)
-> (forall x. Rep Members x -> Members) -> Generic Members
forall x. Rep Members x -> Members
forall x. Members -> Rep Members x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Members x -> Members
$cfrom :: forall x. Members -> Rep Members x
Generic)
instance FromJSON Members
data PostbackDateTime =
PostbackDay Day
| PostbackLocalTime LocalTime
| PostbackTimeOfDay TimeOfDay
deriving (PostbackDateTime -> PostbackDateTime -> Bool
(PostbackDateTime -> PostbackDateTime -> Bool)
-> (PostbackDateTime -> PostbackDateTime -> Bool)
-> Eq PostbackDateTime
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostbackDateTime -> PostbackDateTime -> Bool
$c/= :: PostbackDateTime -> PostbackDateTime -> Bool
== :: PostbackDateTime -> PostbackDateTime -> Bool
$c== :: PostbackDateTime -> PostbackDateTime -> Bool
Eq, Int -> PostbackDateTime -> ShowS
[PostbackDateTime] -> ShowS
PostbackDateTime -> String
(Int -> PostbackDateTime -> ShowS)
-> (PostbackDateTime -> String)
-> ([PostbackDateTime] -> ShowS)
-> Show PostbackDateTime
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostbackDateTime] -> ShowS
$cshowList :: [PostbackDateTime] -> ShowS
show :: PostbackDateTime -> String
$cshow :: PostbackDateTime -> String
showsPrec :: Int -> PostbackDateTime -> ShowS
$cshowsPrec :: Int -> PostbackDateTime -> ShowS
Show)
instance FromJSON PostbackDateTime where
parseJSON :: Value -> Parser PostbackDateTime
parseJSON = String
-> (Object -> Parser PostbackDateTime)
-> Value
-> Parser PostbackDateTime
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PostbackDateTime" ((Object -> Parser PostbackDateTime)
-> Value -> Parser PostbackDateTime)
-> (Object -> Parser PostbackDateTime)
-> Value
-> Parser PostbackDateTime
forall a b. (a -> b) -> a -> b
$ \Object
o ->
[Parser PostbackDateTime] -> Parser PostbackDateTime
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
asum
[ Day -> PostbackDateTime
PostbackDay (Day -> PostbackDateTime) -> Parser Day -> Parser PostbackDateTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> MessageId -> Parser Day
forall a. FromJSON a => Object -> MessageId -> Parser a
.: MessageId
"date"
, LocalTime -> PostbackDateTime
PostbackLocalTime (LocalTime -> PostbackDateTime)
-> Parser LocalTime -> Parser PostbackDateTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> MessageId -> Parser LocalTime
forall a. FromJSON a => Object -> MessageId -> Parser a
.: MessageId
"datetime"
, TimeOfDay -> PostbackDateTime
PostbackTimeOfDay (TimeOfDay -> PostbackDateTime)
-> Parser TimeOfDay -> Parser PostbackDateTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> MessageId -> Parser TimeOfDay
forall a. FromJSON a => Object -> MessageId -> Parser a
.: MessageId
"time"
]
data Postback = Postback Text (Maybe PostbackDateTime)
deriving (Postback -> Postback -> Bool
(Postback -> Postback -> Bool)
-> (Postback -> Postback -> Bool) -> Eq Postback
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Postback -> Postback -> Bool
$c/= :: Postback -> Postback -> Bool
== :: Postback -> Postback -> Bool
$c== :: Postback -> Postback -> Bool
Eq, Int -> Postback -> ShowS
[Postback] -> ShowS
Postback -> String
(Int -> Postback -> ShowS)
-> (Postback -> String) -> ([Postback] -> ShowS) -> Show Postback
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Postback] -> ShowS
$cshowList :: [Postback] -> ShowS
show :: Postback -> String
$cshow :: Postback -> String
showsPrec :: Int -> Postback -> ShowS
$cshowsPrec :: Int -> Postback -> ShowS
Show)
instance FromJSON Postback where
parseJSON :: Value -> Parser Postback
parseJSON = String -> (Object -> Parser Postback) -> Value -> Parser Postback
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Postback" ((Object -> Parser Postback) -> Value -> Parser Postback)
-> (Object -> Parser Postback) -> Value -> Parser Postback
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
MessageId
postbackData <- Object
o Object -> MessageId -> Parser MessageId
forall a. FromJSON a => Object -> MessageId -> Parser a
.: MessageId
"data"
Maybe PostbackDateTime
params <- Object
o Object -> MessageId -> Parser (Maybe PostbackDateTime)
forall a. FromJSON a => Object -> MessageId -> Parser (Maybe a)
.:? MessageId
"params"
Postback -> Parser Postback
forall (m :: * -> *) a. Monad m => a -> m a
return (Postback -> Parser Postback) -> Postback -> Parser Postback
forall a b. (a -> b) -> a -> b
$ MessageId -> Maybe PostbackDateTime -> Postback
Postback MessageId
postbackData Maybe PostbackDateTime
params
data BeaconEvent = Enter | Leave | Banner
deriving (Int -> BeaconEvent -> ShowS
[BeaconEvent] -> ShowS
BeaconEvent -> String
(Int -> BeaconEvent -> ShowS)
-> (BeaconEvent -> String)
-> ([BeaconEvent] -> ShowS)
-> Show BeaconEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BeaconEvent] -> ShowS
$cshowList :: [BeaconEvent] -> ShowS
show :: BeaconEvent -> String
$cshow :: BeaconEvent -> String
showsPrec :: Int -> BeaconEvent -> ShowS
$cshowsPrec :: Int -> BeaconEvent -> ShowS
Show, ReadPrec [BeaconEvent]
ReadPrec BeaconEvent
Int -> ReadS BeaconEvent
ReadS [BeaconEvent]
(Int -> ReadS BeaconEvent)
-> ReadS [BeaconEvent]
-> ReadPrec BeaconEvent
-> ReadPrec [BeaconEvent]
-> Read BeaconEvent
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BeaconEvent]
$creadListPrec :: ReadPrec [BeaconEvent]
readPrec :: ReadPrec BeaconEvent
$creadPrec :: ReadPrec BeaconEvent
readList :: ReadS [BeaconEvent]
$creadList :: ReadS [BeaconEvent]
readsPrec :: Int -> ReadS BeaconEvent
$creadsPrec :: Int -> ReadS BeaconEvent
Read, BeaconEvent -> BeaconEvent -> Bool
(BeaconEvent -> BeaconEvent -> Bool)
-> (BeaconEvent -> BeaconEvent -> Bool) -> Eq BeaconEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BeaconEvent -> BeaconEvent -> Bool
$c/= :: BeaconEvent -> BeaconEvent -> Bool
== :: BeaconEvent -> BeaconEvent -> Bool
$c== :: BeaconEvent -> BeaconEvent -> Bool
Eq, Eq BeaconEvent
Eq BeaconEvent
-> (BeaconEvent -> BeaconEvent -> Ordering)
-> (BeaconEvent -> BeaconEvent -> Bool)
-> (BeaconEvent -> BeaconEvent -> Bool)
-> (BeaconEvent -> BeaconEvent -> Bool)
-> (BeaconEvent -> BeaconEvent -> Bool)
-> (BeaconEvent -> BeaconEvent -> BeaconEvent)
-> (BeaconEvent -> BeaconEvent -> BeaconEvent)
-> Ord BeaconEvent
BeaconEvent -> BeaconEvent -> Bool
BeaconEvent -> BeaconEvent -> Ordering
BeaconEvent -> BeaconEvent -> BeaconEvent
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 :: BeaconEvent -> BeaconEvent -> BeaconEvent
$cmin :: BeaconEvent -> BeaconEvent -> BeaconEvent
max :: BeaconEvent -> BeaconEvent -> BeaconEvent
$cmax :: BeaconEvent -> BeaconEvent -> BeaconEvent
>= :: BeaconEvent -> BeaconEvent -> Bool
$c>= :: BeaconEvent -> BeaconEvent -> Bool
> :: BeaconEvent -> BeaconEvent -> Bool
$c> :: BeaconEvent -> BeaconEvent -> Bool
<= :: BeaconEvent -> BeaconEvent -> Bool
$c<= :: BeaconEvent -> BeaconEvent -> Bool
< :: BeaconEvent -> BeaconEvent -> Bool
$c< :: BeaconEvent -> BeaconEvent -> Bool
compare :: BeaconEvent -> BeaconEvent -> Ordering
$ccompare :: BeaconEvent -> BeaconEvent -> Ordering
$cp1Ord :: Eq BeaconEvent
Ord, (forall x. BeaconEvent -> Rep BeaconEvent x)
-> (forall x. Rep BeaconEvent x -> BeaconEvent)
-> Generic BeaconEvent
forall x. Rep BeaconEvent x -> BeaconEvent
forall x. BeaconEvent -> Rep BeaconEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BeaconEvent x -> BeaconEvent
$cfrom :: forall x. BeaconEvent -> Rep BeaconEvent x
Generic)
instance FromJSON BeaconEvent where
parseJSON :: Value -> Parser BeaconEvent
parseJSON = Options -> Value -> Parser BeaconEvent
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser BeaconEvent)
-> Options -> Value -> Parser BeaconEvent
forall a b. (a -> b) -> a -> b
$
Options
defaultOptions { constructorTagModifier :: ShowS
constructorTagModifier = (Char -> Char) -> ShowS
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Char -> Char
toLower
, allNullaryToStringTag :: Bool
allNullaryToStringTag = Bool
True
}
data Beacon = Beacon
{ Beacon -> MessageId
hwid :: Text
, Beacon -> BeaconEvent
eventType :: BeaconEvent
, Beacon -> Maybe MessageId
dm :: Maybe Text
}
deriving (Beacon -> Beacon -> Bool
(Beacon -> Beacon -> Bool)
-> (Beacon -> Beacon -> Bool) -> Eq Beacon
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Beacon -> Beacon -> Bool
$c/= :: Beacon -> Beacon -> Bool
== :: Beacon -> Beacon -> Bool
$c== :: Beacon -> Beacon -> Bool
Eq, Int -> Beacon -> ShowS
[Beacon] -> ShowS
Beacon -> String
(Int -> Beacon -> ShowS)
-> (Beacon -> String) -> ([Beacon] -> ShowS) -> Show Beacon
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Beacon] -> ShowS
$cshowList :: [Beacon] -> ShowS
show :: Beacon -> String
$cshow :: Beacon -> String
showsPrec :: Int -> Beacon -> ShowS
$cshowsPrec :: Int -> Beacon -> ShowS
Show, (forall x. Beacon -> Rep Beacon x)
-> (forall x. Rep Beacon x -> Beacon) -> Generic Beacon
forall x. Rep Beacon x -> Beacon
forall x. Beacon -> Rep Beacon x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Beacon x -> Beacon
$cfrom :: forall x. Beacon -> Rep Beacon x
Generic)
instance FromJSON Beacon where
parseJSON :: Value -> Parser Beacon
parseJSON = String -> (Object -> Parser Beacon) -> Value -> Parser Beacon
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Beacon" ((Object -> Parser Beacon) -> Value -> Parser Beacon)
-> (Object -> Parser Beacon) -> Value -> Parser Beacon
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
MessageId
hwid <- Object
o Object -> MessageId -> Parser MessageId
forall a. FromJSON a => Object -> MessageId -> Parser a
.: MessageId
"hwid"
BeaconEvent
eventType <- Object
o Object -> MessageId -> Parser BeaconEvent
forall a. FromJSON a => Object -> MessageId -> Parser a
.: MessageId
"type"
Maybe MessageId
dm <- Object
o Object -> MessageId -> Parser (Maybe MessageId)
forall a. FromJSON a => Object -> MessageId -> Parser (Maybe a)
.:? MessageId
"dm"
Beacon -> Parser Beacon
forall (m :: * -> *) a. Monad m => a -> m a
return Beacon :: MessageId -> BeaconEvent -> Maybe MessageId -> Beacon
Beacon{Maybe MessageId
MessageId
BeaconEvent
dm :: Maybe MessageId
eventType :: BeaconEvent
hwid :: MessageId
$sel:dm:Beacon :: Maybe MessageId
$sel:eventType:Beacon :: BeaconEvent
$sel:hwid:Beacon :: MessageId
..}
data AccountLinkResult = Ok | Failed
deriving (AccountLinkResult -> AccountLinkResult -> Bool
(AccountLinkResult -> AccountLinkResult -> Bool)
-> (AccountLinkResult -> AccountLinkResult -> Bool)
-> Eq AccountLinkResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccountLinkResult -> AccountLinkResult -> Bool
$c/= :: AccountLinkResult -> AccountLinkResult -> Bool
== :: AccountLinkResult -> AccountLinkResult -> Bool
$c== :: AccountLinkResult -> AccountLinkResult -> Bool
Eq, Int -> AccountLinkResult -> ShowS
[AccountLinkResult] -> ShowS
AccountLinkResult -> String
(Int -> AccountLinkResult -> ShowS)
-> (AccountLinkResult -> String)
-> ([AccountLinkResult] -> ShowS)
-> Show AccountLinkResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccountLinkResult] -> ShowS
$cshowList :: [AccountLinkResult] -> ShowS
show :: AccountLinkResult -> String
$cshow :: AccountLinkResult -> String
showsPrec :: Int -> AccountLinkResult -> ShowS
$cshowsPrec :: Int -> AccountLinkResult -> ShowS
Show, (forall x. AccountLinkResult -> Rep AccountLinkResult x)
-> (forall x. Rep AccountLinkResult x -> AccountLinkResult)
-> Generic AccountLinkResult
forall x. Rep AccountLinkResult x -> AccountLinkResult
forall x. AccountLinkResult -> Rep AccountLinkResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AccountLinkResult x -> AccountLinkResult
$cfrom :: forall x. AccountLinkResult -> Rep AccountLinkResult x
Generic)
instance FromJSON AccountLinkResult where
parseJSON :: Value -> Parser AccountLinkResult
parseJSON = Options -> Value -> Parser AccountLinkResult
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser AccountLinkResult)
-> Options -> Value -> Parser AccountLinkResult
forall a b. (a -> b) -> a -> b
$
Options
defaultOptions { constructorTagModifier :: ShowS
constructorTagModifier = (Char -> Char) -> ShowS
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Char -> Char
toLower
, allNullaryToStringTag :: Bool
allNullaryToStringTag = Bool
True
}
data AccountLink = AccountLink
{ AccountLink -> MessageId
nonce :: Text
, AccountLink -> AccountLinkResult
result :: AccountLinkResult
}
deriving (AccountLink -> AccountLink -> Bool
(AccountLink -> AccountLink -> Bool)
-> (AccountLink -> AccountLink -> Bool) -> Eq AccountLink
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccountLink -> AccountLink -> Bool
$c/= :: AccountLink -> AccountLink -> Bool
== :: AccountLink -> AccountLink -> Bool
$c== :: AccountLink -> AccountLink -> Bool
Eq, Int -> AccountLink -> ShowS
[AccountLink] -> ShowS
AccountLink -> String
(Int -> AccountLink -> ShowS)
-> (AccountLink -> String)
-> ([AccountLink] -> ShowS)
-> Show AccountLink
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccountLink] -> ShowS
$cshowList :: [AccountLink] -> ShowS
show :: AccountLink -> String
$cshow :: AccountLink -> String
showsPrec :: Int -> AccountLink -> ShowS
$cshowsPrec :: Int -> AccountLink -> ShowS
Show, (forall x. AccountLink -> Rep AccountLink x)
-> (forall x. Rep AccountLink x -> AccountLink)
-> Generic AccountLink
forall x. Rep AccountLink x -> AccountLink
forall x. AccountLink -> Rep AccountLink x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AccountLink x -> AccountLink
$cfrom :: forall x. AccountLink -> Rep AccountLink x
Generic)
instance FromJSON AccountLink
data ThingsEvent = Link | Unlink
deriving (Int -> ThingsEvent -> ShowS
[ThingsEvent] -> ShowS
ThingsEvent -> String
(Int -> ThingsEvent -> ShowS)
-> (ThingsEvent -> String)
-> ([ThingsEvent] -> ShowS)
-> Show ThingsEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ThingsEvent] -> ShowS
$cshowList :: [ThingsEvent] -> ShowS
show :: ThingsEvent -> String
$cshow :: ThingsEvent -> String
showsPrec :: Int -> ThingsEvent -> ShowS
$cshowsPrec :: Int -> ThingsEvent -> ShowS
Show, ReadPrec [ThingsEvent]
ReadPrec ThingsEvent
Int -> ReadS ThingsEvent
ReadS [ThingsEvent]
(Int -> ReadS ThingsEvent)
-> ReadS [ThingsEvent]
-> ReadPrec ThingsEvent
-> ReadPrec [ThingsEvent]
-> Read ThingsEvent
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ThingsEvent]
$creadListPrec :: ReadPrec [ThingsEvent]
readPrec :: ReadPrec ThingsEvent
$creadPrec :: ReadPrec ThingsEvent
readList :: ReadS [ThingsEvent]
$creadList :: ReadS [ThingsEvent]
readsPrec :: Int -> ReadS ThingsEvent
$creadsPrec :: Int -> ReadS ThingsEvent
Read, ThingsEvent -> ThingsEvent -> Bool
(ThingsEvent -> ThingsEvent -> Bool)
-> (ThingsEvent -> ThingsEvent -> Bool) -> Eq ThingsEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ThingsEvent -> ThingsEvent -> Bool
$c/= :: ThingsEvent -> ThingsEvent -> Bool
== :: ThingsEvent -> ThingsEvent -> Bool
$c== :: ThingsEvent -> ThingsEvent -> Bool
Eq, Eq ThingsEvent
Eq ThingsEvent
-> (ThingsEvent -> ThingsEvent -> Ordering)
-> (ThingsEvent -> ThingsEvent -> Bool)
-> (ThingsEvent -> ThingsEvent -> Bool)
-> (ThingsEvent -> ThingsEvent -> Bool)
-> (ThingsEvent -> ThingsEvent -> Bool)
-> (ThingsEvent -> ThingsEvent -> ThingsEvent)
-> (ThingsEvent -> ThingsEvent -> ThingsEvent)
-> Ord ThingsEvent
ThingsEvent -> ThingsEvent -> Bool
ThingsEvent -> ThingsEvent -> Ordering
ThingsEvent -> ThingsEvent -> ThingsEvent
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 :: ThingsEvent -> ThingsEvent -> ThingsEvent
$cmin :: ThingsEvent -> ThingsEvent -> ThingsEvent
max :: ThingsEvent -> ThingsEvent -> ThingsEvent
$cmax :: ThingsEvent -> ThingsEvent -> ThingsEvent
>= :: ThingsEvent -> ThingsEvent -> Bool
$c>= :: ThingsEvent -> ThingsEvent -> Bool
> :: ThingsEvent -> ThingsEvent -> Bool
$c> :: ThingsEvent -> ThingsEvent -> Bool
<= :: ThingsEvent -> ThingsEvent -> Bool
$c<= :: ThingsEvent -> ThingsEvent -> Bool
< :: ThingsEvent -> ThingsEvent -> Bool
$c< :: ThingsEvent -> ThingsEvent -> Bool
compare :: ThingsEvent -> ThingsEvent -> Ordering
$ccompare :: ThingsEvent -> ThingsEvent -> Ordering
$cp1Ord :: Eq ThingsEvent
Ord, (forall x. ThingsEvent -> Rep ThingsEvent x)
-> (forall x. Rep ThingsEvent x -> ThingsEvent)
-> Generic ThingsEvent
forall x. Rep ThingsEvent x -> ThingsEvent
forall x. ThingsEvent -> Rep ThingsEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ThingsEvent x -> ThingsEvent
$cfrom :: forall x. ThingsEvent -> Rep ThingsEvent x
Generic)
instance FromJSON ThingsEvent where
parseJSON :: Value -> Parser ThingsEvent
parseJSON = Options -> Value -> Parser ThingsEvent
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser ThingsEvent)
-> Options -> Value -> Parser ThingsEvent
forall a b. (a -> b) -> a -> b
$
Options
defaultOptions { constructorTagModifier :: ShowS
constructorTagModifier = (Char -> Char) -> ShowS
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Char -> Char
toLower
, allNullaryToStringTag :: Bool
allNullaryToStringTag = Bool
True
}
data Things = Things
{ Things -> MessageId
deviceId :: Text
, Things -> ThingsEvent
eventType :: ThingsEvent
}
deriving (Things -> Things -> Bool
(Things -> Things -> Bool)
-> (Things -> Things -> Bool) -> Eq Things
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Things -> Things -> Bool
$c/= :: Things -> Things -> Bool
== :: Things -> Things -> Bool
$c== :: Things -> Things -> Bool
Eq, Int -> Things -> ShowS
[Things] -> ShowS
Things -> String
(Int -> Things -> ShowS)
-> (Things -> String) -> ([Things] -> ShowS) -> Show Things
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Things] -> ShowS
$cshowList :: [Things] -> ShowS
show :: Things -> String
$cshow :: Things -> String
showsPrec :: Int -> Things -> ShowS
$cshowsPrec :: Int -> Things -> ShowS
Show, (forall x. Things -> Rep Things x)
-> (forall x. Rep Things x -> Things) -> Generic Things
forall x. Rep Things x -> Things
forall x. Things -> Rep Things x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Things x -> Things
$cfrom :: forall x. Things -> Rep Things x
Generic)
instance FromJSON Things where
parseJSON :: Value -> Parser Things
parseJSON = String -> (Object -> Parser Things) -> Value -> Parser Things
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Things" ((Object -> Parser Things) -> Value -> Parser Things)
-> (Object -> Parser Things) -> Value -> Parser Things
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
MessageId
deviceId <- Object
o Object -> MessageId -> Parser MessageId
forall a. FromJSON a => Object -> MessageId -> Parser a
.: MessageId
"deviceId"
ThingsEvent
eventType <- Object
o Object -> MessageId -> Parser ThingsEvent
forall a. FromJSON a => Object -> MessageId -> Parser a
.: MessageId
"type"
Things -> Parser Things
forall (m :: * -> *) a. Monad m => a -> m a
return Things :: MessageId -> ThingsEvent -> Things
Things{MessageId
ThingsEvent
eventType :: ThingsEvent
deviceId :: MessageId
$sel:eventType:Things :: ThingsEvent
$sel:deviceId:Things :: MessageId
..}