summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Omni/Agent/Log.hs196
-rw-r--r--Omni/Agent/Worker.hs32
2 files changed, 108 insertions, 120 deletions
diff --git a/Omni/Agent/Log.hs b/Omni/Agent/Log.hs
index 28dbab2..6541551 100644
--- a/Omni/Agent/Log.hs
+++ b/Omni/Agent/Log.hs
@@ -1,123 +1,103 @@
-{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE NoImplicitPrelude #-}
-module Omni.Agent.Log
- ( LogEntry (..),
- Status (..),
- initialStatus,
- updateStatus,
- renderStatus,
- parseLine,
- format,
- )
-where
+-- : out omni-agent-log
+module Omni.Agent.Log where
import Alpha
-import Data.Aeson (FromJSON (..), (.:), (.:?))
-import qualified Data.Aeson as Aeson
-import qualified Data.ByteString.Lazy as BSL
-import qualified Data.Set as Set
-
-data LogEntry = LogEntry
- { leMessage :: Text,
- leLevel :: Maybe Text,
- leToolName :: Maybe Text,
- leBatches :: Maybe [[Text]],
- leMethod :: Maybe Text,
- lePath :: Maybe Text,
- leTimestamp :: Maybe Text
- }
- deriving (Show, Eq, Generic)
-
-instance FromJSON LogEntry where
- parseJSON =
- Aeson.withObject "LogEntry" <| \v ->
- ( LogEntry
- </ (v .: "message")
- )
- <*> v
- .:? "level"
- <*> v
- .:? "toolName"
- <*> v
- .:? "batches"
- <*> v
- .:? "method"
- <*> v
- .:? "path"
- <*> v
- .:? "timestamp"
+import qualified Data.Text.IO as TIO
+import qualified System.Console.ANSI as ANSI
+import qualified System.IO as IO
+import System.IO.Unsafe (unsafePerformIO)
+import Data.IORef (IORef, newIORef, readIORef, writeIORef, modifyIORef')
+-- | Status of the agent for the UI
data Status = Status
- { sWorkerName :: Text,
- sTaskId :: Maybe Text,
- sFiles :: Set.Set Text,
- sStartTime :: Maybe Text,
- sLastActivity :: Text
+ { statusWorker :: Text,
+ statusTask :: Maybe Text,
+ statusFiles :: Int,
+ statusCredits :: Double,
+ statusTime :: Text, -- formatted time string
+ statusActivity :: Text
}
- deriving (Show, Eq, Generic)
+ deriving (Show, Eq)
-initialStatus :: Text -> Status
-initialStatus name =
+emptyStatus :: Text -> Status
+emptyStatus workerName =
Status
- { sWorkerName = name,
- sTaskId = Nothing,
- sFiles = Set.empty,
- sStartTime = Nothing,
- sLastActivity = "Idle"
+ { statusWorker = workerName,
+ statusTask = Nothing,
+ statusFiles = 0,
+ statusCredits = 0.0,
+ statusTime = "00:00",
+ statusActivity = "Idle"
}
-updateStatus :: LogEntry -> Status -> Status
-updateStatus e s =
- let s' = case format e of
- Just msg -> s {sLastActivity = msg}
- Nothing -> s
- s'' = case leTimestamp e of
- Just t -> if isNothing (sStartTime s) then s' {sStartTime = Just t} else s'
- Nothing -> s'
- in case (leMessage e, lePath e) of
- ("ide-fs", Just p) -> s'' {sFiles = Set.insert p (sFiles s'')}
- _ -> s''
+-- | Global state for the status bar
+{-# NOINLINE currentStatus #-}
+currentStatus :: IORef Status
+currentStatus = unsafePerformIO (newIORef (emptyStatus "Unknown"))
+
+-- | Initialize the status bar system
+init :: Text -> IO ()
+init workerName = do
+ writeIORef currentStatus (emptyStatus workerName)
+ -- Reserve 2 lines at bottom
+ IO.hPutStrLn IO.stderr ""
+ IO.hPutStrLn IO.stderr ""
+ ANSI.hCursorUp IO.stderr 2
+
+-- | Update the status
+update :: (Status -> Status) -> IO ()
+update f = do
+ modifyIORef' currentStatus f
+ render
-renderStatus :: Status -> Text
-renderStatus s =
- let line1 =
- "[Worker: "
- <> sWorkerName s
- <> "] "
- <> "Task: "
- <> fromMaybe "None" (sTaskId s)
- <> " | Files: "
- <> show (Set.size (sFiles s))
- line2 = sLastActivity s
- in line1 <> "\n" <> line2
+-- | Set the activity message
+updateActivity :: Text -> IO ()
+updateActivity msg = update (\s -> s {statusActivity = msg})
-parseLine :: Text -> Maybe LogEntry
-parseLine line = Aeson.decode <| BSL.fromStrict <| encodeUtf8 line
+-- | Log a scrolling message (appears above status bars)
+log :: Text -> IO ()
+log msg = do
+ -- Clear status bars
+ ANSI.hClearLine IO.stderr
+ ANSI.hCursorDown IO.stderr 1
+ ANSI.hClearLine IO.stderr
+ ANSI.hCursorUp IO.stderr 1
+
+ -- Print message (scrolls screen)
+ TIO.hPutStrLn IO.stderr msg
+
+ -- Re-render status bars at bottom
+ -- (Since we scrolled, we are now on the line above where the first status line should be)
+ render
-format :: LogEntry -> Maybe Text
-format e =
- case leMessage e of
- "executing 1 tools in 1 batch(es)" ->
- let tool = case leBatches e of
- Just ((t : _) : _) -> t
- _ -> "unknown"
- in Just <| "🤖 THOUGHT: Planning tool execution (" <> tool <> ")"
- "Tool Bash permitted - action: allow" ->
- Just "🔧 TOOL: Bash command executed"
- msg
- | "Processing tool completion for ledger" == msg && isJust (leToolName e) ->
- Just <| "✅ TOOL: " <> fromMaybe "" (leToolName e) <> " completed"
- "ide-fs" ->
- case leMethod e of
- Just "readFile" -> Just <| "📂 READ: " <> fromMaybe "" (lePath e)
- _ -> Nothing
- "System prompt build complete (no changes)" ->
- Just "🧠 THINKING..."
- "System prompt build complete (first build)" ->
- Just "🚀 STARTING new task context"
- msg ->
- case leLevel e of
- Just "error" -> Just <| "❌ ERROR: " <> msg
- _ -> Nothing
+-- | Render the two status lines
+render :: IO ()
+render = do
+ Status {..} <- readIORef currentStatus
+
+ -- Line 1: Meta
+ -- [Worker: name] Task: t-123 | Files: 3 | Credits: $0.45 | Time: 05:23
+ let taskStr = maybe "None" identity statusTask
+ meta = "[Worker: " <> statusWorker <> "] Task: " <> taskStr
+ <> " | Files: " <> tshow statusFiles
+ <> " | Credits: $" <> tshow statusCredits
+ <> " | Time: " <> statusTime
+
+ ANSI.hSetCursorColumn IO.stderr 0
+ ANSI.hClearLine IO.stderr
+ TIO.hPutStr IO.stderr meta
+
+ -- Line 2: Activity
+ -- [14:05:22] 🤖 Thinking...
+ ANSI.hCursorDown IO.stderr 1
+ ANSI.hSetCursorColumn IO.stderr 0
+ ANSI.hClearLine IO.stderr
+ TIO.hPutStr IO.stderr ("🤖 " <> statusActivity)
+
+ -- Return cursor to line 1
+ ANSI.hCursorUp IO.stderr 1
+ IO.hFlush IO.stderr
diff --git a/Omni/Agent/Worker.hs b/Omni/Agent/Worker.hs
index d201234..01099a0 100644
--- a/Omni/Agent/Worker.hs
+++ b/Omni/Agent/Worker.hs
@@ -8,7 +8,7 @@ import Alpha
import qualified Data.Text as Text
import qualified Omni.Agent.Core as Core
import qualified Omni.Agent.Git as Git
-import qualified Omni.Log as Log
+import qualified Omni.Agent.Log as AgentLog
import qualified Omni.Task.Core as TaskCore
import qualified System.Directory as Directory
import qualified System.Exit as Exit
@@ -17,14 +17,15 @@ import qualified System.Process as Process
start :: Core.Worker -> IO ()
start worker = do
- Log.info ["worker", "starting loop for", Core.workerName worker]
+ AgentLog.init (Core.workerName worker)
+ AgentLog.log ("Worker starting loop for " <> Core.workerName worker)
loop worker
loop :: Core.Worker -> IO ()
loop worker = do
let repo = Core.workerPath worker
- Log.info ["worker", "syncing tasks"]
+ AgentLog.updateActivity "Syncing tasks..."
-- Sync with live first to get latest code and tasks
-- We ignore errors here to keep the loop alive, but syncWithLive panics on conflict.
-- Ideally we should catch exceptions, but for now let it fail and restart (via supervisor or manual).
@@ -41,7 +42,7 @@ loop worker = do
readyTasks <- TaskCore.getReadyTasks
case readyTasks of
[] -> do
- Log.info ["worker", "no work found, sleeping"]
+ AgentLog.updateActivity "No work found, sleeping..."
threadDelay (60 * 1000000) -- 60 seconds
loop worker
(task : _) -> do
@@ -53,7 +54,8 @@ processTask worker task = do
let repo = Core.workerPath worker
let tid = TaskCore.taskId task
- Log.info ["worker", "claiming task", tid]
+ AgentLog.update (\s -> s {AgentLog.statusTask = Just tid})
+ AgentLog.updateActivity ("Claiming task " <> tid)
-- Claim task
TaskCore.updateTaskStatus tid TaskCore.InProgress
@@ -65,30 +67,31 @@ processTask worker task = do
let taskBranch = "task/" <> tid
currentBranch <- Git.getCurrentBranch repo
if currentBranch == taskBranch
- then Log.info ["worker", "resuming branch", taskBranch]
+ then AgentLog.log ("Resuming branch " <> taskBranch)
else do
exists <- Git.branchExists repo taskBranch
if exists
then do
- Log.info ["worker", "switching to existing branch", taskBranch]
+ AgentLog.log ("Switching to existing branch " <> taskBranch)
Git.checkout repo taskBranch
else do
-- Determine base branch from dependencies
baseBranch <- findBaseBranch repo task
if baseBranch /= "live"
then do
- Log.info ["worker", "basing", taskBranch, "on", baseBranch]
+ AgentLog.log ("Basing " <> taskBranch <> " on " <> baseBranch)
Git.checkout repo baseBranch
- else Log.info ["worker", "basing", taskBranch, "on live"]
+ else AgentLog.log ("Basing " <> taskBranch <> " on live")
Git.createBranch repo taskBranch
-- Run Amp
+ AgentLog.updateActivity "Running Amp agent..."
exitCode <- runAmp repo task
case exitCode of
Exit.ExitSuccess -> do
- Log.info ["worker", "agent finished successfully"]
+ AgentLog.log "Agent finished successfully"
-- Update status to Review (bundled with feature commit)
TaskCore.updateTaskStatus tid TaskCore.Review
@@ -98,7 +101,7 @@ processTask worker task = do
Git.commit repo ("feat: implement " <> tid)
-- Submit for review
- Log.info ["worker", "submitting for review"]
+ AgentLog.updateActivity "Submitting for review..."
-- Switch back to worker base
let base = Core.workerName worker
@@ -110,8 +113,13 @@ processTask worker task = do
-- Update status to Review (for signaling)
TaskCore.updateTaskStatus tid TaskCore.Review
Git.commit repo ("task: review " <> tid)
+
+ AgentLog.log ("[✓] Task " <> tid <> " completed")
+ AgentLog.update (\s -> s {AgentLog.statusTask = Nothing})
+
Exit.ExitFailure code -> do
- Log.warn ["worker", "agent failed with code", Text.pack (show code)]
+ AgentLog.log ("Agent failed with code " <> tshow code)
+ AgentLog.updateActivity "Agent failed, retrying..."
threadDelay (10 * 1000000) -- Sleep 10s
runAmp :: FilePath -> TaskCore.Task -> IO Exit.ExitCode