{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE NoImplicitPrelude #-} module Omni.Task.Core where import Alpha import Data.Aeson (FromJSON, ToJSON, decode, encode) import qualified Data.Aeson as Aeson import qualified Data.ByteString.Lazy.Char8 as BLC import qualified Data.List as List import qualified Data.Text as T import qualified Data.Text.IO as TIO import Data.Time (UTCTime, diffTimeToPicoseconds, getCurrentTime, utctDay, utctDayTime) import Data.Time.Calendar (toModifiedJulianDay) import qualified Database.SQLite.Simple as SQL import qualified Database.SQLite.Simple.FromField as SQL import qualified Database.SQLite.Simple.Ok as SQLOk import qualified Database.SQLite.Simple.ToField as SQL import GHC.Generics () import System.Directory (createDirectoryIfMissing, doesFileExist) import System.Environment (lookupEnv) -- 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, taskPriority :: Priority, -- Priority level (0-4) taskDependencies :: [Dependency], -- List of dependencies with types taskDescription :: Maybe Text, -- Optional detailed description taskCreatedAt :: UTCTime, taskUpdatedAt :: UTCTime } deriving (Show, Eq, Generic) data TaskType = Epic | WorkTask | HumanTask deriving (Show, Eq, Read, Generic) data Status = Open | InProgress | Review | Approved | Done deriving (Show, Eq, Read, Generic) -- Priority levels (matching beads convention) data Priority = P0 | P1 | P2 | P3 | P4 deriving (Show, Eq, Ord, Read, 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, Read, Generic) data TaskProgress = TaskProgress { progressTaskId :: Text, progressTotal :: Int, progressCompleted :: Int, progressPercentage :: Int } deriving (Show, Eq, Generic) instance ToJSON TaskType instance FromJSON TaskType instance ToJSON Status instance FromJSON Status instance ToJSON Priority instance FromJSON Priority instance ToJSON DependencyType instance FromJSON DependencyType instance ToJSON Dependency instance FromJSON Dependency instance ToJSON Task instance FromJSON Task instance ToJSON TaskProgress instance FromJSON TaskProgress -- SQLite Instances instance SQL.FromField TaskType where fromField f = do t <- SQL.fromField f :: SQLOk.Ok String case readMaybe t of Just x -> pure x Nothing -> SQL.returnError SQL.ConversionFailed f "Invalid TaskType" instance SQL.ToField TaskType where toField x = SQL.toField (show x :: String) instance SQL.FromField Status where fromField f = do t <- SQL.fromField f :: SQLOk.Ok String case readMaybe t of Just x -> pure x Nothing -> SQL.returnError SQL.ConversionFailed f "Invalid Status" instance SQL.ToField Status where toField x = SQL.toField (show x :: String) instance SQL.FromField Priority where fromField f = do t <- SQL.fromField f :: SQLOk.Ok String case readMaybe t of Just x -> pure x Nothing -> SQL.returnError SQL.ConversionFailed f "Invalid Priority" instance SQL.ToField Priority where toField x = SQL.toField (show x :: String) -- Store dependencies as JSON text instance SQL.FromField [Dependency] where fromField f = do t <- SQL.fromField f :: SQLOk.Ok String case Aeson.decode (BLC.pack t) of Just x -> pure x Nothing -> pure [] -- Default to empty if parse fail or null instance SQL.ToField [Dependency] where toField deps = SQL.toField (BLC.unpack (encode deps)) instance SQL.FromRow Task where fromRow = Task SQL.field <*> SQL.field <*> SQL.field <*> SQL.field <*> SQL.field <*> SQL.field <*> SQL.field <*> SQL.field <*> SQL.field <*> SQL.field instance SQL.ToRow Task where toRow t = [ SQL.toField (taskId t), SQL.toField (taskTitle t), SQL.toField (taskType t), SQL.toField (taskParent t), SQL.toField (taskNamespace t), SQL.toField (taskStatus t), SQL.toField (taskPriority t), SQL.toField (taskDependencies t), SQL.toField (taskDescription t), SQL.toField (taskCreatedAt t), SQL.toField (taskUpdatedAt t) ] -- | Case-insensitive ID comparison matchesId :: Text -> Text -> Bool matchesId id1 id2 = normalizeId id1 == normalizeId id2 -- | Normalize ID to lowercase normalizeId :: Text -> Text normalizeId = T.toLower -- | Find a task by ID (case-insensitive) findTask :: Text -> [Task] -> Maybe Task findTask tid = List.find (\t -> matchesId (taskId t) tid) -- | Normalize task IDs (self, parent, dependencies) to lowercase normalizeTask :: Task -> Task normalizeTask t = t { taskId = normalizeId (taskId t), taskParent = fmap normalizeId (taskParent t), taskDependencies = map normalizeDependency (taskDependencies t) } normalizeDependency :: Dependency -> Dependency normalizeDependency d = d {depId = normalizeId (depId d)} -- Get the tasks database file path getTasksDbPath :: IO FilePath getTasksDbPath = do customPath <- lookupEnv "TASK_DB_PATH" testMode <- lookupEnv "TASK_TEST_MODE" let path = case (customPath, testMode) of (Just p, _) -> p (_, Just "1") -> ".tasks/tasks-test.db" _ -> ".tasks/tasks.db" pure path -- DB Helper withDb :: (SQL.Connection -> IO a) -> IO a withDb action = do dbPath <- getTasksDbPath SQL.withConnection dbPath <| \conn -> do SQL.execute_ conn "PRAGMA busy_timeout = 5000" action conn -- Initialize the task database initTaskDb :: IO () initTaskDb = do createDirectoryIfMissing True ".tasks" withDb <| \conn -> do SQL.execute_ conn "CREATE TABLE IF NOT EXISTS tasks (\ \ id TEXT PRIMARY KEY, \ \ title TEXT NOT NULL, \ \ type TEXT NOT NULL, \ \ parent TEXT, \ \ namespace TEXT, \ \ status TEXT NOT NULL, \ \ priority TEXT NOT NULL, \ \ dependencies TEXT NOT NULL, \ \ description TEXT, \ \ created_at TIMESTAMP NOT NULL, \ \ updated_at TIMESTAMP NOT NULL \ \)" -- Generate a short ID using base36 encoding of timestamp (lowercase) generateId :: IO Text generateId = do now <- getCurrentTime let day = utctDay now dayTime = utctDayTime now mjd = toModifiedJulianDay day micros = diffTimeToPicoseconds dayTime `div` 1000000 totalMicros = (mjd * 100000000000) + micros encoded = toBase36 totalMicros pure <| "t-" <> T.pack encoded -- Generate a child ID based on parent ID generateChildId :: Text -> IO Text generateChildId parentId = do tasks <- loadTasks pure <| computeNextChildId tasks (normalizeId parentId) computeNextChildId :: [Task] -> Text -> Text computeNextChildId tasks parentId = let suffixes = mapMaybe (getSuffix parentId <. taskId) tasks nextSuffix = case suffixes of [] -> 1 s -> maximum s + 1 in parentId <> "." <> T.pack (show nextSuffix) getSuffix :: Text -> Text -> Maybe Int getSuffix parent childId = if parent `T.isPrefixOf` childId && T.length childId > T.length parent then let rest = T.drop (T.length parent) childId in if T.head rest == '.' then readMaybe (T.unpack (T.tail rest)) else Nothing else Nothing -- Convert number to base36 (0-9, a-z) toBase36 :: Integer -> String toBase36 0 = "0" toBase36 n = reverse <| go n where alphabet = ['0' .. '9'] ++ ['a' .. 'z'] go 0 = [] go x = let (q, r) = x `divMod` 36 idx = fromIntegral r char = case drop idx alphabet of (c : _) -> c [] -> '0' in char : go q -- Load all tasks from DB loadTasks :: IO [Task] loadTasks = withDb <| \conn -> do SQL.query_ conn "SELECT id, title, type, parent, namespace, status, priority, dependencies, description, created_at, updated_at FROM tasks" -- Save a single task (UPSERT) saveTask :: Task -> IO () saveTask task = withDb <| \conn -> do SQL.execute conn "INSERT OR REPLACE INTO tasks \ \ (id, title, type, parent, namespace, status, priority, dependencies, description, created_at, updated_at) \ \ VALUES (?, ?, ?, ?, ?, ?, ?, ?, ?, ?, ?)" task -- Create a new task createTask :: Text -> TaskType -> Maybe Text -> Maybe Text -> Priority -> [Dependency] -> Maybe Text -> IO Task createTask title taskType parent namespace priority deps description = do let parent' = fmap normalizeId parent deps' = map normalizeDependency deps tid <- case parent' of Nothing -> generateUniqueId Just pid -> do tasks <- loadTasks pure <| computeNextChildId tasks pid now <- getCurrentTime let task = Task { taskId = normalizeId tid, taskTitle = title, taskType = taskType, taskParent = parent', taskNamespace = namespace, taskStatus = Open, taskPriority = priority, taskDependencies = deps', taskDescription = description, taskCreatedAt = now, taskUpdatedAt = now } saveTask task pure task -- Generate a unique ID generateUniqueId :: IO Text generateUniqueId = do -- We can query DB directly to check existence go where go = do tid <- generateId exists <- withDb <| \conn -> do [SQL.Only c] <- SQL.query conn "SELECT COUNT(*) FROM tasks WHERE id = ?" (SQL.Only tid) :: IO [SQL.Only Int] pure (c > 0) if exists then go else pure tid -- Update task status updateTaskStatus :: Text -> Status -> [Dependency] -> IO () updateTaskStatus tid newStatus newDeps = withDb <| \conn -> do now <- getCurrentTime -- If newDeps is empty, we need to preserve existing deps. -- If newDeps is NOT empty, we replace them. -- This logic is slightly tricky in SQL. We fetch first. rows <- SQL.query conn "SELECT dependencies FROM tasks WHERE id = ?" (SQL.Only tid) :: IO [SQL.Only [Dependency]] case rows of [] -> pure () -- Task not found (SQL.Only existingDeps : _) -> do let finalDeps = if null newDeps then existingDeps else newDeps SQL.execute conn "UPDATE tasks SET status = ?, updated_at = ?, dependencies = ? WHERE id = ?" (newStatus, now, finalDeps, tid) -- Edit a task editTask :: Text -> (Task -> Task) -> IO Task editTask tid modifyFn = do tasks <- loadTasks case findTask tid tasks of Nothing -> panic "Task not found" Just original -> do now <- getCurrentTime let modified = modifyFn original finalTask = modified {taskUpdatedAt = now} saveTask finalTask pure finalTask -- List tasks listTasks :: Maybe TaskType -> Maybe Text -> Maybe Status -> Maybe Text -> IO [Task] listTasks maybeType maybeParent maybeStatus maybeNamespace = do -- Implementing specific filters in SQL would be more efficient, but for MVP and API compat: tasks <- loadTasks let filtered = tasks |> filterByType maybeType |> filterByParent maybeParent |> filterByStatus maybeStatus |> filterByNamespace maybeNamespace 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 filterByStatus Nothing ts = ts filterByStatus (Just status) ts = filter (\t -> taskStatus t == status) ts filterByNamespace Nothing ts = ts filterByNamespace (Just ns) ts = filter (\t -> taskNamespace t == Just ns) ts -- Get ready tasks getReadyTasks :: IO [Task] getReadyTasks = do allTasks <- loadTasks let openTasks = filter (\t -> taskStatus t == Open || taskStatus t == InProgress) allTasks doneIds = map taskId <| filter (\t -> taskStatus t == Done) allTasks parentIds = mapMaybe taskParent allTasks isParent tid = tid `elem` parentIds blockingDepIds task = [depId dep | dep <- taskDependencies task, depType dep `elem` [Blocks, ParentChild]] isReady task = taskType task /= Epic && not (isParent (taskId task)) && all (`elem` doneIds) (blockingDepIds task) && taskType task /= HumanTask pure <| filter isReady openTasks -- Get dependency tree getDependencyTree :: Text -> IO [Task] getDependencyTree tid = do tasks <- loadTasks case findTask tid tasks of Nothing -> pure [] Just task -> pure <| collectDeps tasks task where collectDeps allTasks task = let depIds = map depId (taskDependencies task) deps = filter (\t -> any (matchesId (taskId t)) depIds) allTasks in task : concatMap (collectDeps allTasks) deps -- Get task progress getTaskProgress :: Text -> IO TaskProgress getTaskProgress tidRaw = do let tid = normalizeId tidRaw -- Could be SQL optimized tasks <- loadTasks case findTask tid tasks of Nothing -> panic "Task not found" Just _ -> do let children = filter (\child -> taskParent child == Just tid) tasks total = length children completed = length <| filter (\child -> taskStatus child == Done) children percentage = if total == 0 then 0 else (completed * 100) `div` total pure TaskProgress { progressTaskId = tid, progressTotal = total, progressCompleted = completed, progressPercentage = percentage } showTaskProgress :: Text -> IO () showTaskProgress tid = do progress <- getTaskProgress tid putText <| "Progress for " <> tid <> ": " <> T.pack (show (progressCompleted progress)) <> "/" <> T.pack (show (progressTotal progress)) <> " (" <> T.pack (show (progressPercentage progress)) <> "%)" showDependencyTree :: Text -> IO () showDependencyTree tid = do tasks <- loadTasks case findTask tid tasks of Nothing -> putText "Task not found" Just 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 -> any (matchesId (taskId t)) depIds) allTasks traverse_ (\dep -> printTree allTasks dep (indent + 1)) deps getTaskTree :: Maybe Text -> IO [Task] getTaskTree maybeId = do tasks <- loadTasks case maybeId of Nothing -> do let epics = filter (\t -> taskType t == Epic) tasks in pure <| concatMap (collectChildren tasks) epics Just tid -> do case findTask tid tasks of Nothing -> pure [] Just task -> pure <| collectChildren tasks task where collectChildren allTasks task = let children = filter (maybe False (`matchesId` taskId task) <. taskParent) allTasks in task : concatMap (collectChildren allTasks) children showTaskTree :: Maybe Text -> IO () showTaskTree maybeId = do tasks <- loadTasks case maybeId of Nothing -> do let epics = filter (\t -> taskType t == Epic) tasks if null epics then putText "No epics found" else traverse_ (printEpicTree tasks) epics Just tid -> do case findTask tid tasks of Nothing -> putText "Task not found" Just task -> printEpicTree tasks task where printEpicTree allTasks task = printTreeNode allTasks task (0 :: Int) printTreeNode allTasks task indent = printTreeNode' allTasks task indent [] printTreeNode' allTasks task indent ancestry = do let children = filter (maybe False (`matchesId` taskId task) <. taskParent) allTasks prefix = if indent == 0 then "" else let ancestorPrefixes = map (\hasMore -> if hasMore then "│ " else " ") (List.init ancestry) myPrefix = if List.last ancestry then "├── " else "└── " in T.pack <| concat ancestorPrefixes ++ myPrefix statusStr = case taskType task of Epic -> let total = length children completed = length <| filter (\t -> taskStatus t == Done) children in "[" <> T.pack (show completed) <> "/" <> T.pack (show total) <> "]" _ -> case taskStatus task of Open -> "[ ]" InProgress -> "[~]" Review -> "[?]" Approved -> "[+]" Done -> "[✓]" coloredStatusStr = case taskType task of Epic -> magenta statusStr _ -> case taskStatus task of Open -> bold statusStr InProgress -> yellow statusStr Review -> magenta statusStr Approved -> green statusStr Done -> green statusStr nsStr = case taskNamespace task of Nothing -> "" Just ns -> "[" <> ns <> "] " coloredNsStr = case taskNamespace task of Nothing -> "" Just _ -> gray nsStr usedWidth = T.length prefix + T.length (taskId task) + T.length statusStr + T.length nsStr + 2 availableWidth = max 20 (80 - usedWidth) truncatedTitle = if T.length (taskTitle task) > availableWidth then T.take (availableWidth - 3) (taskTitle task) <> "..." else taskTitle task coloredTitle = if taskType task == Epic then bold truncatedTitle else truncatedTitle putText <| prefix <> cyan (taskId task) <> " " <> coloredStatusStr <> " " <> coloredNsStr <> coloredTitle let indexedChildren = zip [1 ..] children totalChildren = length children traverse_ ( \(idx, child) -> let hasMoreSiblings = idx < totalChildren in printTreeNode' allTasks child (indent + 1) (ancestry ++ [hasMoreSiblings]) ) indexedChildren printTask :: Task -> IO () printTask t = do tasks <- loadTasks let progressInfo = if taskType t == Epic then let children = filter (maybe False (`matchesId` taskId t) <. taskParent) tasks total = length children completed = length <| filter (\child -> taskStatus child == Done) children in " [" <> T.pack (show completed) <> "/" <> T.pack (show total) <> "]" else "" parentInfo = case taskParent t of Nothing -> "" Just p -> " (parent: " <> p <> ")" namespaceInfo = case taskNamespace t of Nothing -> "" Just ns -> " [" <> ns <> "]" coloredStatus = let s = "[" <> T.pack (show (taskStatus t)) <> "]" in case taskStatus t of Open -> bold s InProgress -> yellow s Review -> magenta s Approved -> green s Done -> green s coloredTitle = if taskType t == Epic then bold (taskTitle t) else taskTitle t coloredProgress = if taskType t == Epic then magenta progressInfo else progressInfo coloredNamespace = case taskNamespace t of Nothing -> "" Just _ -> gray namespaceInfo coloredParent = case taskParent t of Nothing -> "" Just _ -> gray parentInfo putText <| cyan (taskId t) <> " [" <> T.pack (show (taskType t)) <> "] " <> coloredStatus <> coloredProgress <> " " <> coloredTitle <> coloredParent <> coloredNamespace showTaskDetailed :: Task -> IO () showTaskDetailed t = do tasks <- loadTasks putText "" putText <| "Task: " <> taskId t putText "" putText <| "Title: " <> taskTitle t putText <| "Type: " <> T.pack (show (taskType t)) putText <| "Status: " <> T.pack (show (taskStatus t)) putText <| "Priority: " <> T.pack (show (taskPriority t)) <> priorityDesc when (taskType t == Epic) <| do let children = filter (maybe False (`matchesId` taskId t) <. taskParent) tasks total = length children completed = length <| filter (\child -> taskStatus child == Done) children percentage = if total == 0 then 0 else (completed * 100) `div` total putText <| "Progress: " <> T.pack (show completed) <> "/" <> T.pack (show total) <> " (" <> T.pack (show percentage) <> "%)" case taskParent t of Nothing -> pure () Just p -> putText <| "Parent: " <> p case taskNamespace t of Nothing -> pure () Just ns -> putText <| "Namespace: " <> ns putText <| "Created: " <> T.pack (show (taskCreatedAt t)) putText <| "Updated: " <> T.pack (show (taskUpdatedAt t)) unless (null (taskDependencies t)) <| do putText "" putText "Dependencies:" traverse_ printDependency (taskDependencies t) case taskDescription t of Nothing -> pure () Just desc -> do putText "" putText "Description:" let indented = T.unlines <| map (" " <>) (T.lines desc) putText indented putText "" where priorityDesc = case taskPriority t of P0 -> " (Critical)" P1 -> " (High)" P2 -> " (Medium)" P3 -> " (Low)" P4 -> " (Backlog)" printDependency dep = putText <| " - " <> depId dep <> " [" <> T.pack (show (depType dep)) <> "]" red, green, yellow, blue, magenta, cyan, gray, bold :: Text -> Text red t = "\ESC[31m" <> t <> "\ESC[0m" green t = "\ESC[32m" <> t <> "\ESC[0m" yellow t = "\ESC[33m" <> t <> "\ESC[0m" blue t = "\ESC[34m" <> t <> "\ESC[0m" magenta t = "\ESC[35m" <> t <> "\ESC[0m" cyan t = "\ESC[36m" <> t <> "\ESC[0m" gray t = "\ESC[90m" <> t <> "\ESC[0m" bold t = "\ESC[1m" <> t <> "\ESC[0m" -- Export tasks: Dump SQLite to JSONL exportTasks :: Maybe FilePath -> IO () exportTasks maybePath = do tasks <- loadTasks case maybePath of Just path -> do TIO.writeFile path "" traverse_ (saveTaskToJsonl path) tasks Nothing -> -- Stream to stdout traverse_ (BLC.putStrLn <. encode) tasks saveTaskToJsonl :: FilePath -> Task -> IO () saveTaskToJsonl path task = do let json = encode task BLC.appendFile path (json <> "\n") data TaskStats = TaskStats { totalTasks :: Int, openTasks :: Int, inProgressTasks :: Int, reviewTasks :: Int, approvedTasks :: Int, doneTasks :: Int, totalEpics :: Int, readyTasks :: Int, blockedTasks :: Int, tasksByPriority :: [(Priority, Int)], tasksByNamespace :: [(Text, Int)] } deriving (Show, Eq, Generic) instance ToJSON TaskStats instance FromJSON TaskStats getTaskStats :: Maybe Text -> IO TaskStats getTaskStats maybeEpicId = do allTasks <- loadTasks targetTasks <- case maybeEpicId of Nothing -> pure allTasks Just epicId -> case findTask epicId allTasks of Nothing -> panic "Epic not found" Just task -> pure <| getAllDescendants allTasks (taskId task) globalReady <- getReadyTasks let readyIds = map taskId globalReady readyCount = length <| filter (\t -> taskId t `elem` readyIds) targetTasks tasks = targetTasks total = length tasks open = length <| filter (\t -> taskStatus t == Open) tasks inProg = length <| filter (\t -> taskStatus t == InProgress) tasks review = length <| filter (\t -> taskStatus t == Review) tasks approved = length <| filter (\t -> taskStatus t == Approved) tasks done = length <| filter (\t -> taskStatus t == Done) tasks epics = length <| filter (\t -> taskType t == Epic) tasks readyCount' = readyCount blockedCount = total - readyCount' - done byPriority = [ (P0, length <| filter (\t -> taskPriority t == P0) tasks), (P1, length <| filter (\t -> taskPriority t == P1) tasks), (P2, length <| filter (\t -> taskPriority t == P2) tasks), (P3, length <| filter (\t -> taskPriority t == P3) tasks), (P4, length <| filter (\t -> taskPriority t == P4) tasks) ] namespaces = mapMaybe taskNamespace tasks uniqueNs = List.nub namespaces byNamespace = map (\ns -> (ns, length <| filter (\t -> taskNamespace t == Just ns) tasks)) uniqueNs pure TaskStats { totalTasks = total, openTasks = open, inProgressTasks = inProg, reviewTasks = review, approvedTasks = approved, doneTasks = done, totalEpics = epics, readyTasks = readyCount', blockedTasks = blockedCount, tasksByPriority = byPriority, tasksByNamespace = byNamespace } getAllDescendants :: [Task] -> Text -> [Task] getAllDescendants allTasks parentId = let children = filter (maybe False (`matchesId` parentId) <. taskParent) allTasks in children ++ concatMap (getAllDescendants allTasks <. taskId) children showTaskStats :: Maybe Text -> IO () showTaskStats maybeEpicId = do stats <- getTaskStats maybeEpicId putText "" case maybeEpicId of Nothing -> putText "Task Statistics" Just epicId -> putText <| "Task Statistics for Epic " <> epicId putText "" putText <| "Total tasks: " <> T.pack (show (totalTasks stats)) putText <| " Open: " <> T.pack (show (openTasks stats)) putText <| " In Progress: " <> T.pack (show (inProgressTasks stats)) putText <| " Review: " <> T.pack (show (reviewTasks stats)) putText <| " Approved: " <> T.pack (show (approvedTasks stats)) putText <| " Done: " <> T.pack (show (doneTasks stats)) putText "" putText <| "Epics: " <> T.pack (show (totalEpics stats)) putText "" putText <| "Ready to work: " <> T.pack (show (readyTasks stats)) putText <| "Blocked: " <> T.pack (show (blockedTasks stats)) putText "" putText "By Priority:" traverse_ printPriority (tasksByPriority stats) unless (null (tasksByNamespace stats)) <| do putText "" putText "By Namespace:" traverse_ printNamespace (tasksByNamespace stats) putText "" where printPriority (p, count) = let label = case p of P0 -> "P0 (Critical)" P1 -> "P1 (High)" P2 -> "P2 (Medium)" P3 -> "P3 (Low)" P4 -> "P4 (Backlog)" in putText <| " " <> T.pack (show count) <> " " <> label printNamespace (ns, count) = putText <| " " <> T.pack (show count) <> " " <> ns -- Import tasks: Read from JSONL and insert/update DB importTasks :: FilePath -> IO () importTasks filePath = do exists <- doesFileExist filePath unless exists <| panic (T.pack filePath <> " does not exist") content <- TIO.readFile filePath let importLines = T.lines content importedTasks = map normalizeTask (mapMaybe decodeTask importLines) -- Save all imported tasks (UPSERT logic handles updates) traverse_ saveTask importedTasks where decodeTask :: Text -> Maybe Task decodeTask line = if T.null line then Nothing else decode (BLC.pack <| T.unpack line)