{-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE TypeApplications #-} module MeSpec ( spec ) where import Data.Either import Data.Generics.Labels () import Lens.Micro.GHC import Network.Reddit import Profile import Test.Hspec spec :: Spec spec = beforeAll loadClientAndProfile . describe "Network.Reddit.Me" $ sequence_ [ account, multireddits, karma, friends, makeFriends ] account :: SpecWith (Client, TestProfile) account = it "gets the current user" $ \(c, profile) -> do me <- runReddit c getMe me ^. #username `shouldBe` profile ^. #username me ^. #userID `shouldBe` profile ^. #userID multireddits :: SpecWith (Client, TestProfile) multireddits = it "gets the current user's multireddits" $ \(c, _) -> do ms <- tryReddit @APIException c getMyMultireddits ms `shouldSatisfy` isRight karma :: SpecWith (Client, TestProfile) karma = it "gets the current user's karma" $ \(c, _) -> do k <- tryReddit @APIException c getMyKarma k `shouldSatisfy` isRight friends :: SpecWith (Client, TestProfile) friends = it "gets the current user's friends" $ \(c, _) -> do fs <- tryReddit @APIException c getMyFriends fs `shouldSatisfy` isRight makeFriends :: SpecWith (Client, TestProfile) makeFriends = it "makes friends with a user" $ \(c, _) -> do username <- mkUsername "heddit-dev" friend <- runReddit c $ makeFriend Nothing username friend2 <- runReddit c $ getMyFriend username friend2 `shouldBe` friend fs <- runReddit c getMyFriends fs ^.. each `shouldContain` [ friend ] runReddit c $ unFriend username fs2 <- runReddit c getMyFriends fs2 ^.. each `shouldNotContain` [ friend ] loadClientAndProfile :: IO (Client, TestProfile) loadClientAndProfile = (,) <$> loadClient Nothing <*> loadProfile