{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Dialogflow.V2.Fulfillment.Webhook.Request where
import Data.Aeson ( FromJSON
, parseJSON
, ToJSON
, toJSON
, withObject
, (.:)
, (.:!)
, (.=))
import qualified Data.Map as M
import Dialogflow.Util
data Intent =
Intent { intentName :: String
, displayName :: String
} deriving (Eq, Show)
instance FromJSON Intent where
parseJSON = withObject "intent" $ \i -> do
intentName <- i .: "name"
displayName <- i .: "displayName"
return Intent {..}
instance ToJSON Intent where
toJSON Intent{..} =
noNullObjects [ "name" .= intentName
, "displayName" .= displayName ]
data Context =
Context { ctxName :: String
, ctxLifespanCount :: Maybe Int
, ctxParameters :: Maybe (M.Map String String)
} deriving (Eq, Show)
instance FromJSON Context where
parseJSON = withObject "context" $ \c -> do
ctxName <- c .: "name"
ctxLifespanCount <- c .:! "lifespanCount"
ctxParameters <- c .: "parameters"
return Context{..}
instance ToJSON Context where
toJSON Context{..} =
noNullObjects [ "name" .= ctxName
, "lifespanCount" .= ctxLifespanCount
, "parameters" .= ctxParameters ]
data QueryResult =
QueryResult { queryText :: String
, parameters :: M.Map String String
, allRequiredParamsPresent :: Bool
, fulfillmentText :: Maybe String
, outputContexts :: Maybe [Context]
, intent :: Maybe Intent
, intentDetectionConfidence :: Maybe Float
, diagnosticInfo :: Maybe (M.Map String String)
, languageCode :: String
} deriving (Eq, Show)
instance FromJSON QueryResult where
parseJSON = withObject "queryResult" $ \qr -> do
queryText <- qr .: "queryText"
parameters <- qr .: "parameters"
allRequiredParamsPresent <- qr .: "allRequiredParamsPresent"
fulfillmentText <- qr .:! "fulfillmentText"
outputContexts <- qr .:! "outputContexts"
intent <- qr .:! "intent"
intentDetectionConfidence <- qr .:! "intentDetectionConfidence"
diagnosticInfo <- qr .:! "diagnosticInfo"
languageCode <- qr .: "languageCode"
return QueryResult{..}
instance ToJSON QueryResult where
toJSON QueryResult{..} =
noNullObjects [ "queryText" .= queryText
, "parameters" .= parameters
, "allRequiredParamsPresent" .= allRequiredParamsPresent
, "fulfillmentText" .= fulfillmentText
, "outputContexts" .= outputContexts
, "intent" .= intent
, "intentDetectionConfidence" .= intentDetectionConfidence
, "diagnosticInfo" .= diagnosticInfo
, "languageCode" .= languageCode ]
data WebhookRequest =
WebhookRequest { responseId :: String
, session :: String
, queryResult :: QueryResult
} deriving(Eq, Show)
instance FromJSON WebhookRequest where
parseJSON = withObject "webhookRequest" $ \wr -> do
responseId <- wr .: "responseId"
session <- wr .: "session"
queryResult <- wr .: "queryResult"
return WebhookRequest{..}
instance ToJSON WebhookRequest where
toJSON WebhookRequest{..} =
noNullObjects [ "responseId" .= responseId
, "session" .= session
, "queryResult" .= queryResult ]
getContextParameter :: [Context]
-> String
-> String
-> Maybe String
getContextParameter ctxs ctx param =
case filter (\Context{..} -> ctxName == ctx) ctxs of
(x:_) -> M.lookup param =<< ctxParameters x
[] -> Nothing