summaryrefslogtreecommitdiff
path: root/Omni/Agent/Tools/Feedback.hs
blob: 1ec684c69f8e43f193041eaef89358369049b039 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE NoImplicitPrelude #-}

-- | Feedback query tool for PodcastItLater user research.
--
-- Allows the agent to query collected feedback from the PIL database.
-- Feedback is submitted via /feedback on the PIL web app.
--
-- : out omni-agent-tools-feedback
-- : dep aeson
-- : dep http-conduit
module Omni.Agent.Tools.Feedback
  ( -- * Tools
    feedbackListTool,
    allFeedbackTools,

    -- * Types
    FeedbackEntry (..),
    ListFeedbackArgs (..),

    -- * Testing
    main,
    test,
  )
where

import Alpha
import Data.Aeson ((.!=), (.:), (.:?), (.=))
import qualified Data.Aeson as Aeson
import qualified Data.Text as Text
import qualified Network.HTTP.Simple as HTTP
import qualified Omni.Agent.Engine as Engine
import qualified Omni.Test as Test
import System.Environment (lookupEnv)

main :: IO ()
main = Test.run test

test :: Test.Tree
test =
  Test.group
    "Omni.Agent.Tools.Feedback"
    [ Test.unit "feedbackListTool has correct name" <| do
        Engine.toolName feedbackListTool Test.@=? "feedback_list",
      Test.unit "allFeedbackTools has 1 tool" <| do
        length allFeedbackTools Test.@=? 1,
      Test.unit "ListFeedbackArgs parses correctly" <| do
        let json = Aeson.object ["limit" .= (10 :: Int)]
        case Aeson.fromJSON json of
          Aeson.Success (args :: ListFeedbackArgs) -> lfaLimit args Test.@=? 10
          Aeson.Error e -> Test.assertFailure e,
      Test.unit "ListFeedbackArgs parses with since" <| do
        let json =
              Aeson.object
                [ "limit" .= (20 :: Int),
                  "since" .= ("2024-01-01" :: Text)
                ]
        case Aeson.fromJSON json of
          Aeson.Success (args :: ListFeedbackArgs) -> do
            lfaLimit args Test.@=? 20
            lfaSince args Test.@=? Just "2024-01-01"
          Aeson.Error e -> Test.assertFailure e,
      Test.unit "FeedbackEntry JSON roundtrip" <| do
        let entry =
              FeedbackEntry
                { feId = "abc123",
                  feEmail = Just "test@example.com",
                  feSource = Just "outreach",
                  feCampaignId = Nothing,
                  feRating = Just 4,
                  feFeedbackText = Just "Great product!",
                  feUseCase = Just "Commute listening",
                  feCreatedAt = "2024-01-15T10:00:00Z"
                }
        case Aeson.decode (Aeson.encode entry) of
          Nothing -> Test.assertFailure "Failed to decode FeedbackEntry"
          Just decoded -> do
            feId decoded Test.@=? "abc123"
            feEmail decoded Test.@=? Just "test@example.com"
            feRating decoded Test.@=? Just 4
    ]

data FeedbackEntry = FeedbackEntry
  { feId :: Text,
    feEmail :: Maybe Text,
    feSource :: Maybe Text,
    feCampaignId :: Maybe Text,
    feRating :: Maybe Int,
    feFeedbackText :: Maybe Text,
    feUseCase :: Maybe Text,
    feCreatedAt :: Text
  }
  deriving (Show, Eq, Generic)

instance Aeson.ToJSON FeedbackEntry where
  toJSON e =
    Aeson.object
      [ "id" .= feId e,
        "email" .= feEmail e,
        "source" .= feSource e,
        "campaign_id" .= feCampaignId e,
        "rating" .= feRating e,
        "feedback_text" .= feFeedbackText e,
        "use_case" .= feUseCase e,
        "created_at" .= feCreatedAt e
      ]

instance Aeson.FromJSON FeedbackEntry where
  parseJSON =
    Aeson.withObject "FeedbackEntry" <| \v ->
      (FeedbackEntry </ (v .: "id"))
        <*> (v .:? "email")
        <*> (v .:? "source")
        <*> (v .:? "campaign_id")
        <*> (v .:? "rating")
        <*> (v .:? "feedback_text")
        <*> (v .:? "use_case")
        <*> (v .: "created_at")

data ListFeedbackArgs = ListFeedbackArgs
  { lfaLimit :: Int,
    lfaSince :: Maybe Text
  }
  deriving (Show, Eq, Generic)

instance Aeson.FromJSON ListFeedbackArgs where
  parseJSON =
    Aeson.withObject "ListFeedbackArgs" <| \v ->
      (ListFeedbackArgs </ (v .:? "limit" .!= 20))
        <*> (v .:? "since")

allFeedbackTools :: [Engine.Tool]
allFeedbackTools = [feedbackListTool]

feedbackListTool :: Engine.Tool
feedbackListTool =
  Engine.Tool
    { Engine.toolName = "feedback_list",
      Engine.toolDescription =
        "List feedback entries from PodcastItLater users. "
          <> "Use to review user research data and understand what potential "
          <> "customers want from the product.",
      Engine.toolJsonSchema =
        Aeson.object
          [ "type" .= ("object" :: Text),
            "properties"
              .= Aeson.object
                [ "limit"
                    .= Aeson.object
                      [ "type" .= ("integer" :: Text),
                        "description" .= ("Max entries to return (default: 20)" :: Text)
                      ],
                  "since"
                    .= Aeson.object
                      [ "type" .= ("string" :: Text),
                        "description" .= ("ISO date to filter by (entries after this date)" :: Text)
                      ]
                ],
            "required" .= ([] :: [Text])
          ],
      Engine.toolExecute = executeFeedbackList
    }

executeFeedbackList :: Aeson.Value -> IO Aeson.Value
executeFeedbackList v =
  case Aeson.fromJSON v of
    Aeson.Error e -> pure (Aeson.object ["error" .= Text.pack e])
    Aeson.Success (args :: ListFeedbackArgs) -> do
      mBaseUrl <- lookupEnv "PIL_BASE_URL"
      let baseUrl = maybe "http://localhost:8000" Text.pack mBaseUrl
          limit = min 100 (max 1 (lfaLimit args))
          sinceParam = case lfaSince args of
            Nothing -> ""
            Just since -> "&since=" <> since
          url = baseUrl <> "/api/feedback?limit=" <> tshow limit <> sinceParam
      result <- fetchFeedback url
      case result of
        Left err -> pure (Aeson.object ["error" .= err])
        Right entries ->
          pure
            ( Aeson.object
                [ "success" .= True,
                  "count" .= length entries,
                  "entries" .= entries
                ]
            )

fetchFeedback :: Text -> IO (Either Text [FeedbackEntry])
fetchFeedback url = do
  result <-
    try <| do
      req <- HTTP.parseRequest (Text.unpack url)
      resp <- HTTP.httpLBS req
      pure (HTTP.getResponseStatusCode resp, HTTP.getResponseBody resp)
  case result of
    Left (e :: SomeException) -> pure (Left ("Request failed: " <> tshow e))
    Right (status, body) ->
      if status /= 200
        then pure (Left ("HTTP " <> tshow status))
        else case Aeson.decode body of
          Nothing -> pure (Left "Failed to parse response")
          Just entries -> pure (Right entries)