{-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE OverloadedStrings #-} {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} module CommentIntegrationSpec (spec) where import Helpers ( assertSucceeds , buildTestTask , generateUniqueName , getTestConfig , liftTodoist ) import Web.Todoist.Domain.Comment ( CommentCreate , CommentId (..) , CommentParam (..) , Content (..) , TodoistCommentM (..) , newCommentBuilder , updateCommentBuilder ) import qualified Web.Todoist.Domain.Comment as C import qualified Web.Todoist.Domain.Project as P import Web.Todoist.Domain.Task (NewTask (..), TodoistTaskM (..)) import Web.Todoist.Domain.Types (ProjectId (..), TaskId (..)) import Web.Todoist.Internal.Config (TodoistConfig) import Web.Todoist.Internal.Error (TodoistError) import Web.Todoist.Lens ((^.)) import Web.Todoist.Runner (todoist) import Web.Todoist.Util.Builder (runBuilder, withProjectId, withTaskId) 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.Function (($)) import Data.Functor ((<$>)) import Data.Int (Int) import qualified Data.List as L import Data.Maybe (Maybe (..)) import Data.Ord ((>=)) import Data.Semigroup ((<>)) import Data.Text (Text, pack) import GHC.Base (mempty) import System.IO (IO, putStrLn) import Test.Hspec (Spec, describe, it, pendingWith, runIO, shouldBe, shouldSatisfy) import Text.Show (show) 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 commentOnProjectLifecycleSpec config commentOnTaskLifecycleSpec config updateCommentSpec config getCommentsSpec config getSingleCommentSpec config commentOnProjectLifecycleSpec :: TodoistConfig -> Spec commentOnProjectLifecycleSpec config = describe "Comment on project lifecycle (create, get, delete)" $ do it "creates, retrieves, and deletes a comment on a project" $ do -- Generate unique names projectName <- pack <$> generateUniqueName "IntegTest-CommentProject-Project" commentContent <- pack <$> generateUniqueName "IntegTest-CommentProject-Comment" -- Use withTestProjectComment for automatic cleanup withTestProjectComment config projectName commentContent $ \projectId commentId -> do -- Verify we can retrieve the comment comment <- liftTodoist config (getComment commentId) -- Extract comment fields for verification using lenses let retrievedId = comment ^. C.commentId retrievedContent = comment ^. C.commentContent retrievedProjectId = comment ^. C.commentProjectId retrievedTaskId = comment ^. C.commentTaskId -- Verify comment ID matches liftIO $ retrievedId `shouldBe` commentId -- Verify content matches liftIO $ retrievedContent `shouldBe` Content commentContent -- Verify project ID matches and task ID is Nothing liftIO $ retrievedProjectId `shouldBe` Just projectId liftIO $ retrievedTaskId `shouldBe` Nothing -- Test explicit delete (cleanup will handle if this fails) liftTodoist config (deleteComment commentId) commentOnTaskLifecycleSpec :: TodoistConfig -> Spec commentOnTaskLifecycleSpec config = describe "Comment on task lifecycle (create, get, delete)" $ do it "creates, retrieves, and deletes a comment on a task" $ do -- Generate unique names projectName <- pack <$> generateUniqueName "IntegTest-CommentTask-Project" taskContent <- pack <$> generateUniqueName "IntegTest-CommentTask-Task" commentContent <- pack <$> generateUniqueName "IntegTest-CommentTask-Comment" -- Use withTestTaskComment for automatic cleanup withTestTaskComment config projectName taskContent commentContent $ \taskId commentId -> do -- Verify we can retrieve the comment comment <- liftTodoist config (getComment commentId) -- Extract comment fields for verification using lenses let retrievedId = comment ^. C.commentId retrievedContent = comment ^. C.commentContent retrievedProjectId = comment ^. C.commentProjectId retrievedTaskId = comment ^. C.commentTaskId -- Verify comment ID matches liftIO $ retrievedId `shouldBe` commentId -- Verify content matches liftIO $ retrievedContent `shouldBe` Content commentContent -- Verify task ID matches and project ID is Nothing liftIO $ retrievedTaskId `shouldBe` Just taskId liftIO $ retrievedProjectId `shouldBe` Nothing -- Test explicit delete (cleanup will handle if this fails) liftTodoist config (deleteComment commentId) updateCommentSpec :: TodoistConfig -> Spec updateCommentSpec config = describe "Update comment" $ do it "creates a comment, updates its content, verifies changes" $ do -- Generate unique names projectName <- pack <$> generateUniqueName "IntegTest-UpdateComment-Project" originalContent <- pack <$> generateUniqueName "IntegTest-UpdateComment-Original" withTestProjectComment config projectName originalContent $ \_ commentId -> do -- Verify initial state comment1 <- liftTodoist config (getComment commentId) let initialContent = comment1 ^. C.commentContent liftIO $ initialContent `shouldBe` Content originalContent -- Update the comment let updatedContent = originalContent <> "-Updated" let commentUpdate = runBuilder (updateCommentBuilder updatedContent) mempty updatedComment <- liftTodoist config (updateComment commentUpdate commentId) -- Verify the response contains updated value let responseContent = updatedComment ^. C.commentContent liftIO $ responseContent `shouldBe` Content updatedContent -- Fetch the comment again to verify persistence comment2 <- liftTodoist config (getComment commentId) let persistedContent = comment2 ^. C.commentContent liftIO $ persistedContent `shouldBe` Content updatedContent getCommentsSpec :: TodoistConfig -> Spec getCommentsSpec config = describe "Get multiple comments" $ do it "creates 3 comments on a project, retrieves them via getComments" $ do -- Generate unique names projectName <- pack <$> generateUniqueName "IntegTest-GetComments-Project" baseName <- generateUniqueName "IntegTest-GetComments-Comment" let commentContent1 = pack $ baseName <> "-Comment1" let commentContent2 = pack $ baseName <> "-Comment2" let commentContent3 = pack $ baseName <> "-Comment3" let commentContents = [commentContent1, commentContent2, commentContent3] withTestProjectComments config projectName commentContents $ \projectId commentIds -> do -- Get all comments for this project let ProjectId {getProjectId = projIdText} = projectId let commentParam = CommentParam { project_id = Just projIdText , task_id = Nothing , cursor = Nothing , limit = Nothing , public_key = Nothing } comments <- liftTodoist config (getComments commentParam) -- Verify we got at least 3 comments (there might be more from previous tests) let commentCount = L.length comments liftIO $ commentCount `shouldSatisfy` (\n -> n >= (3 :: Int)) -- Extract comment IDs and contents from results let commentIdsResult = L.map (^. C.commentId) comments let commentContentsResult = L.map (^. C.commentContent) comments -- Verify all 3 comment IDs are present let [expectedId1, expectedId2, expectedId3] = commentIds liftIO $ (expectedId1 `L.elem` commentIdsResult) `shouldBe` True liftIO $ (expectedId2 `L.elem` commentIdsResult) `shouldBe` True liftIO $ (expectedId3 `L.elem` commentIdsResult) `shouldBe` True -- Verify all 3 comment contents are present liftIO $ (Content commentContent1 `L.elem` commentContentsResult) `shouldBe` True liftIO $ (Content commentContent2 `L.elem` commentContentsResult) `shouldBe` True liftIO $ (Content commentContent3 `L.elem` commentContentsResult) `shouldBe` True -- Verify each comment has the correct project_id forM_ comments $ \comment -> do let commentProjId = comment ^. C.commentProjectId commentTaskId = comment ^. C.commentTaskId case (commentProjId, commentTaskId) of (Just pid, Nothing) -> liftIO $ pid `shouldBe` ProjectId projIdText _ -> pure () -- Skip comments that don't match our filter getSingleCommentSpec :: TodoistConfig -> Spec getSingleCommentSpec config = describe "Get single comment by ID" $ do it "creates a comment and retrieves it by ID" $ do -- Generate unique names projectName <- pack <$> generateUniqueName "IntegTest-GetSingleComment-Project" commentContent <- pack <$> generateUniqueName "IntegTest-GetSingleComment-Comment" withTestProjectComment config projectName commentContent $ \projectId commentId -> do -- Get the comment by ID comment <- liftTodoist config (getComment commentId) -- Verify the comment -- Extract comment fields for verification using lenses let retrievedId = comment ^. C.commentId retrievedContent = comment ^. C.commentContent retrievedProjectId = comment ^. C.commentProjectId liftIO $ retrievedId `shouldBe` commentId liftIO $ retrievedContent `shouldBe` Content commentContent liftIO $ retrievedProjectId `shouldBe` Just projectId {- | Create a test project and comment, run an action with the comment ID, then clean up Uses bracket to ensure cleanup happens even if the action fails Comments are deleted before the project -} withTestProjectComment :: TodoistConfig -> Text -> -- project name Text -> -- comment content (ProjectId -> CommentId -> ExceptT TodoistError IO a) -> IO () withTestProjectComment config projectName commentContent 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 comment: " <> show commentContent let ProjectId {getProjectId = projIdText} = projectId let commentCreate = buildTestCommentForProject commentContent projIdText createdComment <- liftTodoist config (addComment commentCreate) let commentId = createdComment ^. C.commentId pure (projectId, commentId) let deleteResources (projectId, commentId) = do liftIO $ putStrLn $ "Cleaning up test comment: " <> show commentContent void $ todoist config (deleteComment commentId) liftIO $ putStrLn $ "Cleaning up test project: " <> show projectName void $ todoist config (P.deleteProject projectId) let runAction (projectId, commentId) = void $ assertSucceeds $ action projectId commentId bracket (assertSucceeds createResources) deleteResources runAction {- | Create a test project, task, and comment on the task, run an action, then clean up Uses bracket to ensure cleanup happens even if the action fails Comments are deleted before tasks, tasks before projects -} withTestTaskComment :: TodoistConfig -> Text -> -- project name Text -> -- task content Text -> -- comment content (TaskId -> CommentId -> ExceptT TodoistError IO a) -> IO () withTestTaskComment config projectName taskContent commentContent 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 TaskId {getTaskId = taskIdText} = taskId liftIO $ putStrLn $ "Creating test comment: " <> show commentContent let commentCreate = buildTestCommentForTask commentContent taskIdText createdComment <- liftTodoist config (addComment commentCreate) let commentId = createdComment ^. C.commentId pure (projectId, taskId, commentId) let deleteResources (projectId, taskId, commentId) = do liftIO $ putStrLn $ "Cleaning up test comment: " <> show commentContent void $ todoist config (deleteComment commentId) 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 (_, taskId, commentId) = void $ assertSucceeds $ action taskId commentId bracket (assertSucceeds createResources) deleteResources runAction {- | Create a test project and multiple comments, run an action with their IDs, then clean up Ensures all comments are deleted before the project is deleted -} withTestProjectComments :: TodoistConfig -> Text -> -- project name [Text] -> -- comment contents (ProjectId -> [CommentId] -> ExceptT TodoistError IO a) -> IO () withTestProjectComments config projectName commentContents 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 commentContents) <> " test comments" let ProjectId {getProjectId = projIdText} = projectId commentIds <- mapM ( \content -> do let commentCreate = buildTestCommentForProject content projIdText createdComment <- liftTodoist config (addComment commentCreate) pure $ createdComment ^. C.commentId ) commentContents pure (projectId, commentIds) let deleteResources (projectId, commentIds) = do liftIO $ putStrLn $ "Cleaning up " <> show (L.length commentIds) <> " test comments" forM_ commentIds $ \commentId -> void $ todoist config (deleteComment commentId) liftIO $ putStrLn $ "Cleaning up test project: " <> show projectName void $ todoist config (P.deleteProject projectId) let runAction (projectId, commentIds) = void $ assertSucceeds $ action projectId commentIds bracket (assertSucceeds createResources) deleteResources runAction {- | Build a test comment for a project using the Builder pattern Creates a CommentCreate with content and project_id for testing -} buildTestCommentForProject :: Text -> Text -> CommentCreate buildTestCommentForProject commentContent projectId = runBuilder (newCommentBuilder commentContent) (withProjectId projectId) {- | Build a test comment for a task using the Builder pattern Creates a CommentCreate with content and task_id for testing -} buildTestCommentForTask :: Text -> Text -> CommentCreate buildTestCommentForTask commentContent taskId = runBuilder (newCommentBuilder commentContent) (withTaskId taskId)