{-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE TypeApplications #-} module CommentSpec ( spec ) where import Data.Generics.Labels () import Data.Sequence ( Seq((:<|)) ) import Data.Time import Lens.Micro.GHC import Network.Reddit import Test.Hspec spec :: Spec spec = beforeAll (loadClient Nothing) . describe "Network.Reddit.Comment" $ sequence_ [ single, multiple, replies, saveUnsave, loadMore ] single :: SpecWith Client single = it "gets a single comment" $ \c -> do comment <- runReddit c . getComment $ CommentID "dmdwy0x" username <- mkUsername "GreenEyedFriend" subname <- mkSubredditName "haskell" comment ^. #author `shouldBe` username comment ^. #created `shouldBe` read @UTCTime "2017-08-31 17:40:15 +0000" comment ^. #subreddit `shouldBe` subname comment ^. #edited `shouldBe` Nothing comment ^. #linkID `shouldBe` SubmissionID "6x7ms0" multiple :: SpecWith Client multiple = it "gets multiple comments" $ \c -> do comments <- runReddit c . getComments defaultItemOpts $ CommentID <$> [ "dmdwy0x", "dmdr4ji" ] case comments of c1 :<| c2 :<| _ -> do author1 <- mkUsername "GreenEyedFriend" author2 <- mkUsername "semanticistZombie" c1 ^. #author `shouldBe` author1 c2 ^. #author `shouldBe` author2 _ -> expectationFailure "Failed to fetch multiple comments" replies :: SpecWith Client replies = it "gets child comments" $ \c -> do noReplies <- runReddit c . getComment $ CommentID "dmdwy0x" noReplies ^. #replies `shouldBe` mempty hasReplies <- runReddit c $ withReplies defaultItemOpts noReplies case hasReplies ^? #replies . each . #_TopLevel of Nothing -> expectationFailure "Failed to load child comments" Just comment -> do username <- mkUsername "MagicMurderBagYT" comment ^. #author `shouldBe` username (comment ^.. #replies . each . #_TopLevel . #commentID) `shouldContain` [ CommentID "dme9869" ] saveUnsave :: SpecWith Client saveUnsave = it "saves and unsaves comments" $ \c -> do runReddit c $ saveComment commentID saved <- runReddit c $ firstPage getMySaved case saved ^? each . #_CommentItem of Nothing -> expectationFailure "Failed to save comment" Just comment -> do username <- mkUsername "Apterygiformes" comment ^. #commentID `shouldBe` commentID comment ^. #author `shouldBe` username comment ^. #body `shouldBe` "Haha oh no" comment ^. #score `shouldSatisfy` maybe True (< 0) runReddit c $ unsaveComment commentID saved2 <- runReddit c . getMySaved $ emptyPaginator & #limit .~ 100 (saved2 ^.. #children . each . #_CommentItem . #commentID) `shouldNotContain` [ commentID ] where commentID = CommentID "dme1kf9" loadMore :: SpecWith Client loadMore = it "loads more child comments" $ \c -> do children <- runReddit c $ getChildComments submissionID case children ^? each . #_More of Nothing -> expectationFailure "Failed to get collapsed submission comments" Just more -> do more ^. #count `shouldBe` 207 loaded <- runReddit c $ loadMoreComments (Just 1) defaultItemOpts submissionID more case loaded ^.. each . #_TopLevel of [ comment ] -> do username <- mkUsername "i_pk_pjers_i" comment ^. #author `shouldBe` username case loaded ^? each . #_More of Just more2 -> more2 ^. #count `shouldBe` 206 _ -> loadFailed _ -> loadFailed where submissionID = SubmissionID "aeufh6" loadFailed = expectationFailure "Loaded the wrong number of child comments"