Skip to content

Instantly share code, notes, and snippets.

@duane
Created December 27, 2011 11:10
Show Gist options
  • Save duane/1523318 to your computer and use it in GitHub Desktop.
Save duane/1523318 to your computer and use it in GitHub Desktop.
Reddit aeson/bytestring
> {-# LANGUAGE OverloadedStrings #-}
This is the main driver of the program.
> module Main where
We need System.Environment for access command line arguments:
> import System.Environment (getArgs)
We need System.Exit for providing a non-zero exit status:
> import System.Exit (exitWith, ExitCode (ExitFailure))
We need System.Posix.Unistd for the sleep function:
> import System.Posix.Unistd (sleep)
Network.Curl for fetching HTTP data
> import Network.Curl
ByteString for UTF8 encoding
> import Data.ByteString hiding (map)
> import Data.ByteString.UTF8 (fromString)
Data.Aeson for JSON decoding
> import Data.Aeson
Finally, restrict prelude so it doesn't conflict with bytestring.
> import Prelude hiding (putStrLn)
This file is in the Public Domain. No rights reserved.
This program was written by Duane Bailey on Dec 27th, 2011.
The purpose of the program is to "watch" the a subreddit given as a parameter.
The first time the program fetches the front-page links on the homepage, the
program outputs `n` links on the front page, where n is a variable. In
successive update, the program prints out links which made the top `n` links on
the subreddit since the last update.
First, let us define the usage.
> printUsage :: IO ()
> printUsage = do
> putStrLn "USAGE: redw SUBREDDIT LINKS"
> putStrLn "\tSUBREDDIT: The subreddit to be watched."
> putStrLn "\tN: The number of links that qualifies the front page."
Therefore, the driving function is simple:
> watch_driver :: [String] -> IO ()
> watch_driver (subreddit : links : []) = watch subreddit $ read links
> watch_driver _ = do
> printUsage
> exitWith $ ExitFailure 1
This, however, is not the entry function; main is defined as thus:
> main :: IO ()
> main = getArgs >>= watch_driver
> watch :: String -> Int -> IO ()
> watch subr links = do
> curlGetString (jsonURLForSubreddit subr) [CurlConnectTimeout 10] >>= printJSON
> where printJSON (CurlOK, json) = do
> let links = (decode $ fromString json) :: Maybe Subreddit
> putStrLn $ fromString $ show links
> printJSON (_, _) = return ()
Defining the subreddit url for the subreddit is easy:
> jsonURLForSubreddit :: String -> String
> jsonURLForSubreddit subreddit = "http://www.reddit.com/r/" ++ subreddit ++ ".json"
But let's define the main datatypes of this program. Fetching reddit stories is
rather simple: it centers around the "link." Let's define that type now:
> data Link = Link {
> score :: Int,
> title :: String,
> link :: String,
> submitter :: String,
> comments :: Int,
> subreddit :: String
> } deriving Show
And, the subreddit, which stores an `n` links:
> data Subreddit = Subreddit {
> links :: [Link]
> }
Of course, the requests to the api don't allow returning single links at a
time, unfortunately, so parsing the json means parsing an array two layers into
the JSON tree.
> jsonParseError = "Unable to parse JSON resulat as known API instance."
> instance FromJSON Subreddit where
> parseJSON (Object o) =
> let dat = o .: "data"
> in case o of
> Object d -> Subreddit $ map parseJSONLink (d .: "children")
> _ -> fail jsonParseError
Of course, we still need to define the link parser itself. This is simple using Aeson, however, so will will define the parser as following:
> parseJSONLink (Object o) =
> let kind = o .: "kind"
> dat = o .: "data"
> in if kind /= "t3"
> then fail jsonParseError
> else Link $ (read $ dat .: "score") (dat .: "title") (dat .: "url") (dat .: "author") (read $ dat .: "num_comments") (dat .: "subreddit")
> parseJsonLink _ = fail jsonParseError
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment