{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE TypeApplications #-} module Profile ( loadProfile, TestProfile(TestProfile) ) where import Data.Aeson ( FromJSON(parseJSON) , defaultOptions , eitherDecodeFileStrict , genericParseJSON ) import GHC.Generics ( Generic ) import Network.Reddit import UnliftIO import UnliftIO.Directory -- | Info on the authenticated user you are running the tests as data TestProfile = TestProfile { username :: Username , userID :: UserID -- | You must be a moderator on this subreddit , subreddit :: SubredditName } deriving stock ( Show, Eq, Generic ) instance FromJSON TestProfile where parseJSON = genericParseJSON defaultOptions -- | Load the test profile from disk loadProfile :: MonadUnliftIO m => m TestProfile loadProfile = do cwd <- getCurrentDirectory cfgDir <- getXdgDirectory XdgConfig "heddit" findFile [ cwd, cfgDir ] "profile.json" >>= \case Nothing -> throwIO . userError $ mconcat [ "No profile.json found for running tests" , " , please create on in $PWD" , " or $XDG_CONFIG_HOME/heddit" ] Just f -> either (throwIO . userError) pure =<< liftIO (eitherDecodeFileStrict @TestProfile f)