diff options
Diffstat (limited to 'Omni/Agent/Worker.hs')
| -rw-r--r-- | Omni/Agent/Worker.hs | 665 |
1 files changed, 665 insertions, 0 deletions
diff --git a/Omni/Agent/Worker.hs b/Omni/Agent/Worker.hs new file mode 100644 index 0000000..d6afb73 --- /dev/null +++ b/Omni/Agent/Worker.hs @@ -0,0 +1,665 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE NoImplicitPrelude #-} + +module Omni.Agent.Worker + ( start, + buildFullPrompt, + selectModel, + selectCostByComplexity, + ) +where + +import Alpha +import qualified Data.Aeson as Aeson +import qualified Data.Aeson.Key as AesonKey +import qualified Data.ByteString.Lazy as BSL +import Data.IORef (modifyIORef', newIORef, readIORef) +import qualified Data.List as List +import qualified Data.Text as Text +import qualified Data.Text.Encoding as TE +import qualified Data.Time +import qualified Omni.Agent.Core as Core +import qualified Omni.Agent.Engine as Engine +import qualified Omni.Agent.Provider as Provider +import qualified Omni.Agent.Status as AgentStatus +import qualified Omni.Agent.Tools as Tools +import qualified Omni.Fact as Fact +import qualified Omni.Task.Core as TaskCore +import qualified System.Directory as Directory +import qualified System.Environment as Env +import qualified System.Exit as Exit +import System.FilePath ((</>)) +import qualified System.Process as Process + +start :: Core.Worker -> Maybe Text -> IO () +start worker maybeTaskId = do + if Core.workerQuiet worker + then putText ("[worker] Starting for " <> Core.workerName worker) + else do + AgentStatus.init (Core.workerName worker) + AgentStatus.log ("[worker] Starting for " <> Core.workerName worker) + case maybeTaskId of + Just tid -> logMsg worker ("[worker] Target task: " <> tid) + Nothing -> logMsg worker "[worker] No specific task, will pick from ready queue" + runOnce worker maybeTaskId + +-- | Log message respecting quiet mode +logMsg :: Core.Worker -> Text -> IO () +logMsg worker msg = + if Core.workerQuiet worker + then putText msg + else AgentStatus.log msg + +-- | Convert key-value pairs to JSON metadata string +toMetadata :: [(Text, Text)] -> Text +toMetadata pairs = + let obj = Aeson.object [(AesonKey.fromText k, Aeson.String v) | (k, v) <- pairs] + in TE.decodeUtf8 (BSL.toStrict (Aeson.encode obj)) + +-- | Format guardrail result for logging +formatGuardrailResult :: Engine.GuardrailResult -> Text +formatGuardrailResult Engine.GuardrailOk = "OK" +formatGuardrailResult (Engine.GuardrailCostExceeded actual limit) = + "Cost exceeded: " <> tshow actual <> " cents (limit: " <> tshow limit <> ")" +formatGuardrailResult (Engine.GuardrailTokensExceeded actual limit) = + "Tokens exceeded: " <> tshow actual <> " (limit: " <> tshow limit <> ")" +formatGuardrailResult (Engine.GuardrailDuplicateToolCalls tool count) = + "Duplicate tool calls: " <> tool <> " called " <> tshow count <> " times" +formatGuardrailResult (Engine.GuardrailTestFailures count) = + "Test failures: " <> tshow count <> " failures" +formatGuardrailResult (Engine.GuardrailEditFailures count) = + "Edit failures: " <> tshow count <> " 'old_str not found' errors" + +runOnce :: Core.Worker -> Maybe Text -> IO () +runOnce worker maybeTaskId = do + -- Find work + targetTask <- case maybeTaskId of + Just tid -> do + TaskCore.findTask tid </ TaskCore.loadTasks + Nothing -> do + readyTasks <- TaskCore.getReadyTasks + case readyTasks of + [] -> pure Nothing + (task : _) -> pure (Just task) + + case targetTask of + Nothing -> do + case maybeTaskId of + Just tid -> do + unless (Core.workerQuiet worker) <| AgentStatus.updateActivity ("Task " <> tid <> " not found.") + logMsg worker ("[worker] Task " <> tid <> " not found.") + Nothing -> do + unless (Core.workerQuiet worker) <| AgentStatus.updateActivity "No work found." + logMsg worker "[worker] No ready tasks found." + Just task -> do + processTask worker task + +processTask :: Core.Worker -> TaskCore.Task -> IO () +processTask worker task = do + let repo = Core.workerPath worker + let tid = TaskCore.taskId task + let quiet = Core.workerQuiet worker + let say = logMsg worker + + unless quiet <| AgentStatus.update (\s -> s {AgentStatus.statusTask = Just tid}) + say ("[worker] Claiming task " <> tid) + + -- Claim task + TaskCore.logActivity tid TaskCore.Claiming Nothing + TaskCore.updateTaskStatusWithActor tid TaskCore.InProgress [] TaskCore.Junior + say "[worker] Status -> InProgress" + + -- Run agent with timing + startTime <- Data.Time.getCurrentTime + activityId <- TaskCore.logActivityWithMetrics tid TaskCore.Running Nothing Nothing (Just startTime) Nothing Nothing Nothing + + say "[worker] Starting engine..." + engineResult <- runWithEngine worker repo task + + endTime <- Data.Time.getCurrentTime + + -- Update the activity record with metrics (convert Double to Int by rounding) + let costCents = case engineResult of + EngineSuccess _ c -> c + EngineGuardrailViolation _ c -> c + EngineError _ c -> c + TaskCore.updateActivityMetrics activityId Nothing (Just endTime) (Just (round costCents)) Nothing + + case engineResult of + EngineSuccess output _ -> do + say "[worker] Agent completed successfully" + TaskCore.logActivity tid TaskCore.Reviewing Nothing + say "[worker] Running formatters..." + _ <- runFormatters repo + + -- Try to commit (this runs git hooks which may fail) + let commitMsg = formatCommitMessage task output + say "[worker] Attempting commit..." + commitResult <- tryCommit repo commitMsg + + case commitResult of + CommitFailed commitErr -> do + say ("[worker] Commit failed: " <> commitErr) + + -- Save failure context and reopen task for retry + maybeCtx <- TaskCore.getRetryContext tid + let attempt = maybe 1 (\c -> TaskCore.retryAttempt c + 1) maybeCtx + + if attempt > 3 + then do + say "[worker] Task failed 3 times, needs human intervention" + TaskCore.logActivity tid TaskCore.Failed (Just (toMetadata [("reason", "max_retries_exceeded")])) + TaskCore.updateTaskStatusWithActor tid TaskCore.Open [] TaskCore.Junior + else do + let currentReason = "attempt " <> tshow attempt <> ": commit_failed: " <> commitErr + let accumulatedReason = case maybeCtx of + Nothing -> currentReason + Just ctx -> TaskCore.retryReason ctx <> "\n" <> currentReason + TaskCore.setRetryContext + TaskCore.RetryContext + { TaskCore.retryTaskId = tid, + TaskCore.retryOriginalCommit = "", + TaskCore.retryConflictFiles = [], + TaskCore.retryAttempt = attempt, + TaskCore.retryReason = accumulatedReason, + TaskCore.retryNotes = maybeCtx +> TaskCore.retryNotes + } + TaskCore.logActivity tid TaskCore.Retrying (Just (toMetadata [("attempt", tshow attempt)])) + TaskCore.updateTaskStatusWithActor tid TaskCore.Open [] TaskCore.Junior + say ("[worker] Task reopened (attempt " <> tshow attempt <> "/3)") + NoChanges -> do + -- No changes = task already implemented, mark as Done + say "[worker] No changes to commit - task already done" + TaskCore.clearRetryContext tid + TaskCore.logActivity tid TaskCore.Completed (Just (toMetadata [("result", "no_changes")])) + TaskCore.updateTaskStatusWithActor tid TaskCore.Done [] TaskCore.Junior + say ("[worker] ✓ Task " <> tid <> " -> Done (no changes)") + unless quiet <| AgentStatus.update (\s -> s {AgentStatus.statusTask = Nothing}) + CommitSuccess -> do + -- Commit succeeded, set to Review + TaskCore.logActivity tid TaskCore.Completed (Just (toMetadata [("result", "committed")])) + TaskCore.updateTaskStatusWithActor tid TaskCore.Review [] TaskCore.Junior + say ("[worker] ✓ Task " <> tid <> " -> Review") + unless quiet <| AgentStatus.update (\s -> s {AgentStatus.statusTask = Nothing}) + EngineGuardrailViolation errMsg _ -> do + say ("[worker] Guardrail violation: " <> errMsg) + TaskCore.logActivity tid TaskCore.Failed (Just (toMetadata [("reason", "guardrail_violation")])) + -- Add comment with guardrail details + _ <- TaskCore.addComment tid errMsg TaskCore.Junior + -- Set to NeedsHelp so human can review + TaskCore.updateTaskStatusWithActor tid TaskCore.NeedsHelp [] TaskCore.Junior + say ("[worker] Task " <> tid <> " -> NeedsHelp (guardrail violation)") + unless quiet <| AgentStatus.update (\s -> s {AgentStatus.statusTask = Nothing}) + EngineError errMsg _ -> do + say ("[worker] Engine error: " <> errMsg) + TaskCore.logActivity tid TaskCore.Failed (Just (toMetadata [("reason", "engine_error")])) + -- Don't set back to Open here - leave in InProgress for debugging + say "[worker] Task left in InProgress (engine failure)" + +-- | Run lint --fix to format and fix lint issues +runFormatters :: FilePath -> IO (Either Text ()) +runFormatters repo = do + let cmd = (Process.proc "lint" ["--fix"]) {Process.cwd = Just repo} + (code, _, _) <- Process.readCreateProcessWithExitCode cmd "" + case code of + Exit.ExitSuccess -> pure (Right ()) + Exit.ExitFailure _ -> pure (Right ()) -- lint --fix may exit non-zero but still fix things + +data CommitResult = CommitSuccess | NoChanges | CommitFailed Text + deriving (Show, Eq) + +-- | Try to commit, returning result +tryCommit :: FilePath -> Text -> IO CommitResult +tryCommit repo msg = do + -- Stage all changes + let addCmd = (Process.proc "git" ["add", "."]) {Process.cwd = Just repo} + (addCode, _, addErr) <- Process.readCreateProcessWithExitCode addCmd "" + case addCode of + Exit.ExitFailure _ -> pure <| CommitFailed (Text.pack addErr) + Exit.ExitSuccess -> do + -- Check for changes + let checkCmd = (Process.proc "git" ["diff", "--cached", "--quiet"]) {Process.cwd = Just repo} + (checkCode, _, _) <- Process.readCreateProcessWithExitCode checkCmd "" + case checkCode of + Exit.ExitSuccess -> pure NoChanges + Exit.ExitFailure 1 -> do + -- There are changes, commit them + let commitCmd = (Process.proc "git" ["commit", "-m", Text.unpack msg]) {Process.cwd = Just repo} + (commitCode, _, commitErr) <- Process.readCreateProcessWithExitCode commitCmd "" + case commitCode of + Exit.ExitSuccess -> pure CommitSuccess + Exit.ExitFailure _ -> pure <| CommitFailed (Text.pack commitErr) + Exit.ExitFailure c -> pure <| CommitFailed ("git diff failed with code " <> tshow c) + +data EngineResult + = EngineSuccess Text Double -- output, cost + | EngineGuardrailViolation Text Double -- error message, cost + | EngineError Text Double -- error message, cost + +-- | Run task using native Engine +-- Returns engine result with output/error and cost +runWithEngine :: Core.Worker -> FilePath -> TaskCore.Task -> IO EngineResult +runWithEngine worker repo task = do + -- Read API key from environment + maybeApiKey <- Env.lookupEnv "OPENROUTER_API_KEY" + case maybeApiKey of + Nothing -> pure (EngineError "OPENROUTER_API_KEY not set" 0) + Just apiKey -> do + -- Check for retry context + maybeRetry <- TaskCore.getRetryContext (TaskCore.taskId task) + + -- Get progress from database (checkpoint events from previous sessions) + progressContent <- TaskCore.getProgressSummary (TaskCore.taskId task) + + -- Build the full prompt + let ns = fromMaybe "." (TaskCore.taskNamespace task) + let basePrompt = buildBasePrompt ns repo + + -- Add progress context if present + let progressPrompt = buildProgressPrompt progressContent + + -- Add retry context if present + let retryPrompt = buildRetryPrompt maybeRetry + + let prompt = basePrompt <> progressPrompt <> retryPrompt + + -- Read AGENTS.md + agentsMd <- + fmap (fromMaybe "") <| do + exists <- Directory.doesFileExist (repo </> "AGENTS.md") + if exists + then Just </ readFile (repo </> "AGENTS.md") + else pure Nothing + + -- Get relevant facts from the knowledge base + relevantFacts <- getRelevantFacts task + let factsSection = formatFacts relevantFacts + + -- Build system prompt + let systemPrompt = + prompt + <> "\n\nREPOSITORY GUIDELINES (AGENTS.md):\n" + <> agentsMd + <> factsSection + + -- Build user prompt from task comments + let userPrompt = formatTask task + + -- Select model based on task complexity (simple heuristic) + let model = selectModel task + + -- Generate session ID for event logging + sessionId <- TaskCore.generateSessionId + let tid = TaskCore.taskId task + + -- Helper to log events to DB + -- For text content, store as-is; for structured data, JSON-encode + let logJuniorEvent eventType content = TaskCore.insertAgentEvent tid sessionId eventType content TaskCore.Junior + logJuniorJson eventType value = do + let contentJson = TE.decodeUtf8 (BSL.toStrict (Aeson.encode value)) + TaskCore.insertAgentEvent tid sessionId eventType contentJson TaskCore.Junior + logSystemEvent eventType content = TaskCore.insertAgentEvent tid sessionId eventType content TaskCore.System + + -- Build Engine config with callbacks + totalCostRef <- newIORef (0 :: Double) + let quiet = Core.workerQuiet worker + sayLog msg = if quiet then putText msg else AgentStatus.log msg + engineCfg = + Engine.EngineConfig + { Engine.engineLLM = + Engine.defaultLLM + { Engine.llmApiKey = Text.pack apiKey + }, + Engine.engineOnCost = \tokens cost -> do + modifyIORef' totalCostRef (+ cost) + sayLog <| "Cost: " <> tshow cost <> " cents (" <> tshow tokens <> " tokens)" + logJuniorJson "Cost" (Aeson.object [("tokens", Aeson.toJSON tokens), ("cents", Aeson.toJSON cost)]), + Engine.engineOnActivity = \activity -> do + sayLog <| "[engine] " <> activity, + Engine.engineOnToolCall = \toolName args -> do + sayLog <| "[tool] " <> toolName + logJuniorEvent "ToolCall" (toolName <> ": " <> args), + Engine.engineOnAssistant = \msg -> do + sayLog <| "[assistant] " <> Text.take 200 msg + logJuniorEvent "Assistant" msg, + Engine.engineOnToolResult = \toolName success output -> do + let statusStr = if success then "ok" else "failed" + sayLog <| "[result] " <> toolName <> " (" <> statusStr <> "): " <> Text.take 100 output + logJuniorEvent "ToolResult" output, + Engine.engineOnComplete = do + sayLog "[engine] Complete" + logJuniorEvent "Complete" "", + Engine.engineOnError = \err -> do + sayLog <| "[error] " <> err + logJuniorEvent "Error" err, + Engine.engineOnGuardrail = \guardrailResult -> do + let guardrailMsg = formatGuardrailResult guardrailResult + contentJson = TE.decodeUtf8 (BSL.toStrict (Aeson.encode guardrailResult)) + sayLog <| "[guardrail] " <> guardrailMsg + logSystemEvent "Guardrail" contentJson + } + + -- Build Agent config with guardrails (scale cost by complexity) + let baseCost = selectCostByComplexity (TaskCore.taskComplexity task) + guardrails = + Engine.Guardrails + { Engine.guardrailMaxCostCents = baseCost, + Engine.guardrailMaxTokens = 2000000, + Engine.guardrailMaxDuplicateToolCalls = 30, + Engine.guardrailMaxTestFailures = 3, + Engine.guardrailMaxEditFailures = 5 + } + agentCfg = + Engine.AgentConfig + { Engine.agentModel = model, + Engine.agentTools = Tools.allTools, + Engine.agentSystemPrompt = systemPrompt, + Engine.agentMaxIterations = 100, + Engine.agentGuardrails = guardrails + } + + -- Run the agent with appropriate provider + result <- case Core.workerEngine worker of + Core.EngineOpenRouter -> Engine.runAgent engineCfg agentCfg userPrompt + Core.EngineOllama -> do + ollamaModel <- fromMaybe "llama3.1:8b" </ Env.lookupEnv "OLLAMA_MODEL" + let provider = Provider.defaultOllama (Text.pack ollamaModel) + Engine.runAgentWithProvider engineCfg provider agentCfg userPrompt + Core.EngineAmp -> pure (Left "Amp engine not yet implemented") + totalCost <- readIORef totalCostRef + + case result of + Left err -> + if "Guardrail: " `Text.isPrefixOf` err + then pure (EngineGuardrailViolation err totalCost) + else pure (EngineError ("Engine error: " <> err) totalCost) + Right agentResult -> do + let output = Engine.resultFinalMessage agentResult + pure (EngineSuccess output totalCost) + +-- | Build the base prompt for the agent +buildBasePrompt :: Text -> FilePath -> Text +buildBasePrompt ns repo = + "You are `jr`, an autonomous Senior Software Engineer. You are rigorous, efficient, and safety-conscious.\n" + <> "Your Goal: Complete the assigned task with **zero regressions**.\n\n" + <> "# The Workflow\n" + <> "Follow this 4-phase loop. Do not skip phases.\n\n" + <> "## Phase 1: Exploration (MANDATORY)\n" + <> "- NEVER edit immediately. Explore first.\n" + <> "- Use search_and_read to find code relevant to the task.\n" + <> "- Read the imports. Read the tests that cover this code.\n" + <> "- Understand the *callers* of a function before you modify it.\n\n" + <> "## Phase 2: Planning (for multi-file changes)\n" + <> "- If the task involves more than 2 files, plan the order of operations.\n" + <> "- Identify potential breaking changes (API shifts, import cycles).\n" + <> "- For refactors: copy code first, verify it works, then delete the original.\n\n" + <> "## Phase 3: Execution\n" + <> "- Make atomic changes. One logical edit per edit_file call.\n" + <> "- Use edit_file with sufficient context (5+ lines) to match uniquely.\n" + <> "- Do NOT update task status or manage git - the worker handles that.\n\n" + <> "## Phase 4: Verification\n" + <> "- Run 'bild --test " + <> ns + <> "' after your changes.\n" + <> "- 'bild --test' tests ALL dependencies transitively - run it ONCE, not per-file.\n" + <> "- Use 'lint --fix' to handle formatting (not hlint directly).\n" + <> "- If tests pass, STOP. Do not verify again, do not double-check.\n\n" + <> "# Tool Usage\n\n" + <> "Your tools: read_file, write_file, edit_file, run_bash, search_codebase, search_and_read.\n\n" + <> "## Efficient Reading (CRITICAL FOR BUDGET)\n" + <> "- Read files ONCE with large ranges (500+ lines), not many small 100-line chunks.\n" + <> "- WRONG: 10 separate read_file calls with 100-line ranges on the same file.\n" + <> "- RIGHT: 1-2 read_file calls with 500-1000 line ranges to cover the file.\n" + <> "- When you know the target file, use read_file directly with a path argument.\n" + <> "- WRONG: search_and_read across the whole repo when you know the file is Worker.py.\n" + <> "- RIGHT: read_file on Worker.py, or search_codebase with path='Worker.py'.\n" + <> "- search_and_read is for discovery when you DON'T know which file to look in.\n\n" + <> "## Efficient Editing\n" + <> "- Include enough context in old_str to match uniquely (usually 5+ lines).\n" + <> "- If edit_file fails with 'old_str not found', you are hallucinating the content.\n" + <> "- STOP. Call read_file on those exact lines to get fresh content. Then retry.\n" + <> "- After 3 failed edits on the same file, reconsider your approach.\n\n" + <> "## Cost Awareness\n" + <> "- Each tool call costs tokens. Large file writes are expensive.\n" + <> "- For refactors: plan all new files first, then write them in order.\n" + <> "- Don't write a file, then immediately read it back - you just wrote it!\n" + <> "- Monitor your progress: if you're on tool call 30+ and not close to done, simplify.\n\n" + <> "# Debugging\n" + <> "If 'bild' fails, do NOT guess the fix.\n" + <> "1. Read the error output carefully.\n" + <> "2. For type errors: read the definition of the types involved.\n" + <> "3. For import cycles: create a Types or Common module to break the cycle.\n" + <> "4. If tests fail 3 times on the same issue, STOP - the task will be marked for human review.\n\n" + <> "# Examples\n\n" + <> "## Example: Splitting a Module\n" + <> "1. search_and_read to understand the file structure\n" + <> "2. write_file NewModule.py (with extracted code + proper imports)\n" + <> "3. edit_file Original.py (remove moved code, add 'from NewModule import ...')\n" + <> "4. run_bash: bild --test <namespace>\n" + <> "5. Tests pass -> STOP\n\n" + <> "## Example: Fixing a Type Error\n" + <> "1. read_file Main.hs (lines around the error)\n" + <> "2. Identify: function expects Text but got String\n" + <> "3. edit_file Main.hs (add import, apply T.pack)\n" + <> "4. run_bash: bild --test <namespace>\n" + <> "5. Tests pass -> STOP\n\n" + <> "# Constraints\n" + <> "- You are autonomous. There is NO human to ask for clarification.\n" + <> "- Make reasonable decisions. If ambiguous, implement the straightforward interpretation.\n" + <> "- Aim to complete the task in under 50 tool calls.\n" + <> "- Guardrails will stop you if you exceed cost/token limits or make repeated mistakes.\n\n" + <> "# Context\n" + <> "- Working directory: " + <> Text.pack repo + <> "\n" + <> "- Namespace: " + <> ns + <> "\n" + +-- | Build progress context prompt +buildProgressPrompt :: Maybe Text -> Text +buildProgressPrompt Nothing = "" +buildProgressPrompt (Just progress) = + "\n\n## PROGRESS FROM PREVIOUS SESSIONS (from database)\n\n" + <> "This task has been worked on before. Here are the checkpoint notes:\n\n" + <> progress + <> "\n\n" + <> "IMPORTANT:\n" + <> "- Review these checkpoints to understand what's already done\n" + <> "- Do NOT repeat work that's already completed\n" + <> "- If the task appears complete, verify tests pass and exit\n\n" + +-- | Build retry context prompt +buildRetryPrompt :: Maybe TaskCore.RetryContext -> Text +buildRetryPrompt Nothing = "" +buildRetryPrompt (Just ctx) = + "\n\n## RETRY CONTEXT (IMPORTANT)\n\n" + <> "This task was previously attempted but failed. Attempt: " + <> tshow (TaskCore.retryAttempt ctx) + <> "/3\n" + <> "Reason: " + <> TaskCore.retryReason ctx + <> "\n\n" + <> ( if null (TaskCore.retryConflictFiles ctx) + then "" + else + "Conflicting files from previous attempt:\n" + <> Text.unlines (map (" - " <>) (TaskCore.retryConflictFiles ctx)) + <> "\n" + ) + <> "Original commit: " + <> TaskCore.retryOriginalCommit ctx + <> "\n\n" + <> maybe "" (\notes -> "## HUMAN NOTES/GUIDANCE\n\n" <> notes <> "\n\n") (TaskCore.retryNotes ctx) + <> "INSTRUCTIONS FOR RETRY:\n" + <> "- The codebase has changed since your last attempt\n" + <> "- Re-implement this task on top of the CURRENT codebase\n" + <> "- If there were merge conflicts, the conflicting files may have been modified by others\n" + <> "- Review the current state of those files before making changes\n" + +-- | Select model based on task complexity (1-5 scale) +-- Uses OpenRouter model identifiers for Claude models +selectModel :: TaskCore.Task -> Text +selectModel task = selectModelByComplexity (TaskCore.taskComplexity task) + +-- | Select model based on complexity level +selectModelByComplexity :: Maybe Int -> Text +selectModelByComplexity Nothing = "anthropic/claude-sonnet-4.5" +selectModelByComplexity (Just 1) = "anthropic/claude-haiku-4.5" +selectModelByComplexity (Just 2) = "anthropic/claude-haiku-4.5" +selectModelByComplexity (Just 3) = "anthropic/claude-sonnet-4.5" +selectModelByComplexity (Just 4) = "anthropic/claude-sonnet-4.5" +selectModelByComplexity (Just 5) = "anthropic/claude-opus-4.5" +selectModelByComplexity (Just _) = "anthropic/claude-sonnet-4.5" + +-- | Select cost guardrail based on complexity level (in cents) +-- Lower complexity = lower budget, higher complexity = more room for iteration +selectCostByComplexity :: Maybe Int -> Double +selectCostByComplexity Nothing = 200.0 +selectCostByComplexity (Just 1) = 50.0 +selectCostByComplexity (Just 2) = 100.0 +selectCostByComplexity (Just 3) = 200.0 +selectCostByComplexity (Just 4) = 400.0 +selectCostByComplexity (Just 5) = 600.0 +selectCostByComplexity (Just _) = 200.0 + +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" + <> (if Text.null (TaskCore.taskDescription t) then "" else "Description:\n" <> TaskCore.taskDescription t <> "\n\n") + <> formatDeps (TaskCore.taskDependencies t) + <> formatComments (TaskCore.taskComments t) + where + formatDeps [] = "" + formatDeps deps = "\nDependencies:\n" <> Text.unlines (map formatDep deps) + formatDep dep = " - " <> TaskCore.depId dep <> " [" <> Text.pack (show (TaskCore.depType dep)) <> "]" + formatComments [] = "" + formatComments cs = "\nComments/Notes:\n" <> Text.unlines (map formatComment cs) + formatComment c = " [" <> Text.pack (show (TaskCore.commentCreatedAt c)) <> "] " <> TaskCore.commentText c + +formatCommitMessage :: TaskCore.Task -> Text -> Text +formatCommitMessage task agentOutput = + let tid = TaskCore.taskId task + subject = cleanSubject (TaskCore.taskTitle task) + body = cleanBody agentOutput + in if Text.null body + then subject <> "\n\nTask-Id: " <> tid + else subject <> "\n\n" <> body <> "\n\nTask-Id: " <> tid + where + cleanSubject s = + let trailingPunct = ['.', ':', '!', '?', ',', ';', ' ', '-'] + stripped = Text.dropWhileEnd (`elem` trailingPunct) s + truncated = Text.take 72 stripped + noPunct = Text.dropWhileEnd (`elem` trailingPunct) truncated + capitalized = case Text.uncons noPunct of + Just (c, rest) -> Text.cons (toUpper c) rest + Nothing -> noPunct + in capitalized + + cleanBody :: Text -> Text + cleanBody output = + let stripped = Text.strip output + in if Text.null stripped + then "" + else + let lns = Text.lines stripped + cleaned = [Text.take 72 ln | ln <- lns] + in Text.intercalate "\n" cleaned + +-- | Get facts relevant to a task based on namespace/project +getRelevantFacts :: TaskCore.Task -> IO [TaskCore.Fact] +getRelevantFacts task = do + let namespace = fromMaybe "Omni" (TaskCore.taskNamespace task) + projectFacts <- Fact.getFactsByProject namespace + let sorted = List.sortBy (comparing (Down <. TaskCore.factConfidence)) projectFacts + pure (take 10 sorted) + +-- | Format facts for inclusion in the prompt +formatFacts :: [TaskCore.Fact] -> Text +formatFacts [] = "" +formatFacts facts = + Text.unlines + [ "\n\nKNOWLEDGE BASE FACTS:", + "(These are learned patterns/conventions from previous work)", + "" + ] + <> Text.unlines (map formatFact facts) + +-- | Format a single fact for the prompt +formatFact :: TaskCore.Fact -> Text +formatFact f = + "- " + <> TaskCore.factContent f + <> ( if null (TaskCore.factRelatedFiles f) + then "" + else " [" <> Text.intercalate ", " (TaskCore.factRelatedFiles f) <> "]" + ) + +-- | Build the full system prompt for a task without starting the agent. +-- This is useful for debugging/inspecting what the agent will be told. +buildFullPrompt :: TaskCore.Task -> IO Text +buildFullPrompt task = do + repo <- Directory.getCurrentDirectory + let ns = fromMaybe "." (TaskCore.taskNamespace task) + let basePrompt = buildBasePrompt ns repo + + maybeRetry <- TaskCore.getRetryContext (TaskCore.taskId task) + progressContent <- TaskCore.getProgressSummary (TaskCore.taskId task) + + let progressPrompt = buildProgressPrompt progressContent + let retryPrompt = buildRetryPrompt maybeRetry + let prompt = basePrompt <> progressPrompt <> retryPrompt + + agentsMd <- + fmap (fromMaybe "") <| do + exists <- Directory.doesFileExist (repo </> "AGENTS.md") + if exists + then Just </ readFile (repo </> "AGENTS.md") + else pure Nothing + + relevantFacts <- getRelevantFacts task + let factsSection = formatFacts relevantFacts + + let systemPrompt = + prompt + <> "\n\nREPOSITORY GUIDELINES (AGENTS.md):\n" + <> agentsMd + <> factsSection + + let model = selectModel task + let costBudget = selectCostByComplexity (TaskCore.taskComplexity task) + + pure + <| Text.unlines + [ "=== AGENT CONFIGURATION ===", + "Model: " <> model, + "Cost budget: " <> tshow costBudget <> " cents", + "", + "=== SYSTEM PROMPT ===", + systemPrompt, + "", + "=== USER PROMPT (task details) ===", + formatTask task + ] |
