diff options
Diffstat (limited to 'Omni/Agent')
| -rw-r--r-- | Omni/Agent/Core.hs | 37 | ||||
| -rw-r--r-- | Omni/Agent/DESIGN.md | 9 | ||||
| -rw-r--r-- | Omni/Agent/Git.hs | 201 | ||||
| -rw-r--r-- | Omni/Agent/Log.hs | 218 | ||||
| -rw-r--r-- | Omni/Agent/LogTest.hs | 74 | ||||
| -rw-r--r-- | Omni/Agent/WORKER_AGENT_GUIDE.md | 67 | ||||
| -rw-r--r-- | Omni/Agent/Worker.hs | 252 | ||||
| -rwxr-xr-x | Omni/Agent/harvest-tasks.sh | 9 | ||||
| -rwxr-xr-x | Omni/Agent/monitor.sh | 29 | ||||
| -rwxr-xr-x | Omni/Agent/setup-worker.sh | 7 | ||||
| -rwxr-xr-x | Omni/Agent/start-worker.sh | 171 |
11 files changed, 893 insertions, 181 deletions
diff --git a/Omni/Agent/Core.hs b/Omni/Agent/Core.hs new file mode 100644 index 0000000..2d09e39 --- /dev/null +++ b/Omni/Agent/Core.hs @@ -0,0 +1,37 @@ +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE NoImplicitPrelude #-} + +-- : out omni-agent-core +module Omni.Agent.Core where + +import Alpha +import Data.Aeson (FromJSON, ToJSON) + +-- | Status of a worker agent +data WorkerStatus + = Idle + | Syncing + | -- | Task ID + Working Text + | -- | Task ID + Submitting Text + | -- | Error message + Error Text + deriving (Show, Eq, Generic) + +instance ToJSON WorkerStatus + +instance FromJSON WorkerStatus + +-- | Representation of a worker agent +data Worker = Worker + { workerName :: Text, + workerPid :: Maybe Int, + workerStatus :: WorkerStatus, + workerPath :: FilePath + } + deriving (Show, Eq, Generic) + +instance ToJSON Worker + +instance FromJSON Worker diff --git a/Omni/Agent/DESIGN.md b/Omni/Agent/DESIGN.md index eb30ecb..2d1e6e3 100644 --- a/Omni/Agent/DESIGN.md +++ b/Omni/Agent/DESIGN.md @@ -77,6 +77,7 @@ The Haskell implementation should replicate the logic of `start-worker.sh` but w - **Two-line Status**: The CLI should maintain two reserved lines at the bottom (or top) of the output for each worker: - **Line 1 (Meta)**: `[Worker: omni-worker-1] Task: t-123 | Files: 3 | Credits: $0.45 | Time: 05:23` - **Line 2 (Activity)**: `[14:05:22] 🤖 Thinking...` (updates in place) + - **Task Details**: When claiming a task, print the full task description/details to the log/console so the user can see what is being worked on without looking it up. - **Completion**: When a task finishes, print a summary line (e.g., `[✓] Task t-123 completed in 12m 30s`) and a hard line break before starting the next loop. - **History**: Previous log lines (tool outputs, thoughts) scroll up above these two status lines. @@ -84,13 +85,19 @@ The Haskell implementation should replicate the logic of `start-worker.sh` but w - Iterate over `.tasks/workers/` or `git worktree list`. - For each worker, extract `.tasks/tasks.jsonl` via `git show`. - Run `Task.import`. +- **Squashing**: If the previous commit on the target branch (live) was a harvest commit, use `git commit --amend` to consolidate updates and reduce commit noise. ### 4.5 Git Robustness (Learnings) +- **Identity**: Configure `git config user.name "Omni Worker"` and `user.email` in the worktree to clearly distinguish worker commits from human commits. - **Force Checkout**: The worker must use `git checkout -f` (or equivalent) when switching to task branches to ensure untracked files (like `.tasks/counters.jsonl`) don't block the switch. - **Base Branch Logic**: - If the task depends on another task that is *not* yet in `live` (e.g., in `Review`), the worker should branch off the dependency's branch (`task/<dep-id>`). - - Otherwise, branch off `live` (via the worker's base branch). + - Otherwise, branch off `live` directly. Do NOT use the local worker branch (`omni-worker-N`) as the base, as it may contain temporary sync commits that shouldn't be merged. +- **Commit Hygiene**: Bundle the task status update (marking as 'Review') *inside* the feature implementation commit. This keeps the history clean (one commit per feature) and avoids separate "sync" commits for status changes. - **Clean State**: The worker should ensure the workspace is clean (no uncommitted changes) before starting a new loop iteration. +- **Rebase Safety**: Always check the exit code of `git rebase`. If it fails (conflicts), abort immediately (`git rebase --abort`) to avoid leaving the repo in a broken interactive rebase state. +- **Status Verification**: Verify that task status updates actually succeed. Check `task ready` output against `live` state to prevent "zombie" tasks (completed in live but stuck in local loop) from being re-claimed. +- **Binary Freshness**: Ensure the `task` binary used by the worker is rebuilt/updated when source code changes, otherwise logic fixes (like `task ready` filtering) won't take effect. ## 5. Migration Strategy diff --git a/Omni/Agent/Git.hs b/Omni/Agent/Git.hs new file mode 100644 index 0000000..b1978f2 --- /dev/null +++ b/Omni/Agent/Git.hs @@ -0,0 +1,201 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE NoImplicitPrelude #-} + +-- | Git operations for the agent. +-- +-- : out omni-agent-git +-- : dep temporary +module Omni.Agent.Git + ( checkout, + syncWithLive, + commit, + createBranch, + getCurrentBranch, + branchExists, + isMerged, + main, + test, + ) +where + +import Alpha +import qualified Data.Text as Text +import qualified Omni.Log as Log +import Omni.Test ((@=?)) +import qualified Omni.Test as Test +import qualified System.Directory as Directory +import qualified System.Exit as Exit +import qualified System.IO.Temp as Temp +import qualified System.Process as Process + +main :: IO () +main = Test.run test + +test :: Test.Tree +test = + Test.group + "Omni.Agent.Git" + [ Test.unit "checkout works" <| do + Temp.withSystemTempDirectory "omni-agent-git-test" <| \tmpDir -> do + let repo = tmpDir <> "/repo" + Directory.createDirectory repo + -- init repo + git repo ["init"] + git repo ["branch", "-m", "master"] + git repo ["config", "user.email", "you@example.com"] + git repo ["config", "user.name", "Your Name"] + + -- commit A + writeFile (repo <> "/a.txt") "A" + git repo ["add", "a.txt"] + git repo ["commit", "-m", "A"] + shaA <- getSha repo "HEAD" + + -- create branch dev + git repo ["checkout", "-b", "dev"] + + -- commit B + writeFile (repo <> "/b.txt") "B" + git repo ["add", "b.txt"] + git repo ["commit", "-m", "B"] + shaB <- getSha repo "HEAD" + + -- switch back to master + git repo ["checkout", "master"] + + -- Test 1: checkout dev + checkout repo "dev" + current <- getSha repo "HEAD" + shaB @=? current + + -- Test 2: checkout master + checkout repo "master" + current' <- getSha repo "HEAD" + shaA @=? current' + + -- Test 3: dirty state + writeFile (repo <> "/a.txt") "DIRTY" + checkout repo "dev" + current'' <- getSha repo "HEAD" + shaB @=? current'' + -- Verify dirty file is gone/overwritten (b.txt should exist, a.txt should be A from master? No, a.txt is in A and B) + -- Wait, in dev, a.txt is "A". + content <- readFile (repo <> "/a.txt") + "A" @=? content + + -- Test 4: untracked file + writeFile (repo <> "/untracked.txt") "DELETE ME" + checkout repo "master" + exists <- Directory.doesFileExist (repo <> "/untracked.txt") + False @=? exists + ] + +getSha :: FilePath -> String -> IO String +getSha dir ref = do + let cmd = (Process.proc "git" ["rev-parse", ref]) {Process.cwd = Just dir} + (code, out, _) <- Process.readCreateProcessWithExitCode cmd "" + case code of + Exit.ExitSuccess -> pure <| strip out + _ -> panic "getSha failed" + +-- | Checkout a specific ref (SHA, branch, tag) in the given repository path. +-- This function ensures the repository is in the correct state by: +-- 1. Fetching all updates +-- 2. Checking out the ref (forcing overwrites of local changes) +-- 3. Resetting hard to the ref (to ensure clean state) +-- 4. Cleaning untracked files +-- 5. Updating submodules +checkout :: FilePath -> Text -> IO () +checkout repoPath ref = do + let r = Text.unpack ref + + Log.info ["git", "checkout", ref, "in", Text.pack repoPath] + + -- Fetch all refs to ensure we have the target + git repoPath ["fetch", "--all", "--tags"] + + -- Checkout the ref, discarding local changes + git repoPath ["checkout", "--force", r] + + -- Reset hard to ensure we are exactly at the target state + git repoPath ["reset", "--hard", r] + + -- Remove untracked files and directories + git repoPath ["clean", "-fdx"] + + -- Update submodules + git repoPath ["submodule", "update", "--init", "--recursive"] + + Log.good ["git", "checkout", "complete"] + Log.br + +-- | Run a git command in the given directory. +git :: FilePath -> [String] -> IO () +git dir args = do + let cmd = (Process.proc "git" args) {Process.cwd = Just dir} + (exitCode, out, err) <- Process.readCreateProcessWithExitCode cmd "" + case exitCode of + Exit.ExitSuccess -> pure () + Exit.ExitFailure code -> do + Log.fail ["git command failed", Text.pack (show args), "code: " <> show code] + Log.info [Text.pack out] + Log.info [Text.pack err] + Log.br + panic <| "git command failed: git " <> show args + +syncWithLive :: FilePath -> IO () +syncWithLive repo = do + Log.info ["git", "syncing with live"] + -- git repo ["fetch", "origin", "live"] -- Optional + + -- Try sync (branchless sync), if fail, panic + -- This replaces manual rebase and handles stack movement + let cmd = (Process.proc "git" ["sync"]) {Process.cwd = Just repo} + (code, out, err) <- Process.readCreateProcessWithExitCode cmd "" + case code of + Exit.ExitSuccess -> pure () + Exit.ExitFailure _ -> do + Log.warn ["git sync failed", Text.pack err] + Log.info [Text.pack out] + panic "Sync with live failed (git sync)" + +commit :: FilePath -> Text -> IO () +commit repo msg = do + Log.info ["git", "commit", msg] + git repo ["add", "."] + + -- Check for changes before committing to avoid error + let checkCmd = (Process.proc "git" ["diff", "--cached", "--quiet"]) {Process.cwd = Just repo} + (code, _, _) <- Process.readCreateProcessWithExitCode checkCmd "" + + case code of + Exit.ExitSuccess -> Log.warn ["git", "nothing to commit", "skipping"] + Exit.ExitFailure 1 -> git repo ["commit", "-m", Text.unpack msg] + Exit.ExitFailure c -> panic <| "git diff failed with code " <> show c + +createBranch :: FilePath -> Text -> IO () +createBranch repo branch = do + Log.info ["git", "create branch", branch] + git repo ["checkout", "-b", Text.unpack branch] + +getCurrentBranch :: FilePath -> IO Text +getCurrentBranch repo = do + let cmd = (Process.proc "git" ["branch", "--show-current"]) {Process.cwd = Just repo} + (code, out, _) <- Process.readCreateProcessWithExitCode cmd "" + case code of + Exit.ExitSuccess -> pure <| Text.strip (Text.pack out) + _ -> panic "git branch failed" + +branchExists :: FilePath -> Text -> IO Bool +branchExists repo branch = do + let cmd = (Process.proc "git" ["show-ref", "--verify", "refs/heads/" <> Text.unpack branch]) {Process.cwd = Just repo} + (code, _, _) <- Process.readCreateProcessWithExitCode cmd "" + pure (code == Exit.ExitSuccess) + +isMerged :: FilePath -> Text -> Text -> IO Bool +isMerged repo branch target = do + -- Check if 'branch' is merged into 'target' + -- git merge-base --is-ancestor <branch> <target> + let cmd = (Process.proc "git" ["merge-base", "--is-ancestor", Text.unpack branch, Text.unpack target]) {Process.cwd = Just repo} + (code, _, _) <- Process.readCreateProcessWithExitCode cmd "" + pure (code == Exit.ExitSuccess) diff --git a/Omni/Agent/Log.hs b/Omni/Agent/Log.hs new file mode 100644 index 0000000..dd66abc --- /dev/null +++ b/Omni/Agent/Log.hs @@ -0,0 +1,218 @@ +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE NoImplicitPrelude #-} + +-- : out omni-agent-log +module Omni.Agent.Log where + +import Alpha +import Data.Aeson (Value (..), decode) +import qualified Data.Aeson.KeyMap as KM +import qualified Data.ByteString.Lazy as BL +import Data.IORef (IORef, modifyIORef', newIORef, readIORef, writeIORef) +import qualified Data.Text.Encoding as TextEnc +import qualified Data.Text.IO as TIO +import qualified Data.Vector as V +import qualified System.Console.ANSI as ANSI +import qualified System.IO as IO +import System.IO.Unsafe (unsafePerformIO) +import Text.Printf (printf) + +-- | Parsed log entry +data LogEntry = LogEntry + { leMessage :: Maybe Text, + leLevel :: Maybe Text, + leToolName :: Maybe Text, + leBatches :: Maybe [[Text]], + leMethod :: Maybe Text, + lePath :: Maybe Text + } + deriving (Show, Eq) + +-- | Status of the agent for the UI +data Status = Status + { statusWorker :: Text, + statusTask :: Maybe Text, + statusThreadId :: Maybe Text, + statusFiles :: Int, + statusCredits :: Double, + statusTime :: Text, -- formatted time string + statusActivity :: Text + } + deriving (Show, Eq) + +emptyStatus :: Text -> Status +emptyStatus workerName = + Status + { statusWorker = workerName, + statusTask = Nothing, + statusThreadId = Nothing, + statusFiles = 0, + statusCredits = 0.0, + statusTime = "00:00", + statusActivity = "Idle" + } + +-- | 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 + IO.hSetBuffering IO.stderr IO.LineBuffering + writeIORef currentStatus (emptyStatus workerName) + -- Reserve 5 lines at bottom + replicateM_ 5 (IO.hPutStrLn IO.stderr "") + ANSI.hCursorUp IO.stderr 5 + +-- | Update the status +update :: (Status -> Status) -> IO () +update f = do + modifyIORef' currentStatus f + render + +-- | Set the activity message +updateActivity :: Text -> IO () +updateActivity msg = update (\s -> s {statusActivity = msg}) + +-- | Process a log line from the agent and update status if relevant +processLogLine :: Text -> IO () +processLogLine line = do + let entry = parseLine line + for_ (entry +> formatLogEntry) updateActivity + +-- | Parse a JSON log line into a LogEntry +parseLine :: Text -> Maybe LogEntry +parseLine line = do + let lbs = BL.fromStrict (TextEnc.encodeUtf8 line) + obj <- decode lbs + case obj of + Object o -> + Just + LogEntry + { leMessage = getString "message" o, + leLevel = getString "level" o, + leToolName = getString "toolName" o, + leBatches = getBatches o, + leMethod = getString "method" o, + lePath = getString "path" o + } + _ -> Nothing + where + getString k o = + case KM.lookup k o of + Just (String s) -> Just s + _ -> Nothing + + getBatches o = + case KM.lookup "batches" o of + Just (Array b) -> + Just + <| mapMaybe + ( \case + Array b0 -> + Just + <| mapMaybe + ( \case + String s -> Just s + _ -> Nothing + ) + (V.toList b0) + _ -> Nothing + ) + (V.toList b) + _ -> Nothing + +-- | Format a log entry into a user-friendly status message (NO EMOJIS) +formatLogEntry :: LogEntry -> Maybe Text +formatLogEntry LogEntry {..} = + case leMessage of + Just "executing 1 tools in 1 batch(es)" -> do + let tools = fromMaybe [] leBatches + let firstTool = case tools of + ((t : _) : _) -> t + _ -> "unknown" + Just ("THOUGHT: Planning tool execution (" <> firstTool <> ")") + Just "Tool Bash permitted - action: allow" -> + Just "TOOL: Bash command executed" + Just "Processing tool completion for ledger" + | isJust leToolName -> + Just ("TOOL: " <> fromMaybe "unknown" leToolName <> " completed") + Just "ide-fs" | leMethod == Just "readFile" -> + case lePath of + Just p -> Just ("READ: " <> p) + _ -> Nothing + Just "System prompt build complete (no changes)" -> + Just "THINKING..." + Just "System prompt build complete (first build)" -> + Just "STARTING new task context" + Just msg + | leLevel == Just "error" -> + Just ("ERROR: " <> msg) + _ -> Nothing + +-- | Log a scrolling message (appears above status bars) +log :: Text -> IO () +log msg = do + -- Clear status bars (5 lines) + ANSI.hClearLine IO.stderr + ANSI.hCursorDown IO.stderr 1 + ANSI.hClearLine IO.stderr + ANSI.hCursorDown IO.stderr 1 + ANSI.hClearLine IO.stderr + ANSI.hCursorDown IO.stderr 1 + ANSI.hClearLine IO.stderr + ANSI.hCursorDown IO.stderr 1 + ANSI.hClearLine IO.stderr + ANSI.hCursorUp IO.stderr 4 + + -- 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 + +-- | Render the 5 status lines (Vertical Layout) +render :: IO () +render = do + Status {..} <- readIORef currentStatus + + let taskStr = maybe "None" identity statusTask + threadStr = maybe "None" identity statusThreadId + + -- Line 1: Worker + Time + ANSI.hSetCursorColumn IO.stderr 0 + ANSI.hClearLine IO.stderr + TIO.hPutStr IO.stderr <| "Worker: " <> statusWorker <> " | Time: " <> statusTime + + -- Line 2: Task + ANSI.hCursorDown IO.stderr 1 + ANSI.hSetCursorColumn IO.stderr 0 + ANSI.hClearLine IO.stderr + TIO.hPutStr IO.stderr <| "Task: " <> taskStr + + -- Line 3: Thread + ANSI.hCursorDown IO.stderr 1 + ANSI.hSetCursorColumn IO.stderr 0 + ANSI.hClearLine IO.stderr + TIO.hPutStr IO.stderr <| "Thread: " <> threadStr + + -- Line 4: Credits + ANSI.hCursorDown IO.stderr 1 + ANSI.hSetCursorColumn IO.stderr 0 + ANSI.hClearLine IO.stderr + TIO.hPutStr IO.stderr <| "Credits: $" <> str (printf "%.2f" statusCredits :: String) + + -- Line 5: Activity + 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 4 + IO.hFlush IO.stderr diff --git a/Omni/Agent/LogTest.hs b/Omni/Agent/LogTest.hs new file mode 100644 index 0000000..97b558d --- /dev/null +++ b/Omni/Agent/LogTest.hs @@ -0,0 +1,74 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE NoImplicitPrelude #-} + +-- : out agent-log-test +module Omni.Agent.LogTest where + +import Alpha +import Omni.Agent.Log +import qualified Omni.Test as Test + +main :: IO () +main = Test.run tests + +tests :: Test.Tree +tests = + Test.group + "Omni.Agent.Log" + [ Test.unit "Parse LogEntry" testParse, + Test.unit "Format LogEntry" testFormat + ] + +testParse :: IO () +testParse = do + let json = "{\"message\": \"executing 1 tools in 1 batch(es)\", \"batches\": [[\"grep\"]]}" + let expected = + LogEntry + { leMessage = Just "executing 1 tools in 1 batch(es)", + leLevel = Nothing, + leToolName = Nothing, + leBatches = Just [["grep"]], + leMethod = Nothing, + lePath = Nothing + } + parseLine json @?= Just expected + +testFormat :: IO () +testFormat = do + let entry = + LogEntry + { leMessage = Just "executing 1 tools in 1 batch(es)", + leLevel = Nothing, + leToolName = Nothing, + leBatches = Just [["grep"]], + leMethod = Nothing, + lePath = Nothing + } + -- Expect NO emoji + formatLogEntry entry @?= Just "THOUGHT: Planning tool execution (grep)" + + let entry2 = + LogEntry + { leMessage = Just "some random log", + leLevel = Nothing, + leToolName = Nothing, + leBatches = Nothing, + leMethod = Nothing, + lePath = Nothing + } + formatLogEntry entry2 @?= Nothing + + let entry3 = + LogEntry + { leMessage = Just "some error", + leLevel = Just "error", + leToolName = Nothing, + leBatches = Nothing, + leMethod = Nothing, + lePath = Nothing + } + -- Expect NO emoji + formatLogEntry entry3 @?= Just "ERROR: some error" + +(@?=) :: (Eq a, Show a) => a -> a -> IO () +(@?=) = (Test.@?=) diff --git a/Omni/Agent/WORKER_AGENT_GUIDE.md b/Omni/Agent/WORKER_AGENT_GUIDE.md index af81bb0..e832a2a 100644 --- a/Omni/Agent/WORKER_AGENT_GUIDE.md +++ b/Omni/Agent/WORKER_AGENT_GUIDE.md @@ -55,13 +55,10 @@ task update t-123 in-progress 2. **Check for Unmerged Work**: Look for dependencies that have existing branches (e.g., `task/t-parent-id`) which are NOT yet merged into `live`. 3. **Select Base**: * If you find an unmerged dependency branch, check it out: `git checkout task/t-parent-id`. - * Otherwise, start from fresh live code: `git checkout omni-worker-1` (which tracks `live`). + * Otherwise, start from fresh live code: `git checkout -b task/t-123 live`. -4. **Create/Checkout Feature Branch**: - ```bash - # Try to switch to existing branch, otherwise create new one - git checkout task/t-123 || git checkout -b task/t-123 - ``` +4. **Implement**: + (Proceed to implementation) ### Step 4: Implement @@ -70,29 +67,35 @@ task update t-123 in-progress 3. **Run Tests**: `bild --test Omni/YourNamespace.hs` ### Step 5: Submit for Review - -1. **Commit Implementation**: - ```bash - git add . - git commit -m "feat: implement t-123" - ``` - -2. **Signal Review Readiness**: - The Planner checks the `omni-worker-X` branch for status updates. You must switch back and update the status there. - - ```bash - # Switch to base branch - git checkout omni-worker-1 - - # Sync to get latest state (and any manual merges) - ./Omni/Agent/sync-tasks.sh - - # Mark task for review - task update t-123 review - - # Commit this status change to the worker branch - ./Omni/Agent/sync-tasks.sh --commit - ``` + + 1. **Update Status and Commit**: + Bundle the task status update with your implementation to keep history clean. + + ```bash + # 1. Mark task for review (updates .tasks/tasks.jsonl) + task update t-123 review + + # 2. Commit changes + task update + git add . + git commit -m "feat: implement t-123" + ``` + + 2. **Signal Review Readiness**: + Update the worker branch to signal the planner. + + ```bash + # Switch to base branch + git checkout omni-worker-1 + + # Sync to get latest state + ./Omni/Agent/sync-tasks.sh + + # Ensure the task is marked review here too (for harvest visibility) + task update t-123 review + + # Commit this status change to the worker branch + ./Omni/Agent/sync-tasks.sh --commit + ``` *Note: The Planner will now see 't-123' in 'Review' when it runs `harvest-tasks.sh`.* @@ -103,10 +106,14 @@ The Planner Agent (running in the main repo) will: 2. **Find Reviews**: Run `task list --status=review`. 3. **Review Code**: * Check out the feature branch: `git checkout task/t-123`. + * **Rebase onto Live**: Ensure the branch is up-to-date and linear. + ```bash + git rebase live + ``` * Run tests and review code. 4. **Merge**: * `git checkout live` - * `git merge task/t-123` + * `git merge task/t-123` (This will now be a fast-forward or clean merge) 5. **Complete**: * `task update t-123 done` * `git commit -am "task: t-123 done"` diff --git a/Omni/Agent/Worker.hs b/Omni/Agent/Worker.hs new file mode 100644 index 0000000..1cc0b8d --- /dev/null +++ b/Omni/Agent/Worker.hs @@ -0,0 +1,252 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE NoImplicitPrelude #-} + +-- : out omni-agent-worker +module Omni.Agent.Worker where + +import Alpha +import qualified Data.Text as Text +import qualified Data.Text.IO as TIO +import qualified Omni.Agent.Core as Core +import qualified Omni.Agent.Git as Git +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 +import System.FilePath ((</>)) +import qualified System.IO as IO +import qualified System.Process as Process + +start :: Core.Worker -> IO () +start worker = do + 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 + + 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). + Git.syncWithLive repo + + -- Sync tasks database (import from live) + -- Since we rebased, .tasks/tasks.jsonl should be up to date with live. + -- But we might need to consolidate if there are merge artifacts (not likely with rebase). + -- The bash script calls ./Omni/Agent/sync-tasks.sh which calls 'task import'. + -- Here we rely on 'task loadTasks' reading the file. + -- But 'syncWithLive' already updated the file from git. + + -- Find ready work + readyTasks <- TaskCore.getReadyTasks + case readyTasks of + [] -> do + AgentLog.updateActivity "No work found, sleeping..." + threadDelay (60 * 1000000) -- 60 seconds + loop worker + (task : _) -> do + processTask worker task + loop worker + +processTask :: Core.Worker -> TaskCore.Task -> IO () +processTask worker task = do + let repo = Core.workerPath worker + let tid = TaskCore.taskId task + + AgentLog.update (\s -> s {AgentLog.statusTask = Just tid}) + AgentLog.updateActivity ("Claiming task " <> tid) + + -- Claim task + TaskCore.updateTaskStatus tid TaskCore.InProgress [] + + -- Commit claim locally + Git.commit repo ("task: claim " <> tid) + + -- Prepare branch + let taskBranch = "task/" <> tid + currentBranch <- Git.getCurrentBranch repo + if currentBranch == taskBranch + then AgentLog.log ("Resuming branch " <> taskBranch) + else do + exists <- Git.branchExists repo taskBranch + if exists + then do + 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 + AgentLog.log ("Basing " <> taskBranch <> " on " <> baseBranch) + Git.checkout repo baseBranch + else AgentLog.log ("Basing " <> taskBranch <> " on live") + + Git.createBranch repo taskBranch + + -- Run Amp + AgentLog.updateActivity "Running Amp agent..." + (exitCode, output) <- runAmp repo task + + case exitCode of + Exit.ExitSuccess -> do + AgentLog.log "Agent finished successfully" + + -- Update status to Review (bundled with feature commit) + TaskCore.updateTaskStatus tid TaskCore.Review [] + + -- Commit changes + -- We use the agent's output as the extended commit description + let summary = Text.strip output + let commitMsg = "feat: implement " <> tid <> "\n\n" <> summary + Git.commit repo commitMsg + + -- Submit for review + AgentLog.updateActivity "Submitting for review..." + + -- Switch back to worker base + let base = Core.workerName worker + Git.checkout repo base + + -- Sync again + Git.syncWithLive repo + + -- 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 + 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, Text) +runAmp repo task = do + let prompt = + "You are a Worker Agent.\n" + <> "Your goal is to implement the following task:\n\n" + <> formatTask task + <> "\n\nINSTRUCTIONS:\n" + <> "1. Analyze the codebase (use finder/Grep) to understand where to make changes.\n" + <> "2. Implement the changes by editing files.\n" + <> "3. Run tests to verify your work (e.g., 'bild --test Omni/Namespace').\n" + <> "4. Fix any errors found during testing.\n" + <> "5. Do NOT update the task status or manage git branches (the system handles that).\n" + <> "6. Do NOT run 'git commit'. The system will commit your changes automatically.\n" + <> "7. When finished and tested, exit.\n\n" + <> "Context:\n" + <> "- You are working in '" + <> Text.pack repo + <> "'.\n" + <> "- The task is in namespace '" + <> fromMaybe "root" (TaskCore.taskNamespace task) + <> "'.\n" + + Directory.createDirectoryIfMissing True (repo </> "_/llm") + let logPath = repo </> "_/llm/amp.log" + + -- Ensure log file is empty/exists + IO.writeFile logPath "" + + -- Read AGENTS.md + agentsMd <- + fmap (fromMaybe "") <| do + exists <- Directory.doesFileExist (repo </> "AGENTS.md") + if exists + then Just </ readFile (repo </> "AGENTS.md") + else pure Nothing + + let fullPrompt = + prompt + <> "\n\nREPOSITORY GUIDELINES (AGENTS.md):\n" + <> agentsMd + + -- Monitor log file + tidLog <- forkIO (monitorLog logPath) + + -- Assume amp is in PATH + let args = ["--log-level", "debug", "--log-file", "_/llm/amp.log", "--dangerously-allow-all", "-x", Text.unpack fullPrompt] + + let cp = (Process.proc "amp" args) {Process.cwd = Just repo} + (exitCode, out, _err) <- Process.readCreateProcessWithExitCode cp "" + + -- Cleanup + killThread tidLog + + pure (exitCode, Text.pack out) + +formatTask :: TaskCore.Task -> Text +formatTask t = + "Task: " + <> TaskCore.taskId t + <> "\n" + <> "Title: " + <> TaskCore.taskTitle t + <> "\n" + <> "Type: " + <> Text.pack (show (TaskCore.taskType t)) + <> "\n" + <> "Status: " + <> Text.pack (show (TaskCore.taskStatus t)) + <> "\n" + <> "Priority: " + <> Text.pack (show (TaskCore.taskPriority t)) + <> "\n" + <> maybe "" (\p -> "Parent: " <> p <> "\n") (TaskCore.taskParent t) + <> maybe "" (\ns -> "Namespace: " <> ns <> "\n") (TaskCore.taskNamespace t) + <> "Created: " + <> Text.pack (show (TaskCore.taskCreatedAt t)) + <> "\n" + <> "Updated: " + <> Text.pack (show (TaskCore.taskUpdatedAt t)) + <> "\n" + <> maybe "" (\d -> "Description:\n" <> d <> "\n\n") (TaskCore.taskDescription t) + <> (if null (TaskCore.taskDependencies t) then "" else "\nDependencies:\n" <> Text.unlines (map formatDep (TaskCore.taskDependencies t))) + where + formatDep dep = " - " <> TaskCore.depId dep <> " [" <> Text.pack (show (TaskCore.depType dep)) <> "]" + +findBaseBranch :: FilePath -> TaskCore.Task -> IO Text +findBaseBranch repo task = do + let deps = TaskCore.taskDependencies task + -- Filter for blocking dependencies + let blockingDeps = filter (\d -> TaskCore.depType d == TaskCore.Blocks || TaskCore.depType d == TaskCore.ParentChild) deps + + -- Check if any have unmerged branches + candidates <- + flip filterM blockingDeps <| \dep -> do + let branch = "task/" <> TaskCore.depId dep + exists <- Git.branchExists repo branch + if exists + then do + merged <- Git.isMerged repo branch "live" + pure (not merged) + else pure False + + case candidates of + (candidate : _) -> pure ("task/" <> TaskCore.depId candidate) + [] -> pure "live" + +monitorLog :: FilePath -> IO () +monitorLog path = do + -- Wait for file to exist + waitForFile path + + IO.withFile path IO.ReadMode <| \h -> do + IO.hSetBuffering h IO.LineBuffering + forever <| do + eof <- IO.hIsEOF h + if eof + then threadDelay 100000 -- 0.1s + else do + line <- TIO.hGetLine h + AgentLog.processLogLine line + +waitForFile :: FilePath -> IO () +waitForFile p = do + e <- Directory.doesFileExist p + if e then pure () else threadDelay 100000 >> waitForFile p diff --git a/Omni/Agent/harvest-tasks.sh b/Omni/Agent/harvest-tasks.sh index 282beab..44c2322 100755 --- a/Omni/Agent/harvest-tasks.sh +++ b/Omni/Agent/harvest-tasks.sh @@ -45,7 +45,14 @@ if [ "$UPDATED" -eq 1 ]; then # Commit if there are changes if [[ -n $(git status --porcelain .tasks/tasks.jsonl) ]]; then git add .tasks/tasks.jsonl - git commit -m "task: harvest updates from workers" + + LAST_MSG=$(git log -1 --pretty=%s) + if [[ "$LAST_MSG" == "task: harvest updates from workers" ]]; then + echo "Squashing with previous harvest commit..." + git commit --amend --no-edit + else + git commit -m "task: harvest updates from workers" + fi echo "Success: Task database updated and committed." else echo "No effective changes found." diff --git a/Omni/Agent/monitor.sh b/Omni/Agent/monitor.sh new file mode 100755 index 0000000..1626354 --- /dev/null +++ b/Omni/Agent/monitor.sh @@ -0,0 +1,29 @@ +#!/usr/bin/env bash +# Omni/Agent/monitor.sh +# Monitor the logs of a worker agent +# Usage: ./Omni/Agent/monitor.sh [worker-name] + +WORKER="${1:-omni-worker-1}" +REPO_ROOT="$(git rev-parse --show-toplevel)" +WORKER_DIR="$REPO_ROOT/../$WORKER" + +if [ ! -d "$WORKER_DIR" ]; then + echo "Error: Worker directory '$WORKER_DIR' not found." + echo "Usage: $0 [worker-name]" + exit 1 +fi + +LOG_FILE="$WORKER_DIR/_/llm/amp.log" + +echo "Monitoring worker: $WORKER" +echo "Watching log: $LOG_FILE" +echo "---------------------------------------------------" + +# Wait for log file to appear +while [ ! -f "$LOG_FILE" ]; do + echo "Waiting for log file to be created..." + sleep 2 +done + +# Tail the log file +tail -f "$LOG_FILE" diff --git a/Omni/Agent/setup-worker.sh b/Omni/Agent/setup-worker.sh index 28c29b1..42b7fc9 100755 --- a/Omni/Agent/setup-worker.sh +++ b/Omni/Agent/setup-worker.sh @@ -22,3 +22,10 @@ if [ -f "$REPO_ROOT/.envrc.local" ]; then echo "Copying .envrc.local..." cp "$REPO_ROOT/.envrc.local" "$WORKTREE_PATH/" fi + +# Configure git identity for the worker +echo "Configuring git identity for worker..." +git -C "$WORKTREE_PATH" config user.name "Omni Worker" +git -C "$WORKTREE_PATH" config user.email "bot@omni.agent" + +echo "Worker setup complete at $WORKTREE_PATH" diff --git a/Omni/Agent/start-worker.sh b/Omni/Agent/start-worker.sh index ad519a0..310ca56 100755 --- a/Omni/Agent/start-worker.sh +++ b/Omni/Agent/start-worker.sh @@ -34,157 +34,30 @@ if [ ! -x "$TASK_BIN" ]; then echo "Warning: Task binary not found at '$TASK_BIN'. Assuming it's in path or build it first." fi -echo "Starting Worker Agent Loop" -echo " Worker Path: $WORKER_PATH" -echo " Amp Binary: $AMP_BIN" -echo " Log File: $WORKER_PATH/_/llm/amp.log" -echo " Monitor: tail -f $WORKER_PATH/_/llm/amp.log" -echo " Press Ctrl+C to stop." - -# Function to sync tasks safely -sync_tasks() { - "$MAIN_REPO/Omni/Agent/sync-tasks.sh" "$@" -} +# Ensure worker has local task and agent binaries +mkdir -p "$WORKER_PATH/_/bin" -cd "$WORKER_PATH" - -# 3. The Worker Loop -while true; do - echo "----------------------------------------------------------------" - echo "$(date): Syncing and checking for work..." - - # A. Sync with Live - # We use 'git rebase' to keep history linear - # Force checkout to clean up any untracked files from previous runs - git checkout -f omni-worker-1 >/dev/null 2>&1 - - # Rebase directly on local live branch (shared repo) - if ! git rebase live >/dev/null 2>&1; then - echo "Warning: Rebase conflict at start of loop. Aborting rebase and proceeding with local state." - git rebase --abort || true - fi - - # B. Sync Tasks - sync_tasks - - # C. Find Ready Work - # We use jq to parse the first task - # Note: task ready --json returns an array [...] - TASK_JSON=$("$TASK_BIN" ready --json 2>/dev/null | jq -r '.[0] // empty') - - if [ -z "$TASK_JSON" ]; then - echo "$(date): No ready tasks. Sleeping for 60s..." - sleep 60 - continue - fi - - TASK_ID=$(echo "$TASK_JSON" | jq -r '.taskId') - TASK_TITLE=$(echo "$TASK_JSON" | jq -r '.taskTitle') - TASK_NS=$(echo "$TASK_JSON" | jq -r '.taskNamespace // "root"') - - # Verify against live state to prevent re-claiming completed work - # (This handles cases where local 'InProgress' timestamp > live 'Review' timestamp due to retries) - git show live:.tasks/tasks.jsonl > .tasks/temp-live-tasks.jsonl 2>/dev/null - LIVE_TASK=$(grep "\"taskId\":\"$TASK_ID\"" .tasks/temp-live-tasks.jsonl || true) - LIVE_STATUS=$(echo "$LIVE_TASK" | jq -r '.taskStatus // empty') - rm -f .tasks/temp-live-tasks.jsonl - - if [[ "$LIVE_STATUS" == "Review" ]] || [[ "$LIVE_STATUS" == "Done" ]]; then - echo "Task $TASK_ID is already $LIVE_STATUS in live. Skipping and updating local state." - # Force update local DB to match live for this task - # We can't easily use 'task update' because it updates timestamp. - # Instead, we just rely on the loop continuing and hopefully 'task import' eventually winning - # if we stop touching it. Or we could force import again. - sleep 60 - continue - fi - - echo "$(date): Claiming task $TASK_ID: $TASK_TITLE" - - # D. Claim Task - "$TASK_BIN" update "$TASK_ID" in-progress >/dev/null - sync_tasks --commit >/dev/null - - # E. Prepare Branch - BRANCH_NAME="task/$TASK_ID" - if git show-ref --verify --quiet "refs/heads/$BRANCH_NAME"; then - echo "Resuming existing branch $BRANCH_NAME" - # Force checkout to overwrite untracked files (like .tasks/counters.jsonl) - # that may have been generated by sync tools but are tracked in the branch. - git checkout -f "$BRANCH_NAME" >/dev/null - else - echo "Creating new branch $BRANCH_NAME" - git checkout -b "$BRANCH_NAME" >/dev/null - fi - - # F. Execute Agent - echo "Launching Amp to implement task..." - - TASK_DETAILS=$("$TASK_BIN" show "$TASK_ID") - - # We construct a specific prompt for the agent - PROMPT="You are a Worker Agent. -Your goal is to implement the following task: +echo "Building 'task' in worker..." +if ! (cd "$WORKER_PATH" && bild Omni/Task.hs); then + echo "Error: Failed to build 'task' in worker directory." + exit 1 +fi -$TASK_DETAILS +echo "Building 'agent' in worker..." +if ! (cd "$WORKER_PATH" && bild Omni/Agent.hs); then + echo "Error: Failed to build 'agent' in worker directory." + exit 1 +fi -INSTRUCTIONS: -1. Analyze the codebase (use finder/Grep) to understand where to make changes. -2. Implement the changes by editing files. -3. Run tests to verify your work (e.g., 'bild --test Omni/Namespace'). -4. Fix any errors found during testing. -5. Do NOT update the task status or manage git branches (the system handles that). -6. When finished and tested, exit. +echo "Starting Worker Agent (Haskell)" +echo " Worker Path: $WORKER_PATH" +echo " Agent Bin: $WORKER_PATH/_/bin/agent" +echo " Log File: $WORKER_PATH/_/llm/amp.log" +echo " Monitor: ./Omni/Agent/monitor.sh $TARGET" +echo " Press Ctrl+C to stop." -Context: -- You are working in '$WORKER_PATH'. -- The task is in namespace '$TASK_NS'. -" +# Add amp to PATH so the agent can find it +export PATH="$MAIN_REPO/node_modules/.bin:$PATH" - mkdir -p _/llm - "$AMP_BIN" --log-level debug --log-file "_/llm/amp.log" --dangerously-allow-all -x "$PROMPT" - - AGENT_EXIT_CODE=$? - - if [ $AGENT_EXIT_CODE -eq 0 ]; then - echo "Agent finished successfully." - - # G. Submit Work - if [ -n "$(git status --porcelain)" ]; then - echo "Committing changes..." - git add . - git commit -m "feat: implement $TASK_ID" || true - else - echo "No changes to commit." - fi - - echo "Submitting for review..." - # Switch back to base - git checkout omni-worker-1 >/dev/null - - # Sync again (rebase on latest live) - # If rebase fails, we MUST abort to avoid leaving the repo in a broken state - if ! git rebase live >/dev/null 2>&1; then - echo "Warning: Rebase conflict. Aborting rebase and proceeding with local state." - git rebase --abort || true - fi - - sync_tasks - - # Update status - echo "Marking task $TASK_ID as Review..." - if "$TASK_BIN" update "$TASK_ID" review; then - sync_tasks --commit >/dev/null - echo "Task $TASK_ID submitted for review." - else - echo "Error: Failed to update task status to Review." - fi - - else - echo "Agent failed (exit code $AGENT_EXIT_CODE). Sleeping for 10s before retrying..." - sleep 10 - fi - - echo "Cooldown..." - sleep 5 -done +# Run the agent +"$WORKER_PATH/_/bin/agent" start "$TARGET" --path "$WORKER_PATH" |
