summaryrefslogtreecommitdiff
path: root/Omni
diff options
context:
space:
mode:
Diffstat (limited to 'Omni')
-rw-r--r--Omni/Agent/Engine.hs4
-rw-r--r--Omni/Agent/Worker.hs38
-rwxr-xr-xOmni/Jr.hs69
-rw-r--r--Omni/Jr/Web.hs184
-rw-r--r--Omni/Jr/Web/Style.hs160
5 files changed, 432 insertions, 23 deletions
diff --git a/Omni/Agent/Engine.hs b/Omni/Agent/Engine.hs
index 1f5dcc8..01a04e9 100644
--- a/Omni/Agent/Engine.hs
+++ b/Omni/Agent/Engine.hs
@@ -521,8 +521,8 @@ runAgent engineCfg agentCfg userPrompt = do
engineOnCost engineCfg tokens cost
let newTokens = totalTokens + tokens
let assistantText = msgContent msg
- unless (Text.null assistantText) <|
- engineOnAssistant engineCfg assistantText
+ unless (Text.null assistantText)
+ <| engineOnAssistant engineCfg assistantText
case msgToolCalls msg of
Nothing -> do
engineOnActivity engineCfg "Agent completed"
diff --git a/Omni/Agent/Worker.hs b/Omni/Agent/Worker.hs
index 1c69b15..79cf3c8 100644
--- a/Omni/Agent/Worker.hs
+++ b/Omni/Agent/Worker.hs
@@ -93,7 +93,7 @@ processTask worker task = do
activityId <- TaskCore.logActivityWithMetrics tid TaskCore.Running Nothing Nothing (Just startTime) Nothing Nothing Nothing
say "[worker] Starting engine..."
- (exitCode, output, costCents) <- runWithEngine repo task
+ (exitCode, output, costCents) <- runWithEngine worker repo task
endTime <- Data.Time.getCurrentTime
say ("[worker] Agent exited with: " <> tshow exitCode)
@@ -199,8 +199,8 @@ tryCommit repo msg = do
-- | Run task using native Engine
-- Returns (ExitCode, output text, cost in cents)
-runWithEngine :: FilePath -> TaskCore.Task -> IO (Exit.ExitCode, Text, Int)
-runWithEngine repo task = do
+runWithEngine :: Core.Worker -> FilePath -> TaskCore.Task -> IO (Exit.ExitCode, Text, Int)
+runWithEngine worker repo task = do
-- Read API key from environment
maybeApiKey <- Env.lookupEnv "OPENROUTER_API_KEY"
case maybeApiKey of
@@ -254,7 +254,9 @@ runWithEngine repo task = do
-- Build Engine config with callbacks
totalCostRef <- newIORef (0 :: Int)
- let engineCfg =
+ let quiet = Core.workerQuiet worker
+ sayLog msg = if quiet then putText msg else AgentLog.log msg
+ engineCfg =
Engine.EngineConfig
{ Engine.engineLLM =
Engine.defaultLLM
@@ -262,26 +264,26 @@ runWithEngine repo task = do
},
Engine.engineOnCost = \tokens cost -> do
modifyIORef' totalCostRef (+ cost)
- AgentLog.log <| "Cost: " <> tshow cost <> " cents (" <> tshow tokens <> " tokens)"
- logEvent "cost" (Aeson.object [("tokens", Aeson.toJSON tokens), ("cents", Aeson.toJSON cost)]),
+ sayLog <| "Cost: " <> tshow cost <> " cents (" <> tshow tokens <> " tokens)"
+ logEvent "Cost" (Aeson.object [("tokens", Aeson.toJSON tokens), ("cents", Aeson.toJSON cost)]),
Engine.engineOnActivity = \activity -> do
- AgentLog.log <| "[engine] " <> activity,
+ sayLog <| "[engine] " <> activity,
Engine.engineOnToolCall = \toolName args -> do
- AgentLog.log <| "[tool] " <> toolName
- logEvent "tool_call" (Aeson.object [("tool", Aeson.toJSON toolName), ("args", Aeson.toJSON args)]),
+ sayLog <| "[tool] " <> toolName
+ logEvent "ToolCall" (Aeson.String (toolName <> ": " <> args)),
Engine.engineOnAssistant = \msg -> do
- AgentLog.log <| "[assistant] " <> Text.take 200 msg
- logEvent "assistant" (Aeson.String msg),
+ sayLog <| "[assistant] " <> Text.take 200 msg
+ logEvent "Assistant" (Aeson.String msg),
Engine.engineOnToolResult = \toolName success output -> do
let statusStr = if success then "ok" else "failed"
- AgentLog.log <| "[result] " <> toolName <> " (" <> statusStr <> "): " <> Text.take 100 output
- logEvent "tool_result" (Aeson.object [("tool", Aeson.toJSON toolName), ("success", Aeson.toJSON success), ("output", Aeson.toJSON output)]),
+ sayLog <| "[result] " <> toolName <> " (" <> statusStr <> "): " <> Text.take 100 output
+ logEvent "ToolResult" (Aeson.String output),
Engine.engineOnComplete = do
- AgentLog.log "[engine] Complete"
- logEvent "complete" Aeson.Null,
+ sayLog "[engine] Complete"
+ logEvent "Complete" Aeson.Null,
Engine.engineOnError = \err -> do
- AgentLog.log <| "[error] " <> err
- logEvent "error" (Aeson.String err)
+ sayLog <| "[error] " <> err
+ logEvent "Error" (Aeson.String err)
}
-- Build Agent config
@@ -290,7 +292,7 @@ runWithEngine repo task = do
{ Engine.agentModel = model,
Engine.agentTools = Tools.allTools,
Engine.agentSystemPrompt = systemPrompt,
- Engine.agentMaxIterations = 20
+ Engine.agentMaxIterations = 100
}
-- Run the agent
diff --git a/Omni/Jr.hs b/Omni/Jr.hs
index 0690970..f45ed2f 100755
--- a/Omni/Jr.hs
+++ b/Omni/Jr.hs
@@ -421,6 +421,7 @@ autoReview tid task commitSha = do
TaskCore.clearRetryContext tid
TaskCore.updateTaskStatus tid TaskCore.Done []
putText ("[review] Task " <> tid <> " -> Done")
+ extractFacts tid commitSha
checkEpicCompletion task
Exit.ExitFailure code -> do
putText ("[review] ✗ Tests failed (exit " <> tshow code <> ")")
@@ -500,6 +501,7 @@ interactiveReview tid task commitSha = do
TaskCore.clearRetryContext tid
TaskCore.updateTaskStatus tid TaskCore.Done []
putText ("Task " <> tid <> " marked as Done.")
+ extractFacts tid commitSha
checkEpicCompletion task
| "r" `Text.isPrefixOf` c -> do
putText "Enter rejection reason: "
@@ -579,6 +581,73 @@ extractConflictFile line =
| not (Text.null rest) -> Just (Text.strip (Text.drop 3 rest))
_ -> Nothing
+-- | Extract facts from completed task
+extractFacts :: Text -> String -> IO ()
+extractFacts tid commitSha = do
+ -- Get the diff for this commit
+ (_, diffOut, _) <- Process.readProcessWithExitCode "git" ["show", "--stat", commitSha] ""
+
+ -- Get task context
+ tasks <- TaskCore.loadTasks
+ case TaskCore.findTask tid tasks of
+ Nothing -> pure ()
+ Just task -> do
+ let prompt = buildFactExtractionPrompt task diffOut
+ -- Call llm CLI
+ (code, llmOut, _) <- Process.readProcessWithExitCode "llm" ["-s", Text.unpack prompt] ""
+ case code of
+ Exit.ExitSuccess -> parseFacts tid llmOut
+ _ -> putText "[facts] Failed to extract facts"
+
+-- | Build prompt for LLM to extract facts from completed task
+buildFactExtractionPrompt :: TaskCore.Task -> String -> Text
+buildFactExtractionPrompt task diffSummary =
+ Text.unlines
+ [ "You just completed the following task:",
+ "",
+ "Task: " <> TaskCore.taskId task,
+ "Title: " <> TaskCore.taskTitle task,
+ "Description: " <> TaskCore.taskDescription task,
+ "",
+ "Diff summary:",
+ Text.pack diffSummary,
+ "",
+ "List any facts you learned about this codebase that would be useful for future tasks.",
+ "Each fact should be on its own line, starting with 'FACT: '.",
+ "Include the relevant file paths in brackets after each fact.",
+ "Example: FACT: The Alpha module re-exports common Prelude functions [Alpha.hs]",
+ "If you didn't learn anything notable, respond with 'NO_FACTS'."
+ ]
+
+-- | Parse facts from LLM output and add them to the knowledge base
+parseFacts :: Text -> String -> IO ()
+parseFacts tid output = do
+ let outputLines = Text.lines (Text.pack output)
+ factLines = filter (Text.isPrefixOf "FACT: ") outputLines
+ traverse_ (addFactFromLine tid) factLines
+
+-- | Parse a single fact line and add it to the knowledge base
+addFactFromLine :: Text -> Text -> IO ()
+addFactFromLine tid line = do
+ let content = Text.drop 6 line -- Remove "FACT: "
+ (factText, filesRaw) = Text.breakOn " [" content
+ files = parseFiles filesRaw
+ _ <- Fact.createFact "Omni" factText files (Just tid) 0.7 -- Lower initial confidence
+ putText ("[facts] Added: " <> factText)
+
+-- | Parse file list from brackets [file1, file2, ...]
+parseFiles :: Text -> [Text]
+parseFiles raw
+ | Text.null raw = []
+ | not ("[" `Text.isInfixOf` raw) = []
+ | otherwise =
+ let stripped = Text.strip (Text.dropWhile (/= '[') raw)
+ inner = Text.dropEnd 1 (Text.drop 1 stripped) -- Remove [ and ]
+ trimmed = Text.strip inner
+ in if Text.null trimmed
+ then []
+ else map Text.strip (Text.splitOn "," inner)
+
-- | Check if all children of an epic are Done, and if so, transition epic to Review
checkEpicCompletion :: TaskCore.Task -> IO ()
checkEpicCompletion task =
diff --git a/Omni/Jr/Web.hs b/Omni/Jr/Web.hs
index fe1711b..86647d4 100644
--- a/Omni/Jr/Web.hs
+++ b/Omni/Jr/Web.hs
@@ -241,6 +241,7 @@ type API =
:> QueryParam "sort" Text
:> Get '[Lucid.HTML] TaskListPartial
:<|> "partials" :> "task" :> Capture "id" Text :> "metrics" :> Get '[Lucid.HTML] TaskMetricsPartial
+ :<|> "partials" :> "task" :> Capture "id" Text :> "events" :> QueryParam "since" Int :> Get '[Lucid.HTML] AgentEventsPartial
data CSS
@@ -261,7 +262,7 @@ data InterventionPage = InterventionPage TaskCore.HumanActionItems SortOrder UTC
data TaskListPage = TaskListPage [TaskCore.Task] TaskFilters SortOrder UTCTime
data TaskDetailPage
- = TaskDetailFound TaskCore.Task [TaskCore.Task] [TaskCore.TaskActivity] (Maybe TaskCore.RetryContext) [GitCommit] (Maybe TaskCore.AggregatedMetrics) UTCTime
+ = TaskDetailFound TaskCore.Task [TaskCore.Task] [TaskCore.TaskActivity] (Maybe TaskCore.RetryContext) [GitCommit] (Maybe TaskCore.AggregatedMetrics) [TaskCore.StoredEvent] UTCTime
| TaskDetailNotFound Text
data GitCommit = GitCommit
@@ -330,6 +331,8 @@ newtype TaskListPartial = TaskListPartial [TaskCore.Task]
data TaskMetricsPartial = TaskMetricsPartial Text [TaskCore.TaskActivity] (Maybe TaskCore.RetryContext) UTCTime
+data AgentEventsPartial = AgentEventsPartial [TaskCore.StoredEvent] Bool UTCTime
+
data DescriptionViewPartial = DescriptionViewPartial Text Text Bool
data DescriptionEditPartial = DescriptionEditPartial Text Text Bool
@@ -1487,7 +1490,7 @@ instance Lucid.ToHtml TaskDetailPage where
"The task "
Lucid.code_ (Lucid.toHtml tid)
" could not be found."
- toHtml (TaskDetailFound task allTasks activities maybeRetry commits maybeAggMetrics now) =
+ toHtml (TaskDetailFound task allTasks activities maybeRetry commits maybeAggMetrics agentEvents now) =
let crumbs = taskBreadcrumbs allTasks task
in Lucid.doctypehtml_ <| do
pageHead (TaskCore.taskId task <> " - Jr")
@@ -1588,6 +1591,8 @@ instance Lucid.ToHtml TaskDetailPage where
Lucid.class_ "review-link-btn"
]
"Review This Task"
+
+ renderAgentLogSection (TaskCore.taskId task) agentEvents (TaskCore.taskStatus task) now
where
renderDependency :: (Monad m) => TaskCore.Dependency -> Lucid.HtmlT m ()
renderDependency dep =
@@ -2386,6 +2391,162 @@ renderInlinePart part = case part of
InlineCode txt -> Lucid.code_ [Lucid.class_ "md-inline-code"] (Lucid.toHtml txt)
BoldText txt -> Lucid.strong_ (Lucid.toHtml txt)
+renderAgentLogSection :: (Monad m) => Text -> [TaskCore.StoredEvent] -> TaskCore.Status -> UTCTime -> Lucid.HtmlT m ()
+renderAgentLogSection tid events status now = do
+ let shouldShow = not (null events) || status == TaskCore.InProgress
+ when shouldShow <| do
+ let isInProgress = status == TaskCore.InProgress
+ pollAttrs =
+ if isInProgress
+ then
+ [ Lucid.makeAttribute "hx-get" ("/partials/task/" <> tid <> "/events"),
+ Lucid.makeAttribute "hx-trigger" "every 3s",
+ Lucid.makeAttribute "hx-swap" "innerHTML"
+ ]
+ else []
+ Lucid.div_ ([Lucid.class_ "agent-log-section", Lucid.id_ "agent-log-container"] <> pollAttrs) <| do
+ Lucid.h3_ <| do
+ Lucid.toHtml ("Agent Log (" <> tshow (length events) <> ")")
+ when isInProgress <| Lucid.span_ [Lucid.class_ "agent-log-live"] " LIVE"
+ if null events
+ then Lucid.p_ [Lucid.class_ "empty-msg"] "Agent session starting..."
+ else do
+ Lucid.div_ [Lucid.class_ "agent-log"] <| do
+ traverse_ (renderAgentEvent now) events
+ agentLogScrollScript
+
+renderAgentEvent :: (Monad m) => UTCTime -> TaskCore.StoredEvent -> Lucid.HtmlT m ()
+renderAgentEvent now event =
+ let eventType = TaskCore.storedEventType event
+ content = TaskCore.storedEventContent event
+ timestamp = TaskCore.storedEventTimestamp event
+ eventId = TaskCore.storedEventId event
+ in Lucid.div_
+ [ Lucid.class_ ("agent-event agent-event-" <> eventType),
+ Lucid.makeAttribute "data-event-id" (tshow eventId)
+ ]
+ <| do
+ case eventType of
+ "Assistant" -> renderAssistantEvent content timestamp now
+ "ToolCall" -> renderToolCallEvent content timestamp now
+ "ToolResult" -> renderToolResultEvent content timestamp now
+ "Cost" -> renderCostEvent content
+ "Error" -> renderErrorEvent content timestamp now
+ "Complete" -> renderCompleteEvent timestamp now
+ _ -> Lucid.div_ [Lucid.class_ "event-unknown"] (Lucid.toHtml content)
+
+renderAssistantEvent :: (Monad m) => Text -> UTCTime -> UTCTime -> Lucid.HtmlT m ()
+renderAssistantEvent content timestamp now =
+ Lucid.div_ [Lucid.class_ "event-assistant"] <| do
+ Lucid.div_ [Lucid.class_ "event-header"] <| do
+ Lucid.span_ [Lucid.class_ "event-icon"] "💬"
+ Lucid.span_ [Lucid.class_ "event-label"] "Assistant"
+ renderRelativeTimestamp now timestamp
+ Lucid.div_ [Lucid.class_ "event-content event-bubble"] <| do
+ let truncated = Text.take 2000 content
+ isTruncated = Text.length content > 2000
+ Lucid.toHtml truncated
+ when isTruncated <| Lucid.span_ [Lucid.class_ "event-truncated"] "..."
+
+renderToolCallEvent :: (Monad m) => Text -> UTCTime -> UTCTime -> Lucid.HtmlT m ()
+renderToolCallEvent content timestamp now =
+ let (toolName, args) = parseToolCallContent content
+ in Lucid.details_ [Lucid.class_ "event-tool-call"] <| do
+ Lucid.summary_ <| do
+ Lucid.span_ [Lucid.class_ "event-icon"] "🔧"
+ Lucid.span_ [Lucid.class_ "event-label tool-name"] (Lucid.toHtml toolName)
+ renderRelativeTimestamp now timestamp
+ Lucid.div_ [Lucid.class_ "event-content tool-args"] <| do
+ renderCollapsibleOutput args
+
+renderToolResultEvent :: (Monad m) => Text -> UTCTime -> UTCTime -> Lucid.HtmlT m ()
+renderToolResultEvent content timestamp now =
+ let lineCount = length (Text.lines content)
+ isLong = lineCount > 20
+ in Lucid.div_ [Lucid.class_ "event-tool-result"] <| do
+ Lucid.div_ [Lucid.class_ "event-header result-header"] <| do
+ Lucid.span_ [Lucid.class_ "event-icon"] "📋"
+ Lucid.span_ [Lucid.class_ "event-label"] "Result"
+ when (lineCount > 1)
+ <| Lucid.span_ [Lucid.class_ "line-count"] (Lucid.toHtml (tshow lineCount <> " lines"))
+ renderRelativeTimestamp now timestamp
+ if isLong
+ then
+ Lucid.details_ [Lucid.class_ "result-collapsible"] <| do
+ Lucid.summary_ "Show output"
+ Lucid.pre_ [Lucid.class_ "event-content tool-output"] (Lucid.toHtml content)
+ else Lucid.pre_ [Lucid.class_ "event-content tool-output"] (Lucid.toHtml content)
+
+renderCostEvent :: (Monad m) => Text -> Lucid.HtmlT m ()
+renderCostEvent content =
+ Lucid.div_ [Lucid.class_ "event-cost"] <| do
+ Lucid.span_ [Lucid.class_ "event-icon"] "💰"
+ Lucid.span_ [Lucid.class_ "cost-text"] (Lucid.toHtml content)
+
+renderErrorEvent :: (Monad m) => Text -> UTCTime -> UTCTime -> Lucid.HtmlT m ()
+renderErrorEvent content timestamp now =
+ Lucid.div_ [Lucid.class_ "event-error"] <| do
+ Lucid.div_ [Lucid.class_ "event-header"] <| do
+ Lucid.span_ [Lucid.class_ "event-icon"] "❌"
+ Lucid.span_ [Lucid.class_ "event-label"] "Error"
+ renderRelativeTimestamp now timestamp
+ Lucid.div_ [Lucid.class_ "event-content error-message"] (Lucid.toHtml content)
+
+renderCompleteEvent :: (Monad m) => UTCTime -> UTCTime -> Lucid.HtmlT m ()
+renderCompleteEvent timestamp now =
+ Lucid.div_ [Lucid.class_ "event-complete"] <| do
+ Lucid.span_ [Lucid.class_ "event-icon"] "✅"
+ Lucid.span_ [Lucid.class_ "event-label"] "Session completed"
+ renderRelativeTimestamp now timestamp
+
+parseToolCallContent :: Text -> (Text, Text)
+parseToolCallContent content =
+ case Text.breakOn ":" content of
+ (name, rest)
+ | Text.null rest -> (content, "")
+ | otherwise -> (Text.strip name, Text.strip (Text.drop 1 rest))
+
+renderCollapsibleOutput :: (Monad m) => Text -> Lucid.HtmlT m ()
+renderCollapsibleOutput content =
+ let lineCount = length (Text.lines content)
+ in if lineCount > 20
+ then
+ Lucid.details_ [Lucid.class_ "output-collapsible"] <| do
+ Lucid.summary_ (Lucid.toHtml (tshow lineCount <> " lines"))
+ Lucid.pre_ [Lucid.class_ "tool-output-pre"] (Lucid.toHtml content)
+ else Lucid.pre_ [Lucid.class_ "tool-output-pre"] (Lucid.toHtml content)
+
+agentLogScrollScript :: (Monad m) => Lucid.HtmlT m ()
+agentLogScrollScript =
+ Lucid.script_
+ [ Lucid.type_ "text/javascript"
+ ]
+ ( Text.unlines
+ [ "(function() {",
+ " var log = document.querySelector('.agent-log');",
+ " if (log) {",
+ " var isNearBottom = log.scrollHeight - log.scrollTop - log.clientHeight < 100;",
+ " if (isNearBottom) {",
+ " log.scrollTop = log.scrollHeight;",
+ " }",
+ " }",
+ "})();"
+ ]
+ )
+
+instance Lucid.ToHtml AgentEventsPartial where
+ toHtmlRaw = Lucid.toHtml
+ toHtml (AgentEventsPartial events isInProgress now) = do
+ Lucid.h3_ <| do
+ Lucid.toHtml ("Agent Log (" <> tshow (length events) <> ")")
+ when isInProgress <| Lucid.span_ [Lucid.class_ "agent-log-live"] " LIVE"
+ if null events
+ then Lucid.p_ [Lucid.class_ "empty-msg"] "Agent session starting..."
+ else do
+ Lucid.div_ [Lucid.class_ "agent-log"] <| do
+ traverse_ (renderAgentEvent now) events
+ agentLogScrollScript
+
api :: Proxy API
api = Proxy
@@ -2422,6 +2583,7 @@ server =
:<|> readyCountHandler
:<|> taskListPartialHandler
:<|> taskMetricsPartialHandler
+ :<|> agentEventsPartialHandler
where
styleHandler :: Servant.Handler LazyText.Text
styleHandler = pure Style.css
@@ -2584,7 +2746,8 @@ server =
if TaskCore.taskType task == TaskCore.Epic
then Just </ liftIO (TaskCore.getAggregatedMetrics tid)
else pure Nothing
- pure (TaskDetailFound task tasks activities retryCtx commits aggMetrics now)
+ agentEvents <- liftIO (TaskCore.getEventsForTask tid)
+ pure (TaskDetailFound task tasks activities retryCtx commits aggMetrics agentEvents now)
taskStatusHandler :: Text -> StatusForm -> Servant.Handler StatusBadgePartial
taskStatusHandler tid (StatusForm newStatus) = do
@@ -2725,6 +2888,21 @@ server =
maybeRetry <- liftIO (TaskCore.getRetryContext tid)
pure (TaskMetricsPartial tid activities maybeRetry now)
+ agentEventsPartialHandler :: Text -> Maybe Int -> Servant.Handler AgentEventsPartial
+ agentEventsPartialHandler tid maybeSince = do
+ now <- liftIO getCurrentTime
+ maybeSession <- liftIO (TaskCore.getLatestSessionForTask tid)
+ events <- case maybeSession of
+ Nothing -> pure []
+ Just sid -> case maybeSince of
+ Nothing -> liftIO (TaskCore.getEventsForSession sid)
+ Just lastId -> liftIO (TaskCore.getEventsSince sid lastId)
+ tasks <- liftIO TaskCore.loadTasks
+ let isInProgress = case TaskCore.findTask tid tasks of
+ Nothing -> False
+ Just task -> TaskCore.taskStatus task == TaskCore.InProgress
+ pure (AgentEventsPartial events isInProgress now)
+
taskToUnixTs :: TaskCore.Task -> Int
taskToUnixTs t = round (utcTimeToPOSIXSeconds (TaskCore.taskUpdatedAt t))
diff --git a/Omni/Jr/Web/Style.hs b/Omni/Jr/Web/Style.hs
index 8c423bb..00d66c2 100644
--- a/Omni/Jr/Web/Style.hs
+++ b/Omni/Jr/Web/Style.hs
@@ -39,6 +39,7 @@ stylesheet = do
taskMetaStyles
timeFilterStyles
sortDropdownStyles
+ agentLogStyles
responsiveStyles
darkModeStyles
@@ -1402,6 +1403,151 @@ taskMetaStyles = do
color "#d1d5db"
Stylesheet.key "user-select" ("none" :: Text)
+agentLogStyles :: Css
+agentLogStyles = do
+ ".agent-log-section" ? do
+ marginTop (em 1)
+ paddingTop (em 1)
+ borderTop (px 1) solid "#e5e7eb"
+ ".agent-log-live" ? do
+ fontSize (px 10)
+ fontWeight bold
+ color "#10b981"
+ backgroundColor "#d1fae5"
+ padding (px 2) (px 6) (px 2) (px 6)
+ borderRadius (px 10) (px 10) (px 10) (px 10)
+ marginLeft (px 8)
+ textTransform uppercase
+ Stylesheet.key "animation" ("pulse 2s infinite" :: Text)
+ ".agent-log" ? do
+ maxHeight (px 600)
+ overflowY auto
+ display flex
+ flexDirection column
+ Stylesheet.key "gap" ("8px" :: Text)
+ padding (px 8) (px 0) (px 8) (px 0)
+ ".agent-event" ? do
+ fontSize (px 13)
+ ".event-header" ? do
+ display flex
+ alignItems center
+ Stylesheet.key "gap" ("8px" :: Text)
+ marginBottom (px 4)
+ ".event-icon" ? do
+ fontSize (px 14)
+ width (px 20)
+ textAlign center
+ ".event-label" ? do
+ fontWeight (weight 500)
+ color "#374151"
+ ".event-assistant" ? do
+ padding (px 0) (px 0) (px 0) (px 0)
+ ".event-bubble" ? do
+ backgroundColor "#f3f4f6"
+ padding (px 8) (px 12) (px 8) (px 12)
+ borderRadius (px 8) (px 8) (px 8) (px 8)
+ whiteSpace preWrap
+ lineHeight (em 1.5)
+ ".event-truncated" ? do
+ color "#6b7280"
+ fontStyle italic
+ ".event-tool-call" ? do
+ borderLeft (px 3) solid "#3b82f6"
+ paddingLeft (px 8)
+ ".event-tool-call" |> "summary" ? do
+ cursor pointer
+ listStyleType none
+ display flex
+ alignItems center
+ Stylesheet.key "gap" ("8px" :: Text)
+ ".event-tool-call" |> "summary" # before ? do
+ content (stringContent "▶")
+ fontSize (px 10)
+ color "#6b7280"
+ transition "transform" (ms 150) ease (sec 0)
+ ".event-tool-call[open]" |> "summary" # before ? do
+ Stylesheet.key "transform" ("rotate(90deg)" :: Text)
+ ".tool-name" ? do
+ fontFamily ["SF Mono", "Monaco", "Consolas", "monospace"] [monospace]
+ color "#3b82f6"
+ ".tool-args" ? do
+ marginTop (px 4)
+ paddingLeft (px 20)
+ ".tool-output-pre" ? do
+ fontFamily ["SF Mono", "Monaco", "Consolas", "monospace"] [monospace]
+ fontSize (px 11)
+ backgroundColor "#1e1e1e"
+ color "#d4d4d4"
+ padding (px 8) (px 10) (px 8) (px 10)
+ borderRadius (px 4) (px 4) (px 4) (px 4)
+ overflowX auto
+ whiteSpace preWrap
+ maxHeight (px 300)
+ margin (px 0) (px 0) (px 0) (px 0)
+ ".event-tool-result" ? do
+ borderLeft (px 3) solid "#10b981"
+ paddingLeft (px 8)
+ ".result-header" ? do
+ fontSize (px 12)
+ ".line-count" ? do
+ fontSize (px 11)
+ color "#6b7280"
+ backgroundColor "#f3f4f6"
+ padding (px 1) (px 6) (px 1) (px 6)
+ borderRadius (px 10) (px 10) (px 10) (px 10)
+ ".result-collapsible" |> "summary" ? do
+ cursor pointer
+ fontSize (px 12)
+ color "#0066cc"
+ marginBottom (px 4)
+ ".result-collapsible" |> "summary" # hover ? textDecoration underline
+ ".tool-output" ? do
+ fontFamily ["SF Mono", "Monaco", "Consolas", "monospace"] [monospace]
+ fontSize (px 11)
+ backgroundColor "#1e1e1e"
+ color "#d4d4d4"
+ padding (px 8) (px 10) (px 8) (px 10)
+ borderRadius (px 4) (px 4) (px 4) (px 4)
+ overflowX auto
+ whiteSpace preWrap
+ maxHeight (px 300)
+ margin (px 0) (px 0) (px 0) (px 0)
+ ".event-cost" ? do
+ display flex
+ alignItems center
+ Stylesheet.key "gap" ("6px" :: Text)
+ fontSize (px 11)
+ color "#6b7280"
+ padding (px 4) (px 0) (px 4) (px 0)
+ ".cost-text" ? do
+ fontFamily ["SF Mono", "Monaco", "Consolas", "monospace"] [monospace]
+ ".event-error" ? do
+ borderLeft (px 3) solid "#ef4444"
+ paddingLeft (px 8)
+ backgroundColor "#fef2f2"
+ padding (px 8) (px 8) (px 8) (px 12)
+ borderRadius (px 4) (px 4) (px 4) (px 4)
+ ".event-error" |> ".event-label" ? color "#dc2626"
+ ".error-message" ? do
+ color "#dc2626"
+ fontFamily ["SF Mono", "Monaco", "Consolas", "monospace"] [monospace]
+ fontSize (px 12)
+ whiteSpace preWrap
+ ".event-complete" ? do
+ display flex
+ alignItems center
+ Stylesheet.key "gap" ("8px" :: Text)
+ color "#10b981"
+ fontWeight (weight 500)
+ padding (px 8) (px 0) (px 8) (px 0)
+ ".output-collapsible" |> "summary" ? do
+ cursor pointer
+ fontSize (px 12)
+ color "#0066cc"
+ marginBottom (px 4)
+ ".output-collapsible" |> "summary" # hover ? textDecoration underline
+ Stylesheet.key "@keyframes pulse" ("0%, 100% { opacity: 1; } 50% { opacity: 0.5; }" :: Text)
+
responsiveStyles :: Css
responsiveStyles = do
query Media.screen [Media.maxWidth (px 600)] <| do
@@ -1703,6 +1849,20 @@ darkModeStyles =
".retry-banner-details" ? color "#d1d5db"
".retry-value" ? color "#9ca3af"
".retry-commit" ? backgroundColor "#374151"
+ ".agent-log-section" ? borderTopColor "#374151"
+ ".agent-log-live" ? do
+ backgroundColor "#065f46"
+ color "#a7f3d0"
+ ".event-bubble" ? backgroundColor "#374151"
+ ".event-label" ? color "#d1d5db"
+ ".line-count" ? do
+ backgroundColor "#374151"
+ color "#9ca3af"
+ ".event-error" ? do
+ backgroundColor "#450a0a"
+ borderColor "#dc2626"
+ ".event-error" |> ".event-label" ? color "#f87171"
+ ".error-message" ? color "#f87171"
-- Responsive dark mode: dropdown content needs background on mobile
query Media.screen [Media.maxWidth (px 600)] <| do
".navbar-dropdown-content" ? do