{-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE TypeApplications #-} module LiveSpec ( spec ) where import Data.Generics.Labels () import Data.Time import GHC.Exts ( fromList ) import Lens.Micro.GHC import Network.Reddit import Network.Reddit.Live import Test.Hspec spec :: Spec spec = beforeAll (loadClient Nothing) . describe "Network.Reddit.Live" $ sequence_ [ liveThread, contributors, updates, excess, discussions ] liveThread :: SpecWith Client liveThread = it "gets a livethread" $ \c -> do thread <- runReddit c . getLiveThread $ LiveThreadID "ta40l9u2ermf" thread ^. #title `shouldBe` "[Live] Test, please don't upvote." thread ^. #created `shouldBe` read @UTCTime "2014-07-23 17:07:51 +0000" thread ^. #liveState `shouldBe` Complete thread ^. #nsfw `shouldBe` False thread ^. #websocketURL `shouldBe` Nothing contributors :: SpecWith Client contributors = it "gets livethread contributors" $ \c -> do cs <- runReddit c . getLiveContributors $ LiveThreadID "ta40l9u2ermf" case cs ^? _head of Just contributor -> do (contributor ^. #permissions) `shouldBe` fromList [ Update ] contributor ^. #userID `shouldBe` UserID "bji9w" _ -> expectationFailure "Failed to get contributors" updates :: SpecWith Client updates = it "gets livethread updates" $ \c -> do us <- runReddit c . firstPage . getLiveUpdates $ LiveThreadID "ta40l9u2ermf" case us ^? _head of Just update -> do username <- mkUsername "pokoleo" update ^. #author `shouldBe` username update ^. #body `shouldBe` "Woah, this still exists" update ^. #stricken `shouldBe` False _ -> expectationFailure "Failed to get updates" excess :: SpecWith Client excess = it "gets livethread info in excess of API limit" $ \c -> do threads <- runReddit c . getAllLiveInfo $ LiveThreadID <$> replicate 101 "ta40l9u2ermf" length threads `shouldBe` 101 discussions :: SpecWith Client discussions = it "gets livethread discussions" $ \c -> do ds <- runReddit c $ getLiveDiscussions (LiveThreadID "11e4mknpbhjqr") emptyPaginator (ds ^. #children & length) `shouldBe` 4