{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
module Dialogflow.V2.Fulfillment.Payload.Google where
import Data.Aeson ( parseJSON
, toJSON
, withObject
, FromJSON
, ToJSON
, Value(..)
, (.=)
, (.:)
, (.:!) )
import Data.Foldable (asum)
import qualified Data.HashMap.Strict as HM
import Dialogflow.Util
import qualified Dialogflow.V2.Fulfillment.Message as M
newtype GooglePayload =
GooglePayload { unGooglePayload :: Response } deriving (Eq, Show)
instance ToJSON GooglePayload where
toJSON gp =
noNullObjects [ "google" .= unGooglePayload gp]
data Image =
Image { iUrl :: String
, iAccessibilityText :: String
, iHeight :: Maybe Int
, iWidth :: Maybe Int
} deriving (Eq, Show)
instance FromJSON Image where
parseJSON = withObject "image" $ \i -> do
iUrl <- i .: "url"
iAccessibilityText <- i .: "accessibilityText"
iHeight <- i .:! "height"
iWidth <- i .:! "width"
return Image{..}
instance ToJSON Image where
toJSON Image{..} =
noNullObjects [ "url" .= iUrl
, "accessibilityText" .= iAccessibilityText
, "height" .= iHeight
, "width" .= iWidth ]
data BasicCardContent = BasicCardImage Image
| BasicCardFormattedText String
deriving (Eq, Show)
instance FromJSON BasicCardContent where
parseJSON = withObject "Image or formatted text" $ \bcc ->
asum [ BasicCardImage <$> bcc .: "image"
, BasicCardFormattedText <$> bcc .: "formattedText" ]
instance ToJSON BasicCardContent where
toJSON = \case
BasicCardImage image -> noNullObjects [ "image" .= image ]
BasicCardFormattedText formattedText -> noNullObjects [ "formattedText" .= formattedText ]
data ImageDisplayOption = DEFAULT
| WHITE
| CROPPED
deriving (Eq, Read, Show)
instance FromJSON ImageDisplayOption where
parseJSON = withObject "imageDisplayOption" $ \x -> do
ido <- x .: "imageDisplayOptions"
return $ read ido
instance ToJSON ImageDisplayOption where
toJSON x = noNullObjects [ "imageDisplayOptions" .= show x ]
data MediaType = MEDIA_TYPE_UNSPECIFIED
| AUDIO
deriving (Eq, Read, Show)
instance FromJSON MediaType where
parseJSON = withObject "mediaType" $ \x -> do
mt <- x .: "mediaType"
return $ read mt
instance ToJSON MediaType where
toJSON x = noNullObjects [ "mediaType" .= show x ]
data MediaObject =
MediaObject { moName :: String
, moDescription :: String
, moContentUrl :: String
, moLargeImage :: Image
, moIcon :: Image
} deriving (Eq, Show)
instance FromJSON MediaObject where
parseJSON = withObject "MediaObject" $ \mo -> do
moName <- mo .: "name"
moDescription <- mo .: "description"
moContentUrl <- mo .: "contentUrl"
moLargeImage <- mo .: "largeImage"
moIcon <- mo .: "icon"
return MediaObject{..}
instance ToJSON MediaObject where
toJSON MediaObject{..} =
noNullObjects [ "name" .= moName
, "description" .= moDescription
, "contentUrl" .= moContentUrl
, "largeImage" .= moLargeImage
, "icon" .= moIcon ]
data RichMessageType = RMTSimpleResponse
| RMTBasicCard
| RMTMediaResponse
data Res t where
SimpleResponse :: M.SimpleResponse -> Res 'RMTSimpleResponse
BasicCard :: Maybe String
-> Maybe String
-> BasicCardContent
-> [M.BasicCardButton]
-> ImageDisplayOption
-> Res 'RMTBasicCard
MediaResponse :: MediaType
-> [MediaObject]
-> Res 'RMTMediaResponse
deriving instance Eq (Res t)
deriving instance Show (Res t)
instance FromJSON (Res 'RMTSimpleResponse) where
parseJSON = withObject "simpleResponse" $ \sr -> do
simpleResponse <- sr .: "simpleResponse"
return $ SimpleResponse simpleResponse
instance FromJSON (Res 'RMTBasicCard) where
parseJSON = withObject "basicCard" $ \basicCard -> do
bc <- basicCard .: "basicCard"
mbTitle <- bc .:! "title"
mbSubtitle <- bc .: "subtitle"
content <- parseJSON (Object bc)
buttons <- bc .: "buttons"
imageDisplayOption <- parseJSON (Object bc)
return $ BasicCard mbTitle mbSubtitle content buttons imageDisplayOption
instance FromJSON (Res 'RMTMediaResponse) where
parseJSON = withObject "mediaResponse" $ \mediaResponse -> do
mr <- mediaResponse .: "mediaResponse"
mediaType <- parseJSON (Object mr)
mediaObjects <- mr .: "mediaObjects"
return $ MediaResponse mediaType mediaObjects
instance ToJSON (Res t) where
toJSON (SimpleResponse s) = noNullObjects [ "simpleResponse" .= s ]
toJSON (BasicCard t s c b d) =
noNullObjects [ "basicCard" .= obj ]
where
obj = Object $ HM.fromList [ "title" .= t
, "subtitle" .= s
, "buttons" .= b ] <> toObject c <> toObject d
toJSON (MediaResponse mediaType mos) =
noNullObjects [ "mediaResponse" .= obj ]
where
obj = Object $ HM.fromList [ "mediaObjects" .= mos ] <> toObject mediaType
data Item where
Item :: (Show (Res t)) => Res t -> Item
instance Eq Item where
(==) (Item x@BasicCard{}) (Item y@BasicCard{}) = x == y
(==) (Item x@SimpleResponse{}) (Item y@SimpleResponse{}) = x == y
(==) (Item x@MediaResponse{}) (Item y@MediaResponse{}) = x == y
(==) _ _ = False
instance ToJSON Item where
toJSON (Item x) = toJSON x
deriving instance Show Item
data RichResponse = RichResponse
{ items :: [Item]
, suggestions :: [Suggestion]
, linkOutSuggestion :: Maybe LinkOutSuggestion
} deriving (Eq, Show)
instance ToJSON RichResponse where
toJSON RichResponse{..} =
noNullObjects [ "items" .= items
, "suggestions" .= suggestions
, "linkOutSuggestion" .= linkOutSuggestion ]
data Response =
Response { expectUserResponse :: Bool
, userStorage :: Maybe String
, richResponse :: RichResponse
} deriving (Eq, Show)
instance ToJSON Response where
toJSON Response{..} =
noNullObjects [ "expectUserResponse" .= expectUserResponse
, "userStorage" .= userStorage
, "richResponse" .= richResponse ]
data UrlTypeHint = URL_TYPE_HINT_UNSPECIFIED
| AMP_CONTENT
deriving (Eq, Read, Show)
instance FromJSON UrlTypeHint where
parseJSON = withObject "urlTypeHint" $ \x -> do
uth <- x .: "urlTypeHint"
return $ read uth
instance ToJSON UrlTypeHint where
toJSON x = noNullObjects [ "urlTypeHint" .= show x ]
data VersionFilter = VersionFilter
{ minVersion :: Int
, maxVersion :: Int
} deriving (Eq, Read, Show)
instance FromJSON VersionFilter where
parseJSON = withObject "versionFilter" $ \vf -> do
minVersion <- vf .: "minVersion"
maxVersion <- vf .: "maxVersion"
return VersionFilter{..}
instance ToJSON VersionFilter where
toJSON VersionFilter{..} =
noNullObjects [ "minVersion" .= minVersion
, "maxVersion" .= maxVersion ]
data AndroidApp = AndroidApp
{ aaPackageName :: String
, aaVersions :: [VersionFilter]
} deriving (Eq, Read, Show)
instance FromJSON AndroidApp where
parseJSON = withObject "androidApp" $ \aa -> do
aaPackageName <- aa .: "packageName"
aaVersions <- aa .: "versions"
return AndroidApp{..}
instance ToJSON AndroidApp where
toJSON AndroidApp{..} =
noNullObjects [ "packageName" .= aaPackageName
, "versions" .= aaVersions ]
data OpenUrlAction =
OpenUrlAction { ouaUrl :: String
, ouaAndroidApp :: AndroidApp
, ouaUrlTypeHint :: UrlTypeHint
} deriving (Eq, Read, Show)
instance FromJSON OpenUrlAction where
parseJSON = withObject "openUrlAction" $ \oua -> do
ouaUrl <- oua .: "url"
ouaAndroidApp <- oua .: "androidApp"
ouaUrlTypeHint <- parseJSON (Object oua)
return OpenUrlAction{..}
instance ToJSON OpenUrlAction where
toJSON OpenUrlAction{..} =
Object $ HM.fromList [ "url" .= ouaUrl
, "androidApp" .= ouaAndroidApp
] <> toObject ouaUrlTypeHint
data LinkOutSuggestion = LinkOutSuggestion
{ losDestinationName :: String
, losUrl :: String
, losOpenUrlAction :: OpenUrlAction
} deriving (Eq, Show)
instance FromJSON LinkOutSuggestion where
parseJSON = withObject "linkOutSuggestion" $ \los -> do
losDestinationName <- los .: "destinationName"
losUrl <- los .: "url"
losOpenUrlAction <- los .: "openUrlAction"
return LinkOutSuggestion{..}
instance ToJSON LinkOutSuggestion where
toJSON LinkOutSuggestion{..} =
noNullObjects [ "destinationName" .= losDestinationName
, "url" .= losUrl
, "openUrlAction" .= losOpenUrlAction ]
newtype Suggestion = Suggestion { unSuggestion :: String }
deriving (Eq, Show)
instance FromJSON Suggestion where
parseJSON = withObject "suggestion" $ \s -> do
suggestion <- s .: "title"
return $ Suggestion suggestion
instance ToJSON Suggestion where
toJSON s = noNullObjects [ "title" .= unSuggestion s ]