{-# LANGUAGE TypeApplications #-} module Main where import Data.Aeson ( eitherDecodeFileStrict' ) import Data.Either ( isRight ) import Data.Sequence ( Seq ) import Network.Reddit.Types import Network.Reddit.Types.Account import Network.Reddit.Types.Award import Network.Reddit.Types.Comment import Network.Reddit.Types.Emoji import Network.Reddit.Types.Flair import Network.Reddit.Types.Live import Network.Reddit.Types.Message import Network.Reddit.Types.Moderation import Network.Reddit.Types.Multireddit import Network.Reddit.Types.Submission import Network.Reddit.Types.Subreddit import Network.Reddit.Types.Widget import Network.Reddit.Types.Wiki import Test.Hspec main :: IO () main = sequence_ [ decodeAccountTypes , decodeCommentTypes , decodeSubmissionTypes , decodeSubredditTypes , decodeMessageTypes , decodeModerationTypes , decodeFlairTypes , decodeWikiTypes , decodeWidgetTypes , decodeEmojiTypes , decodeLiveTypes , decodeAwardTypes ] {- HLINT ignore "Redundant do"-} decodeAccountTypes :: IO () decodeAccountTypes = hspec $ do describe "Network.Reddit.Types.Account" $ do it "decodes Account" $ do userAccount <- eitherDecodeFileStrict' @Account $ typesDataPath "user-account.json" userAccount `shouldSatisfy` isRight it "decodes FriendList" $ do friendList <- eitherDecodeFileStrict' @FriendList $ typesDataPath "friend-list.json" friendList `shouldSatisfy` isRight it "decodes KarmaList" $ do karmaList <- eitherDecodeFileStrict' @KarmaList $ typesDataPath "karma-list.json" karmaList `shouldSatisfy` isRight it "decodes TrophyList" $ do trophyList <- eitherDecodeFileStrict' @TrophyList $ typesDataPath "trophy-list.json" trophyList `shouldSatisfy` isRight it "decodes Preferences" $ do trophyList <- eitherDecodeFileStrict' @Preferences $ typesDataPath "prefs.json" trophyList `shouldSatisfy` isRight decodeCommentTypes :: IO () decodeCommentTypes = hspec $ do describe "Network.Reddit.Types.Comment" $ do it "decodes (Listing CommentID Comment)" $ do commentListing <- eitherDecodeFileStrict' @(Listing CommentID Comment) $ typesDataPath "comment-listing.json" commentListing `shouldSatisfy` isRight decodeSubmissionTypes :: IO () decodeSubmissionTypes = hspec $ do describe "Network.Reddit.Types.Submission" $ do it "decodes Submission" $ do submission <- eitherDecodeFileStrict' @Submission $ typesDataPath "submission.json" submission `shouldSatisfy` isRight describe "Network.Reddit.Types.Collection" $ do it "decodes Collection" $ do collection <- eitherDecodeFileStrict' @Collection $ typesDataPath "collection.json" collection `shouldSatisfy` isRight decodeSubredditTypes :: IO () decodeSubredditTypes = hspec $ do describe "Network.Reddit.Types.Subreddit" $ do it "decodes Subreddit" $ do sr <- eitherDecodeFileStrict' @Subreddit $ typesDataPath "subreddit.json" sr `shouldSatisfy` isRight it "decodes PostRequirements" $ do postRequirements <- eitherDecodeFileStrict' @PostRequirements $ typesDataPath "post-requirements.json" postRequirements `shouldSatisfy` isRight it "decodes SubredditRule" $ do postRequirements <- eitherDecodeFileStrict' @SubredditRule $ typesDataPath "rule.json" postRequirements `shouldSatisfy` isRight it "decodes Multireddit" $ do postRequirements <- eitherDecodeFileStrict' @(Seq Multireddit) $ typesDataPath "multireddits.json" postRequirements `shouldSatisfy` isRight decodeMessageTypes :: IO () decodeMessageTypes = hspec $ do describe "Network.Reddit.Types.Message" $ do it "decodes Message" $ do msg <- eitherDecodeFileStrict' @(Listing MessageID Message) $ typesDataPath "message-listing.json" msg `shouldSatisfy` isRight decodeModerationTypes :: IO () decodeModerationTypes = hspec $ do describe "Network.Reddit.Types.Moderation" $ do it "decodes Ban" $ do ban <- eitherDecodeFileStrict' @Ban $ typesDataPath "ban.json" ban `shouldSatisfy` isRight it "decodes SubredditSettings" $ do settings <- eitherDecodeFileStrict' @SubredditSettings $ typesDataPath "subreddit-settings.json" settings `shouldSatisfy` isRight it "decodes Modmail" $ do settings <- eitherDecodeFileStrict' @Modmail $ typesDataPath "modmail.json" settings `shouldSatisfy` isRight it "decodes (Listing ModActionID ModAction)" $ do modlog <- eitherDecodeFileStrict' @(Listing ModActionID ModAction) $ typesDataPath "modaction-listing.json" modlog `shouldSatisfy` isRight it "decodes ModInviteeList" $ do invitees <- eitherDecodeFileStrict' @ModInviteeList $ typesDataPath "modinvitee-list.json" invitees `shouldSatisfy` isRight it "decodes Traffic" $ do traffic <- eitherDecodeFileStrict' @Traffic $ typesDataPath "traffic.json" traffic `shouldSatisfy` isRight it "decodes S3ModerationLease" $ do lease <- eitherDecodeFileStrict' @S3ModerationLease $ typesDataPath "upload-lease.json" lease `shouldSatisfy` isRight decodeFlairTypes :: IO () decodeFlairTypes = hspec $ do describe "Network.Reddit.Types.Flair" $ do it "decodes FlairTemplate" $ do flairTemplate <- eitherDecodeFileStrict' @FlairTemplate $ typesDataPath "flair-template.json" flairTemplate `shouldSatisfy` isRight describe "Network.Reddit.Types.Flair" $ do it "decodes FlairChoice" $ do flairChoices <- eitherDecodeFileStrict' @FlairChoiceList $ typesDataPath "flair-response.json" flairChoices `shouldSatisfy` isRight describe "Network.Reddit.Types.Flair" $ do it "decodes UserFlair" $ do userFlair <- eitherDecodeFileStrict' @CurrentUserFlair $ typesDataPath "flair-response.json" userFlair `shouldSatisfy` isRight decodeWikiTypes :: IO () decodeWikiTypes = hspec $ do describe "Network.Reddit.Types.Wiki" $ do it "decodes WikiPage" $ do wikiPage <- eitherDecodeFileStrict' @WikiPage $ typesDataPath "wikipage.json" wikiPage `shouldSatisfy` isRight it "decodes WikiRevision" $ do wikiRevListing <- eitherDecodeFileStrict' -- @(Listing WikiRevisionID WikiRevision) $ typesDataPath "wiki-revision-listing.json" wikiRevListing `shouldSatisfy` isRight it "decodes WikiPageSettings" $ do wikipageSettings <- eitherDecodeFileStrict' @WikiPageSettings $ typesDataPath "wikipage-settings.json" wikipageSettings `shouldSatisfy` isRight decodeWidgetTypes :: IO () decodeWidgetTypes = hspec $ do describe "Network.Reddit.Types.Widget" $ do it "decodes Widget" $ do widgets <- eitherDecodeFileStrict' @WidgetList $ typesDataPath "widgets.json" widgets `shouldSatisfy` isRight decodeEmojiTypes :: IO () decodeEmojiTypes = hspec $ do describe "Network.Reddit.Types.Emoji" $ do it "decodes Widget" $ do emojis <- eitherDecodeFileStrict' @EmojiList $ typesDataPath "emoji-list.json" emojis `shouldSatisfy` isRight decodeLiveTypes :: IO () decodeLiveTypes = hspec $ do describe "Network.Reddit.Types.Live" $ do it "decodes LiveThread" $ do liveThread <- eitherDecodeFileStrict' @(Listing LiveThreadID LiveThread) $ typesDataPath "live-thread.json" liveThread `shouldSatisfy` isRight it "decodes LiveUpdate" $ do liveUpdates <- eitherDecodeFileStrict' @(Listing LiveUpdateID LiveUpdate) $ typesDataPath "live-update.json" liveUpdates `shouldSatisfy` isRight it "decodes LiveContributorList" $ do liveContributors <- eitherDecodeFileStrict' @LiveContributorList $ typesDataPath "live-contributor-list.json" liveContributors `shouldSatisfy` isRight decodeAwardTypes :: IO () decodeAwardTypes = hspec $ do describe "Network.Reddit.Types.Award" $ do it "decodes Awarding" $ do award <- eitherDecodeFileStrict' @[Awarding] $ typesDataPath "awarding.json" award `shouldSatisfy` isRight typesDataPath :: FilePath -> FilePath typesDataPath = (<>) "./tests/data/types/"