{-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} module TaskIntegrationSpec (spec) where import Helpers ( assertSucceeds , buildTestTask , generateUniqueName , getTestConfig , liftTodoist ) import qualified Web.Todoist.Domain.Project as P import Web.Todoist.Domain.Task ( NewTask (..) , Task (..) , TodoistTaskM (..) , moveTaskBuilder , updateTaskBuilder , completedTasksQueryParamBuilder , filterTaskBuilder ) import qualified Web.Todoist.Domain.Task as T import Web.Todoist.Domain.Types (Content (..), Description (..), ProjectId (..), TaskId (..)) import Web.Todoist.Internal.Config (TodoistConfig) import Web.Todoist.Internal.Error (TodoistError) import Web.Todoist.Runner (todoist) import Web.Todoist.Util.Builder ( runBuilder , withContent , withDescription , withDueDate , withPriority , withProjectId ) import Control.Applicative (pure) import Control.Exception (bracket) import Control.Monad (forM_, mapM, void) import Control.Monad.IO.Class (liftIO) import Control.Monad.Trans.Except (ExceptT) import Data.Bool (Bool (..)) import Data.Either (Either (..)) import Data.Function (($)) import Data.Functor ((<$>)) import Data.Int (Int) import qualified Data.List as L import Data.Maybe (Maybe (..)) import Data.Semigroup ((<>)) import Data.Text (Text, pack) import System.IO (IO, putStrLn) import Test.Hspec (Spec, describe, it, pendingWith, runIO, shouldBe, shouldSatisfy) import Text.Show (show) import GHC.Base (mempty) spec :: Spec spec = do maybeConfig <- runIO getTestConfig case maybeConfig of Nothing -> it "requires TODOIST_TEST_API_TOKEN" $ pendingWith "TODOIST_TEST_API_TOKEN not set" Just config -> do taskLifecycleSpec config taskCompletionSpec config getTasksSpec config updateTaskSpec config taskFilterSpec config moveTaskSpec config taskLifecycleSpec :: TodoistConfig -> Spec taskLifecycleSpec config = describe "Task lifecycle (create, get, delete)" $ do it "creates, retrieves, and deletes a task with all fields verified" $ do -- Generate unique names projectName <- pack <$> generateUniqueName "IntegTest-TaskLifecycle-Project" taskContent <- pack <$> generateUniqueName "IntegTest-TaskLifecycle-Task" -- Use withTestTask for automatic cleanup withTestTask config projectName taskContent $ \projectId taskId -> do -- Verify we can retrieve the task task <- liftTodoist config (getTask taskId) -- Extract task fields for verification let Task { _id = retrievedId , _content = retrievedContent , _description = retrievedDescription , _project_id = retrievedProjectId } = task -- Verify task ID matches liftIO $ retrievedId `shouldBe` taskId -- Verify content matches liftIO $ retrievedContent `shouldBe` Content taskContent -- Verify description was set liftIO $ retrievedDescription `shouldBe` Description "Test task description for integration testing" -- Verify project ID matches liftIO $ retrievedProjectId `shouldBe` projectId -- Test explicit delete (cleanup will handle if this fails) liftTodoist config (deleteTask taskId) taskCompletionSpec :: TodoistConfig -> Spec taskCompletionSpec config = describe "Task completion/uncompletion lifecycle" $ do it "marks a task as complete then reopens it" $ do -- Generate unique names projectName <- pack <$> generateUniqueName "IntegTest-TaskCompletion-Project" taskContent <- pack <$> generateUniqueName "IntegTest-TaskCompletion-Task" withTestTask config projectName taskContent $ \_ taskId -> do -- Verify task starts as not completed task1 <- liftTodoist config (getTask taskId) let Task {_completed_at = initialCompletedAt} = task1 liftIO $ initialCompletedAt `shouldBe` Nothing -- Close the task liftTodoist config (closeTask taskId) -- Try to get the task after closing getResult <- liftIO $ todoist config (getTask taskId) case getResult of Right closedTask -> do -- If we can still get it, verify it's marked as completed let Task {_completed_at = completedAt} = closedTask liftIO $ completedAt `shouldSatisfy` (\case Just _ -> True; Nothing -> False) Left _ -> do -- If we can't get it, that's also acceptable (API behavior) liftIO $ putStrLn "Task not retrievable after closing (expected API behavior)" -- Unclose the task liftTodoist config (uncloseTask taskId) -- Verify task is now uncompleted task2 <- liftTodoist config (getTask taskId) let Task {_completed_at = finalCompletedAt} = task2 liftIO $ finalCompletedAt `shouldBe` Nothing getTasksSpec :: TodoistConfig -> Spec getTasksSpec config = describe "Get multiple tasks" $ do it "creates 3 tasks, retrieves them via getTasks, validates count and properties" $ do -- Generate unique names projectName <- pack <$> generateUniqueName "IntegTest-GetTasks-Project" baseName <- generateUniqueName "IntegTest-GetTasks-Task" let taskContent1 = pack $ baseName <> "-Task1" let taskContent2 = pack $ baseName <> "-Task2" let taskContent3 = pack $ baseName <> "-Task3" let taskContents = [taskContent1, taskContent2, taskContent3] withTestTasks config projectName taskContents $ \projectId taskIds -> do -- Get all tasks for this project let ProjectId {getProjectId = projIdText} = projectId let taskParam = runBuilder T.taskParamBuilder (withProjectId projIdText) tasks <- liftTodoist config (getTasks taskParam) -- Verify we got exactly 3 tasks let taskCount = L.length tasks liftIO $ taskCount `shouldBe` (3 :: Int) -- Extract task IDs and contents from results let taskIdsResult = L.map (\(Task {_id = tid}) -> tid) tasks let taskContentsResult = L.map (\(Task {_content = content}) -> content) tasks -- Verify all 3 task IDs are present let [expectedId1, expectedId2, expectedId3] = taskIds liftIO $ (expectedId1 `L.elem` taskIdsResult) `shouldBe` True liftIO $ (expectedId2 `L.elem` taskIdsResult) `shouldBe` True liftIO $ (expectedId3 `L.elem` taskIdsResult) `shouldBe` True -- Verify all 3 task contents are present liftIO $ (Content taskContent1 `L.elem` taskContentsResult) `shouldBe` True liftIO $ (Content taskContent2 `L.elem` taskContentsResult) `shouldBe` True liftIO $ (Content taskContent3 `L.elem` taskContentsResult) `shouldBe` True -- Verify each task has the correct project_id forM_ tasks $ \(Task {_project_id = taskProjId}) -> do liftIO $ taskProjId `shouldBe` projectId updateTaskSpec :: TodoistConfig -> Spec updateTaskSpec config = describe "Update task" $ do it "creates a task, updates its properties, verifies changes" $ do -- Generate unique names projectName <- pack <$> generateUniqueName "IntegTest-UpdateTask-Project" originalContent <- pack <$> generateUniqueName "IntegTest-UpdateTask-Original" withTestTask config projectName originalContent $ \projectId taskId -> do -- Verify initial state task1 <- liftTodoist config (getTask taskId) let Task { _content = initialContent , _description = initialDescription , _priority = initialPriority } = task1 liftIO $ initialContent `shouldBe` Content originalContent liftIO $ initialDescription `shouldBe` Description "Test task description for integration testing" liftIO $ initialPriority `shouldBe` 1 -- default priority -- Update the task let updatedContent = originalContent <> "-Updated" let updatedDescription = "Updated task description" let updatedPriority = 3 let taskPatch = runBuilder updateTaskBuilder ( withContent updatedContent <> withDescription updatedDescription <> withPriority updatedPriority ) updatedNewTask <- liftTodoist config (updateTask taskPatch taskId) -- Verify the response contains updated values let NewTask { _content = responseContent , _description = responseDescription , _priority = responsePriority } = updatedNewTask liftIO $ responseContent `shouldBe` Content updatedContent liftIO $ responseDescription `shouldBe` Description updatedDescription liftIO $ responsePriority `shouldBe` updatedPriority -- Fetch the task again to verify persistence task2 <- liftTodoist config (getTask taskId) let Task { _content = persistedContent , _description = persistedDescription , _priority = persistedPriority , _project_id = persistedProjectId } = task2 liftIO $ persistedContent `shouldBe` Content updatedContent liftIO $ persistedDescription `shouldBe` Description updatedDescription liftIO $ persistedPriority `shouldBe` updatedPriority -- Verify project_id unchanged liftIO $ persistedProjectId `shouldBe` projectId it "supports partial updates (only updating specific fields)" $ do -- Generate unique names projectName <- pack <$> generateUniqueName "IntegTest-PartialUpdate-Project" taskContent <- pack <$> generateUniqueName "IntegTest-PartialUpdate-Task" withTestTask config projectName taskContent $ \_ taskId -> do -- Get initial state task1 <- liftTodoist config (getTask taskId) let Task { _content = originalContent , _description = originalDescription } = task1 -- Partial update: only change priority let taskPatch = runBuilder updateTaskBuilder (withPriority 4) _ <- liftTodoist config (updateTask taskPatch taskId) -- Verify only priority changed task2 <- liftTodoist config (getTask taskId) let Task { _content = finalContent , _description = finalDescription , _priority = finalPriority } = task2 liftIO $ finalPriority `shouldBe` 4 -- Other fields should remain unchanged liftIO $ finalContent `shouldBe` originalContent liftIO $ finalDescription `shouldBe` originalDescription taskFilterSpec :: TodoistConfig -> Spec taskFilterSpec config = describe "Task filtering" $ do it "searches tasks using text filter" $ do -- Generate unique names with distinctive search term projectName <- pack <$> generateUniqueName "IntegTest-Filter-Project" searchTerm <- generateUniqueName "UNIQUE_SEARCHABLE_TERM" let taskContent = pack $ "Task with " <> searchTerm withTestTask config projectName taskContent $ \_ taskId -> do -- Search for tasks containing our unique term -- Use search: prefix for text search in Todoist filter syntax let filter = runBuilder (filterTaskBuilder (pack $ "search: " <> searchTerm)) mempty taskIds <- liftTodoist config (getTasksByFilter filter) -- Verify our task is in the results let TaskId {getTaskId = expectedIdText} = taskId let taskIdTexts = L.map (\(TaskId {getTaskId = tid}) -> tid) taskIds liftIO $ (expectedIdText `L.elem` taskIdTexts) `shouldBe` True it "retrieves completed tasks by due date range" $ do -- Generate unique names projectName <- pack <$> generateUniqueName "IntegTest-CompletedDue-Project" taskContent <- pack <$> generateUniqueName "IntegTest-CompletedDue-Task" withTestTask config projectName taskContent $ \projectId taskId -> do -- Set a due date on the task first let taskPatch = runBuilder updateTaskBuilder (withDueDate "2025-11-03") _ <- liftTodoist config (updateTask taskPatch taskId) -- Complete the task liftTodoist config (closeTask taskId) -- Query for completed tasks by due date -- Use a wide range to ensure we catch our task let ProjectId {getProjectId = projIdText} = projectId let queryParamWithProject = runBuilder (completedTasksQueryParamBuilder "2025-11-01" "2025-11-30") (withProjectId projIdText) completedTaskIds <- liftTodoist config (getCompletedTasksByDueDate queryParamWithProject) -- Verify our task is in the results let TaskId {getTaskId = expectedIdText} = taskId let taskIdTexts = L.map (\(TaskId {getTaskId = tid}) -> tid) completedTaskIds liftIO $ (expectedIdText `L.elem` taskIdTexts) `shouldBe` True -- Unclose for cleanup liftTodoist config (uncloseTask taskId) it "retrieves completed tasks by completion date range" $ do -- Generate unique names projectName <- pack <$> generateUniqueName "IntegTest-CompletedDate-Project" taskContent <- pack <$> generateUniqueName "IntegTest-CompletedDate-Task" withTestTask config projectName taskContent $ \projectId taskId -> do -- Complete the task liftTodoist config (closeTask taskId) -- Query for completed tasks by completion date (today) -- Use a wide range to ensure we catch our task let ProjectId {getProjectId = projIdText} = projectId let queryParamWithProject = runBuilder (completedTasksQueryParamBuilder "2025-11-01" "2025-11-30") (withProjectId projIdText) completedTaskIds <- liftTodoist config (getCompletedTasksByCompletionDate queryParamWithProject) -- Verify our task is in the results let TaskId {getTaskId = expectedIdText} = taskId let taskIdTexts = L.map (\(TaskId {getTaskId = tid}) -> tid) completedTaskIds liftIO $ (expectedIdText `L.elem` taskIdTexts) `shouldBe` True -- Unclose for cleanup liftTodoist config (uncloseTask taskId) moveTaskSpec :: TodoistConfig -> Spec moveTaskSpec config = describe "Move task between projects" $ do it "creates two projects, moves a task from one to the other" $ do -- Generate unique names project1Name <- pack <$> generateUniqueName "IntegTest-MoveTask-Project1" project2Name <- pack <$> generateUniqueName "IntegTest-MoveTask-Project2" taskContent <- pack <$> generateUniqueName "IntegTest-MoveTask-Task" -- Create project 1 with task withTestTask config project1Name taskContent $ \project1Id taskId -> do -- Create project 2 project2Id <- liftTodoist config (P.addProject $ runBuilder (P.createProjectBuilder project2Name) mempty) -- Verify task is in project 1 task1 <- liftTodoist config (getTask taskId) let Task {_project_id = originalProjectId} = task1 liftIO $ originalProjectId `shouldBe` project1Id -- Move task to project 2 let ProjectId {getProjectId = project2IdText} = project2Id let moveTaskData = runBuilder moveTaskBuilder (withProjectId project2IdText) movedTaskId <- liftTodoist config (moveTask moveTaskData taskId) -- Verify returned task ID matches let TaskId {getTaskId = expectedIdText} = taskId let TaskId {getTaskId = movedIdText} = movedTaskId liftIO $ movedIdText `shouldBe` expectedIdText -- Verify task is now in project 2 task2 <- liftTodoist config (getTask taskId) let Task {_project_id = createProjectBuilderId} = task2 liftIO $ createProjectBuilderId `shouldBe` project2Id -- Clean up project 2 (task will be deleted by withTestTask cleanup) liftTodoist config (P.deleteProject project2Id) {- | Create a test project and task, run an action with the task ID, then clean up Uses bracket to ensure cleanup happens even if the action fails Tasks are deleted before the project -} withTestTask :: TodoistConfig -> Text -> -- project name Text -> -- task content (ProjectId -> TaskId -> ExceptT TodoistError IO a) -> IO () withTestTask config projectName taskContent action = do let createResources = do liftIO $ putStrLn $ "Creating test project: " <> show projectName projectId <- liftTodoist config (P.addProject $ runBuilder (P.createProjectBuilder projectName) mempty) liftIO $ putStrLn $ "Creating test task: " <> show taskContent let ProjectId {getProjectId = projIdText} = projectId let taskCreate = buildTestTask taskContent projIdText newTaskResult <- liftTodoist config (createTask taskCreate) let NewTask {_id = newTaskIdText} = newTaskResult let taskId = newTaskIdText pure (projectId, taskId) let deleteResources (projectId, taskId) = do liftIO $ putStrLn $ "Cleaning up test task: " <> show taskContent void $ todoist config (deleteTask taskId) liftIO $ putStrLn $ "Cleaning up test project: " <> show projectName void $ todoist config (P.deleteProject projectId) let runAction (projectId, taskId) = void $ assertSucceeds $ action projectId taskId bracket (assertSucceeds createResources) deleteResources runAction {- | Create a test project and multiple tasks, run an action with their IDs, then clean up Ensures all tasks are deleted before the project is deleted -} withTestTasks :: TodoistConfig -> Text -> -- project name [Text] -> -- task contents (ProjectId -> [TaskId] -> ExceptT TodoistError IO a) -> IO () withTestTasks config projectName taskContents action = do let createResources = do liftIO $ putStrLn $ "Creating test project: " <> show projectName projectId <- liftTodoist config (P.addProject $ runBuilder (P.createProjectBuilder projectName) mempty) liftIO $ putStrLn $ "Creating " <> show (L.length taskContents) <> " test tasks" let ProjectId {getProjectId = projIdText} = projectId taskIds <- mapM ( \content -> do let taskCreate = buildTestTask content projIdText newTaskResult <- liftTodoist config (createTask taskCreate) let NewTask {_id = newTaskIdText} = newTaskResult pure newTaskIdText ) taskContents pure (projectId, taskIds) let deleteResources (projectId, taskIds) = do liftIO $ putStrLn $ "Cleaning up " <> show (L.length taskIds) <> " test tasks" forM_ taskIds $ \taskId -> void $ todoist config (deleteTask taskId) liftIO $ putStrLn $ "Cleaning up test project: " <> show projectName void $ todoist config (P.deleteProject projectId) let runAction (projectId, taskIds) = void $ assertSucceeds $ action projectId taskIds bracket (assertSucceeds createResources) deleteResources runAction