{-# LANGUAGE OverloadedLabels #-} module Mods where import Control.Monad.IO.Class ( MonadIO(liftIO) ) import Data.Foldable ( for_, maximumBy ) import Data.Generics.Labels () import Data.Generics.Wrapped import Data.Ord ( comparing ) import qualified Data.Text.IO as T import Lens.Micro.Platform import Network.Reddit import Network.Reddit.Moderation ( getModerators ) -- | This tiny program will get the current moderators of r\/haskell, print the -- link karma for each one, and then find the mod with the highest karma and print -- the username. At the moment, running this example produces: -- -- > dons has 76424 -- > jfredett has 748 -- > edwardkmett has 6180 -- > taylorfausak has 6216 -- > Iceland_jack has 1402 -- > BoteboTsebo has 229 -- > AutoModerator has 1000 -- > The mod with the most karma is dons -- main :: IO () main = loadClient Nothing >>= (`runReddit` modsKarmaInfo) where modsKarmaInfo = do mods <- (getModerators =<< mkSubredditName "haskell") >>= traverse (getUser . (^. #username)) for_ mods $ \m -> liftIO . T.putStrLn $ mconcat [ m ^. #username & wrappedTo , " has " , m ^. #linkKarma . to show . packed ] liftIO . T.putStrLn $ mconcat [ "The mod with the most karma is " , topKarma mods ^. #username & wrappedTo ] topKarma = maximumBy (comparing (^. #linkKarma))