{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE NoImplicitPrelude #-} module Omni.Task.Core where import Alpha import Data.Aeson (FromJSON, ToJSON, decode, encode) import qualified Data.ByteString.Lazy.Char8 as BLC import qualified Data.Text as T import qualified Data.Text.IO as TIO import Data.Time (UTCTime, diffTimeToPicoseconds, getCurrentTime, utctDayTime) import GHC.Generics () import System.Directory (createDirectoryIfMissing, doesFileExist) -- Core data types data Task = Task { taskId :: Text, taskTitle :: Text, taskType :: TaskType, taskParent :: Maybe Text, -- Parent epic ID taskNamespace :: Maybe Text, -- Optional namespace (e.g., "Omni/Task", "Biz/Cloud") taskStatus :: Status, taskDependencies :: [Dependency], -- List of dependencies with types taskCreatedAt :: UTCTime, taskUpdatedAt :: UTCTime } deriving (Show, Eq, Generic) data TaskType = Epic | WorkTask deriving (Show, Eq, Generic) data Status = Open | InProgress | Done deriving (Show, Eq, Generic) data Dependency = Dependency { depId :: Text, -- ID of the task this depends on depType :: DependencyType -- Type of dependency relationship } deriving (Show, Eq, Generic) data DependencyType = Blocks -- Hard dependency, blocks ready work queue | DiscoveredFrom -- Work discovered during other work | ParentChild -- Epic/subtask relationship | Related -- Soft relationship, doesn't block deriving (Show, Eq, Generic) instance ToJSON TaskType instance FromJSON TaskType instance ToJSON Status instance FromJSON Status instance ToJSON DependencyType instance FromJSON DependencyType instance ToJSON Dependency instance FromJSON Dependency instance ToJSON Task instance FromJSON Task -- Initialize the task database initTaskDb :: IO () initTaskDb = do createDirectoryIfMissing True ".tasks" exists <- doesFileExist ".tasks/tasks.jsonl" unless exists <| do TIO.writeFile ".tasks/tasks.jsonl" "" putText "Initialized task database at .tasks/tasks.jsonl" -- Generate a short ID using base62 encoding of timestamp generateId :: IO Text generateId = do now <- getCurrentTime -- Convert current time to microseconds since midnight let dayTime = utctDayTime now microseconds = diffTimeToPicoseconds dayTime `div` 1000000 -- Convert to base62 for shorter IDs encoded = toBase62 (fromIntegral microseconds) pure <| "t-" <> T.pack encoded -- Convert number to base62 (0-9, a-z, A-Z) toBase62 :: Integer -> String toBase62 0 = "0" toBase62 n = reverse <| go n where alphabet = ['0' .. '9'] ++ ['a' .. 'z'] ++ ['A' .. 'Z'] go 0 = [] go x = let (q, r) = x `divMod` 62 idx = fromIntegral r char = case drop idx alphabet of (c : _) -> c [] -> '0' -- Fallback (should never happen) in char : go q -- Load all tasks from JSONL file loadTasks :: IO [Task] loadTasks = do exists <- doesFileExist ".tasks/tasks.jsonl" if exists then do content <- TIO.readFile ".tasks/tasks.jsonl" let taskLines = T.lines content pure <| mapMaybe decodeTask taskLines else pure [] where decodeTask :: Text -> Maybe Task decodeTask line = if T.null line then Nothing else decode (BLC.pack <| T.unpack line) -- Save a single task (append to JSONL) saveTask :: Task -> IO () saveTask task = do let json = encode task BLC.appendFile ".tasks/tasks.jsonl" (json <> "\n") -- Create a new task createTask :: Text -> TaskType -> Maybe Text -> Maybe Text -> [Dependency] -> IO Task createTask title taskType parent namespace deps = do tid <- generateId now <- getCurrentTime let task = Task { taskId = tid, taskTitle = title, taskType = taskType, taskParent = parent, taskNamespace = namespace, taskStatus = Open, taskDependencies = deps, taskCreatedAt = now, taskUpdatedAt = now } saveTask task pure task -- Update task status updateTaskStatus :: Text -> Status -> IO () updateTaskStatus tid newStatus = do tasks <- loadTasks now <- getCurrentTime let updatedTasks = map updateIfMatch tasks updateIfMatch t = if taskId t == tid then t {taskStatus = newStatus, taskUpdatedAt = now} else t -- Rewrite the entire file (simple approach for MVP) TIO.writeFile ".tasks/tasks.jsonl" "" traverse_ saveTask updatedTasks -- List tasks, optionally filtered by type or parent listTasks :: Maybe TaskType -> Maybe Text -> IO [Task] listTasks maybeType maybeParent = do tasks <- loadTasks let filtered = tasks |> filterByType maybeType |> filterByParent maybeParent pure filtered where filterByType Nothing ts = ts filterByType (Just typ) ts = filter (\t -> taskType t == typ) ts filterByParent Nothing ts = ts filterByParent (Just pid) ts = filter (\t -> taskParent t == Just pid) ts -- Get ready tasks (not blocked by dependencies) getReadyTasks :: IO [Task] getReadyTasks = do allTasks <- loadTasks let openTasks = filter (\t -> taskStatus t /= Done) allTasks doneIds = map taskId <| filter (\t -> taskStatus t == Done) allTasks -- Only Blocks and ParentChild dependencies block ready work blockingDepIds task = [depId dep | dep <- taskDependencies task, depType dep `elem` [Blocks, ParentChild]] isReady task = all (`elem` doneIds) (blockingDepIds task) pure <| filter isReady openTasks -- Show dependency tree for a task showDependencyTree :: Text -> IO () showDependencyTree tid = do tasks <- loadTasks case filter (\t -> taskId t == tid) tasks of [] -> putText "Task not found" (task : _) -> printTree tasks task 0 where printTree :: [Task] -> Task -> Int -> IO () printTree allTasks task indent = do putText <| T.pack (replicate (indent * 2) ' ') <> taskId task <> ": " <> taskTitle task let depIds = map depId (taskDependencies task) deps = filter (\t -> taskId t `elem` depIds) allTasks traverse_ (\dep -> printTree allTasks dep (indent + 1)) deps -- Helper to print a task printTask :: Task -> IO () printTask t = putText <| taskId t <> " [" <> T.pack (show (taskType t)) <> "] [" <> T.pack (show (taskStatus t)) <> "] " <> taskTitle t <> parentInfo <> namespaceInfo where parentInfo = case taskParent t of Nothing -> "" Just p -> " (parent: " <> p <> ")" namespaceInfo = case taskNamespace t of Nothing -> "" Just ns -> " [" <> ns <> "]" -- Export tasks: Consolidate JSONL file (remove duplicates, keep latest version) exportTasks :: IO () exportTasks = do tasks <- loadTasks -- Rewrite the entire file with deduplicated tasks TIO.writeFile ".tasks/tasks.jsonl" "" traverse_ saveTask tasks -- Import tasks: Read from another JSONL file and merge with existing tasks importTasks :: FilePath -> IO () importTasks filePath = do exists <- doesFileExist filePath unless exists <| panic (T.pack filePath <> " does not exist") -- Load tasks from import file content <- TIO.readFile filePath let importLines = T.lines content importedTasks = mapMaybe decodeTask importLines -- Load existing tasks existingTasks <- loadTasks -- Create a map of existing task IDs for quick lookup let existingIds = map taskId existingTasks -- Filter to only new tasks (not already in our database) newTasks = filter (\t -> taskId t `notElem` existingIds) importedTasks -- For tasks that exist, update them with imported data updatedTasks = map (updateWithImported importedTasks) existingTasks -- Combine: updated existing tasks + new tasks allTasks = updatedTasks ++ newTasks -- Rewrite tasks.jsonl with merged data TIO.writeFile ".tasks/tasks.jsonl" "" traverse_ saveTask allTasks where decodeTask :: Text -> Maybe Task decodeTask line = if T.null line then Nothing else decode (BLC.pack <| T.unpack line) -- Update an existing task if there's a newer version in imported tasks updateWithImported :: [Task] -> Task -> Task updateWithImported imported existing = case filter (\t -> taskId t == taskId existing) imported of [] -> existing -- No imported version, keep existing (importedTask : _) -> -- Use imported version if it's newer (based on updatedAt) if taskUpdatedAt importedTask > taskUpdatedAt existing then importedTask else existing