{-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE TypeApplications #-} module UserSpec ( spec ) where import Data.Generics.Labels () import Data.Time import Lens.Micro.GHC import Network.Reddit import Test.Hspec spec :: Spec spec = beforeAll (loadClient Nothing) . describe "Network.Reddit.User" $ sequence_ [ users , trophies , submissions , summaries , searches , moderated , banned ] users :: SpecWith Client users = it "gets a user" $ \c -> do user <- runReddit c $ getUser =<< mkUsername "edwardkmett" user ^. #userID `shouldBe` UserID "26009" user ^. #created `shouldBe` read @UTCTime "2007-07-13 07:11:06 +0000" user ^. #commentKarma `shouldSatisfy` (> 50000) user ^. #linkKarma `shouldSatisfy` (> 6000) trophies :: SpecWith Client trophies = it "gets a user's trophies" $ \c -> do ts <- runReddit c $ getUserTrophies =<< mkUsername "edwardkmett" case ts ^? each . filtered ((Just "4" ==) . (^. #awardID)) of Nothing -> expectationFailure "Failed to get correct user trophies" Just trophy -> do trophy ^. #name `shouldBe` "Best Comment" trophy ^. #trophyID `shouldBe` Just "y35z3" submissions :: SpecWith Client submissions = it "gets a user's submissions" $ \c -> do let opts = defaultItemOpts & (#itemTime ?~ AllTime) . (#itemSort ?~ Top) paginator = emptyPaginator & (#limit .~ 1) . (#opts .~ opts) username <- mkUsername "bgamari" ss <- runReddit c $ getUserSubmissions username paginator case ss ^? #children . _head of Nothing -> expectationFailure "Failed to get user ss" Just submission -> do submission ^. #submissionID `shouldBe` SubmissionID "4kdzp2" submission ^. #numComments `shouldBe` 124 summaries :: SpecWith Client summaries = it "gets user summaries" $ \c -> do account <- runReddit c $ getUser =<< mkUsername "edwardkmett" summary <- runReddit c . getUserSummary $ account ^. #userID summary ^. #userID `shouldBe` Just (UserID "26009") summary ^. #commentKarma `shouldSatisfy` (> 50000) summary ^. #linkKarma `shouldSatisfy` (> 6000) summary ^. #profileColor `shouldBe` Nothing summary ^. #profileOver18 `shouldBe` False searches :: SpecWith Client searches = it "searches users by name" $ \c -> do results <- runReddit c . firstPage $ searchUsers "edwardkmett" case results ^? _head of Nothing -> expectationFailure "Failed to search users" Just u -> do username <- mkUsername "edwardkmett" u ^. #username `shouldBe` username moderated :: SpecWith Client moderated = it "searches users by name" $ \c -> do ms <- runReddit c $ getUserModerated =<< mkUsername "edwardkmett" subname <- mkSubredditName "haskell" (ms ^.. each . #name) `shouldContain` [ subname ] banned :: SpecWith Client banned = it "throws the correct exception when getting a banned user" $ \c -> do username <- mkUsername "Unidan" let action = getUser username ex = \case UserIsBanned (BannedUser uname _ True) | uname == username -> True _ -> False runReddit c action `shouldThrow` ex