{-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE TypeApplications #-} -- | module SubmissionSpec ( spec ) where import Data.Generics.Labels () import Data.Sequence ( Seq((:<|)) ) import Data.Time import Lens.Micro.GHC import Network.Reddit import Test.Hspec {- HLINT ignore "Redundant do"-} spec :: Spec spec = beforeAll (loadClient Nothing) . describe "Network.Reddit.Submission" $ sequence_ [ single, multiple, excess, none, hideUnhide ] single :: SpecWith Client single = it "gets a single submission by URL" $ \c -> do submission <- runReddit c $ getSubmissionByURL "https://reddit.com/comments/6x7ms0/" author <- mkUsername "ysangkok" subreddit <- mkSubredditName "haskell" submission ^. #author `shouldBe` author submission ^. #content `shouldBe` content submission ^. #title `shouldBe` title submission ^. #subreddit `shouldBe` subreddit submission ^. #numComments `shouldBe` 41 submission ^. #submissionID `shouldBe` SubmissionID "6x7ms0" submission ^. #created `shouldBe` read @UTCTime "2017-08-31 15:42:20 +0000" where content = ExternalLink $ mconcat [ "https://bartoszmilewski.com/" , "2014/10/28/" , "category-theory-for-programmers-the-preface/" ] title = mconcat [ "\"Category Theory for Programmers\" " , "has been finished!" ] multiple :: SpecWith Client multiple = it "gets multiple submissions" $ \c -> do submissions <- runReddit c . getSubmissions defaultItemOpts $ SubmissionID <$> [ "50389g", "eume40" ] case submissions of s1 :<| s2 :<| _ -> do s1 ^. #title `shouldBe` "Resignation" s2 ^. #title `shouldBe` "One Haskell IDE to rule them all" _ -> expectationFailure "Failed to fetch multiple submissions" excess :: SpecWith Client excess = it "gets submissions in excess of API limit" $ \c -> do submissions <- runReddit c . getSubmissions defaultItemOpts $ SubmissionID <$> replicate 101 "50389g" length submissions `shouldBe` 101 none :: SpecWith Client none = it "gracefully gets no submissions with empty container" $ \c -> do submissions <- runReddit c $ getSubmissions defaultItemOpts [] submissions `shouldBe` mempty hideUnhide :: SpecWith Client hideUnhide = -- This is rather fragile way of testing this functionality. It /appears/ -- that newly hidden items are always put at the front of the list in the -- API endpoint for hidden things it "hides and unhides submissions" $ \c -> do let getHidden = runReddit c $ firstPage getMyHidden sid = SubmissionID "4kdzp2" runReddit c $ hideSubmission sid hidden1 <- getHidden <&> (^? _head . #_SubmissionItem . #submissionID) hidden1 `shouldBe` Just sid runReddit c $ unhideSubmission sid hidden2 <- getHidden <&> (^.. each . #_SubmissionItem . #submissionID) hidden2 `shouldNotContain` [ sid ]