{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
module Dialogflow.V2.Fulfillment.Message
( CardButton(..)
, BasicCardContent(..)
, BasicCardButton(..)
, Item(..)
, OpenUriAction(..)
, SpeechText(..)
, SimpleResponse(..)
, Suggestion(..)
, SelectItemInfo(..)
, MsgType(..)
, Msg( Text
, Image
, QuickReplies
, Card
, SimpleResponses
, BasicCard
, Suggestions
, LinkOutSuggestion
, ListSelect
, CarouselSelect
)
, Message(..)
) where
import Data.Aeson ( FromJSON
, parseJSON
, ToJSON
, toJSON
, Value(..)
, withObject
, (.:)
, (.:!)
, (.=))
import Data.Foldable (asum)
import qualified Data.HashMap.Strict as HM
import Dialogflow.Util
data CardButton = CardButton
{ cbText :: Maybe String
, cbPostback :: Maybe String
} deriving (Eq, Show)
instance FromJSON CardButton where
parseJSON = withObject "cardButton" $ \cb -> do
cbText <- cb .:! "text"
cbPostback <- cb .:! "postback"
return CardButton{..}
instance ToJSON CardButton where
toJSON CardButton{..} =
noNullObjects [ "text" .= cbText
, "postback" .= cbPostback ]
data BasicCardContent = BasicCardImage (Msg 'MsgImage)
| BasicCardFormattedText String
deriving (Eq, Show)
instance FromJSON BasicCardContent where
parseJSON = withObject "Image or formatted text" $ \bcc ->
asum [ BasicCardImage <$> bcc .: "image"
, BasicCardFormattedText <$> bcc .: "formatted_text" ]
instance ToJSON BasicCardContent where
toJSON = \case
BasicCardImage image -> noNullObjects [ "image" .= image ]
BasicCardFormattedText formattedText -> noNullObjects [ "formatted_text" .= formattedText ]
data SpeechText = TextToSpeech String
| SSML String
deriving (Eq, Show)
instance FromJSON SpeechText where
parseJSON = withObject "textToSpeech or SSML" $ \st ->
asum [ TextToSpeech <$> st .: "textToSpeech"
, SSML <$> st .: "ssml" ]
instance ToJSON SpeechText where
toJSON = \case
TextToSpeech textToSpeech -> noNullObjects ["textToSpeech" .= textToSpeech]
SSML ssml -> noNullObjects ["ssml" .= ssml]
data SimpleResponse = SimpleResponse
{ simpleResponseText :: SpeechText
, displayText :: Maybe String
} deriving (Eq, Show)
instance FromJSON SimpleResponse where
parseJSON = withObject "simpleResponse" $ \sr -> do
simpleResponseText <- parseJSON (Object sr)
displayText <- sr .:! "displayText"
return SimpleResponse{..}
instance ToJSON SimpleResponse where
toJSON SimpleResponse{..} = Object $
toObject simpleResponseText <> HM.fromList ["displayText" .= displayText ]
newtype OpenUriAction = OpenUriAction
{ unOpenUriAction :: String
} deriving (Eq, Show)
instance ToJSON OpenUriAction where
toJSON oua = noNullObjects [ "uri" .= unOpenUriAction oua ]
instance FromJSON OpenUriAction where
parseJSON = withObject "openUriAction" $ \oua -> do
uri <- oua .: "uri"
return $ OpenUriAction uri
data BasicCardButton = BasicCardButton
{ bcbTitle :: String
, bcbOpenUriAction :: OpenUriAction
} deriving (Eq, Show)
instance FromJSON BasicCardButton where
parseJSON = withObject "basicCardButton" $ \bcb -> do
bcbTitle <- bcb .: "title"
bcbOpenUriAction <- bcb .: "open_uri_action"
return BasicCardButton{..}
instance ToJSON BasicCardButton where
toJSON BasicCardButton{..} =
noNullObjects [ "title" .= bcbTitle
, "open_uri_action" .= bcbOpenUriAction ]
newtype Suggestion = Suggestion
{ unSuggestionTitle :: String
} deriving (Eq, Show)
instance FromJSON Suggestion where
parseJSON = withObject "suggestion" $ \s -> do
unSuggestionTitle <- s .: "title"
return $ Suggestion unSuggestionTitle
instance ToJSON Suggestion where
toJSON s =
noNullObjects [ "title" .= unSuggestionTitle s ]
data SelectItemInfo = SelectItemInfo
{ siiKey :: String
, siiSynonyms :: Maybe [String]
} deriving (Eq, Show)
instance FromJSON SelectItemInfo where
parseJSON = withObject "selectedItemInfo" $ \sii -> do
siiKey <- sii .: "key"
siiSynonyms <- sii .: "synonyms"
return SelectItemInfo{..}
instance ToJSON SelectItemInfo where
toJSON SelectItemInfo{..} =
noNullObjects [ "key" .= siiKey
, "synonyms" .= siiSynonyms ]
data MsgType = MsgText
| MsgImage
| MsgQuickReplies
| MsgCard
| MsgSimpleResponses
| MsgBasicCard
| MsgSuggestions
| MsgLinkOutSuggestion
| MsgListSelect
| MsgCarouselSelect
data Msg t where
Text
:: Maybe [String]
-> Msg 'MsgText
Image
:: String
-> Maybe String
-> Msg 'MsgImage
QuickReplies
:: Maybe String
-> [String]
-> Msg 'MsgQuickReplies
Card
:: Maybe String
-> Maybe String
-> Maybe String
-> Maybe [CardButton]
-> Msg 'MsgCard
SimpleResponses
:: [SimpleResponse]
-> Msg 'MsgSimpleResponses
BasicCard
:: Maybe String
-> Maybe String
-> BasicCardContent
-> Maybe [BasicCardButton]
-> Msg 'MsgBasicCard
Suggestions
:: [Suggestion]
-> Msg 'MsgSuggestions
LinkOutSuggestion
:: String
-> String
-> Msg 'MsgLinkOutSuggestion
ListSelect
:: Maybe String
-> [Item]
-> Msg 'MsgListSelect
CarouselSelect
:: [Item]
-> Msg 'MsgCarouselSelect
deriving instance Show (Msg t)
deriving instance Eq (Msg t)
instance FromJSON (Msg 'MsgImage) where
parseJSON = withObject "image" $ \i -> do
uri <- i .: "image_uri"
allyText <- i .:! "accessibility_text"
return (Image uri allyText)
instance FromJSON (Msg 'MsgText) where
parseJSON = withObject "text" $ \t -> do
text <- t .: "text"
return $ Text text
instance FromJSON (Msg 'MsgQuickReplies) where
parseJSON = withObject "quickReplies" $ \qr -> do
title <- qr .:! "title"
replies <- qr .: "quick_replies"
return $ QuickReplies title replies
instance FromJSON (Msg 'MsgCard) where
parseJSON = withObject "card" $ \card -> do
c <- card .: "card"
mbTitle <- c .:! "title"
mbSubtitle <- c .:! "subtitle"
mbUri <- c .:! "image_uri"
cardButtons <- c .:! "buttons"
return $ Card mbTitle mbSubtitle mbUri cardButtons
instance FromJSON (Msg 'MsgSimpleResponses) where
parseJSON = withObject "simpleResponses" $ \sr -> do
srs <- sr .: "simpleResponses"
responses <- srs .: "simpleResponses"
return $ SimpleResponses responses
instance FromJSON (Msg 'MsgBasicCard) where
parseJSON = withObject "basicCard" $ \bc -> do
mbTitle <- bc .:! "title"
mbSubtitle <- bc .:! "subtitle"
content <- parseJSON (Object bc)
buttons <- bc .:! "buttons"
return $ BasicCard mbTitle mbSubtitle content buttons
instance FromJSON (Msg 'MsgSuggestions) where
parseJSON = withObject "suggestions" $ \sgs -> do
suggestions <- sgs .: "suggestions"
return $ Suggestions suggestions
instance FromJSON (Msg 'MsgLinkOutSuggestion) where
parseJSON = withObject "linkOutSuggestion" $ \los -> do
uri <- los .: "uri"
destinationName <- los .: "destination_name"
return $ LinkOutSuggestion destinationName uri
instance FromJSON (Msg 'MsgListSelect) where
parseJSON = withObject "listSelect" $ \ls -> do
title <- ls .:! "title"
items <- ls .: "items"
return $ ListSelect title items
instance FromJSON (Msg 'MsgCarouselSelect) where
parseJSON = withObject "carouselSelect" $ \cs -> do
items <- cs .: "items"
return $ CarouselSelect items
instance ToJSON (Msg t) where
toJSON (Text mbText) = noNullObjects [ "text" .= mbText ]
toJSON (Image uri accesibilityText) =
noNullObjects [ "image_uri" .= uri
, "accessibility_text" .= accesibilityText ]
toJSON (QuickReplies mbTitle quickReplies) =
noNullObjects [ "title" .= mbTitle
, "quick_replies" .= quickReplies ]
toJSON (Card title subtitle imageUri buttons) =
noNullObjects [ "card" .= noNullObjects ["title" .= title
, "subtitle" .= subtitle
, "image_uri" .= imageUri
, "buttons" .= buttons ] ]
toJSON (SimpleResponses simpleResponses) =
noNullObjects [ "simpleResponses" .= noNullObjects ["simpleResponses" .= simpleResponses ] ]
toJSON (BasicCard mbTitle mbSubtitle content buttons) =
Object $ HM.fromList [ "title" .= mbTitle
, "subtitle" .= mbSubtitle
, "buttons" .= buttons ] <> toObject content
toJSON (Suggestions xs) = noNullObjects [ "suggestions" .= xs ]
toJSON (LinkOutSuggestion name uri) =
noNullObjects [ "destination_name" .= name, "uri" .= uri ]
toJSON (ListSelect mbTitle items) =
noNullObjects [ "title" .= mbTitle
, "items" .= items ]
toJSON (CarouselSelect items) = noNullObjects [ "items" .= items ]
data Message where
Message :: (Show (Msg t)) => Msg t -> Message
instance Show Message where
show (Message o) = show o
instance ToJSON Message where
toJSON (Message bc@BasicCard{}) = noNullObjects [ "basicCard" .= toJSON bc ]
toJSON (Message o) = toJSON o
instance Eq Message where
(==) (Message x@Text{}) (Message y@Text{}) = x == y
(==) (Message x@Image{}) (Message y@Image{}) = x == y
(==) (Message x@QuickReplies{}) (Message y@QuickReplies{}) = x == y
(==) (Message x@Card{}) (Message y@Card{}) = x == y
(==) (Message x@SimpleResponses{}) (Message y@SimpleResponses{}) = x == y
(==) (Message x@BasicCard{}) (Message y@BasicCard{}) = x == y
(==) (Message x@Suggestions{}) (Message y@Suggestions{}) = x == y
(==) (Message x@LinkOutSuggestion{}) (Message y@LinkOutSuggestion{}) = x == y
(==) (Message x@ListSelect{}) (Message y@ListSelect{}) = x == y
(==) (Message x@CarouselSelect{}) (Message y@CarouselSelect{}) = x == y
(==) _ _ = False
data Item = Item
{ iInfo :: SelectItemInfo
, iTitle :: String
, iDescription :: Maybe String
, iImage :: Msg 'MsgImage
} deriving (Eq, Show)
instance FromJSON Item where
parseJSON = withObject "Item" $ \i -> do
iInfo <- i .: "info"
iTitle <- i .: "title"
iDescription <- i .:! "description"
iImage <- i .: "image"
return Item{..}
instance ToJSON Item where
toJSON Item{..} =
noNullObjects [ "info" .= iInfo
, "title" .= iTitle
, "description" .= iDescription
, "image" .= iImage ]