hackernews-1.2.0.0: API for Hacker News

Copyright(c) David Johnson 2014-2016
Maintainerdjohnson.m@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Web.HackerNews

Contents

Description

Synopsis

Hacker News API

type HackerNewsAPI = ("item" :> (HackerCapture ItemId :> Get '[JSON] Item)) :<|> (("user" :> (HackerCapture UserId :> Get '[JSON] User)) :<|> (("maxitem.json" :> Get '[JSON] MaxItem) :<|> (("topstories.json" :> Get '[JSON] TopStories) :<|> (("newstories.json" :> Get '[JSON] NewStories) :<|> (("beststories.json" :> Get '[JSON] BestStories) :<|> (("askstories.json" :> Get '[JSON] AskStories) :<|> (("showstories.json" :> Get '[JSON] ShowStories) :<|> (("jobstories.json" :> Get '[JSON] JobStories) :<|> ("updates.json" :> Get '[JSON] Updates))))))))) Source #

HackerNews API

Custom combinators

data HackerCapture a Source #

Custom combinator for appending '.json' to Item query

Instances

(ToHttpApiData a, HasClient * api) => HasClient * ((:>) * * (HackerCapture a) api) Source #

Custom combinator HasClient instance

Associated Types

type Client ((:>) * * (HackerCapture a) api) (api :: (:>) * * (HackerCapture a) api) :: * #

Methods

clientWithRoute :: Proxy ((* :> *) (HackerCapture a) api) api -> Req -> Client ((* :> *) (HackerCapture a) api) api #

type Client * ((:>) * * (HackerCapture a) api) Source # 
type Client * ((:>) * * (HackerCapture a) api) = a -> Client * api

API functions

Core Types

data Item Source #

Stories, comments, jobs, Ask HNs and even polls are just items. They're identified by their ids, which are unique integers, and live under https://hacker-news.firebaseio.com/v0/item/.

Instances

Eq Item Source # 

Methods

(==) :: Item -> Item -> Bool #

(/=) :: Item -> Item -> Bool #

Show Item Source # 

Methods

showsPrec :: Int -> Item -> ShowS #

show :: Item -> String #

showList :: [Item] -> ShowS #

Generic Item Source # 

Associated Types

type Rep Item :: * -> * #

Methods

from :: Item -> Rep Item x #

to :: Rep Item x -> Item #

Arbitrary Item Source # 

Methods

arbitrary :: Gen Item #

shrink :: Item -> [Item] #

ToJSON Item Source # 
FromJSON Item Source # 
type Rep Item Source # 
type Rep Item = D1 (MetaData "Item" "Web.HackerNews.Types" "hackernews-1.2.0.0-C7hKVOmSPnJK48DfCKv8af" False) (C1 (MetaCons "Item" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "itemId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ItemId))) ((:*:) (S1 (MetaSel (Just Symbol "itemDeleted") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Deleted))) (S1 (MetaSel (Just Symbol "itemType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ItemType)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "itemBy") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe UserName))) (S1 (MetaSel (Just Symbol "itemTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Time)))) ((:*:) (S1 (MetaSel (Just Symbol "itemText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ItemText))) (S1 (MetaSel (Just Symbol "itemDead") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Dead)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "itemParent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Parent))) ((:*:) (S1 (MetaSel (Just Symbol "itemKids") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Kids))) (S1 (MetaSel (Just Symbol "itemURL") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe URL))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "itemScore") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Score))) (S1 (MetaSel (Just Symbol "itemTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Title)))) ((:*:) (S1 (MetaSel (Just Symbol "itemParts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Parts))) (S1 (MetaSel (Just Symbol "itemDescendants") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Descendants))))))))

data User Source #

Users are identified by case-sensitive ids, and live under https://hacker-news.firebaseio.com/v0/user/. Only users that have public activity (comments or story submissions) on the site are available through the API.

Constructors

User 

Fields

Instances

Eq User Source # 

Methods

(==) :: User -> User -> Bool #

(/=) :: User -> User -> Bool #

Show User Source # 

Methods

showsPrec :: Int -> User -> ShowS #

show :: User -> String #

showList :: [User] -> ShowS #

Generic User Source # 

Associated Types

type Rep User :: * -> * #

Methods

from :: User -> Rep User x #

to :: Rep User x -> User #

Arbitrary User Source # 

Methods

arbitrary :: Gen User #

shrink :: User -> [User] #

ToJSON User Source # 
FromJSON User Source # 
type Rep User Source # 

data Updates Source #

The item and profile changes are at https://hacker-news.firebaseio.com/v0/updates

Constructors

Updates 

Fields

newtype MaxItem Source #

The current largest item id is at https://hacker-news.firebaseio.com/v0/maxitem. You can walk backward from here to discover all items.

Constructors

MaxItem ItemId 

newtype UserId Source #

The user's unique username. Case-sensitive. Required.

Constructors

UserId Text 

newtype ItemId Source #

The item's unique id.

Constructors

ItemId Int 

newtype Deleted Source #

true if the item is deleted.

Constructors

Deleted Bool 

data ItemType Source #

The type of item. One of "job", "story", "comment", "poll", or "pollopt"

Constructors

Job 
Story 
Comment 
Poll 
PollOpt 

Instances

Enum ItemType Source # 
Eq ItemType Source # 
Show ItemType Source # 
Generic ItemType Source # 

Associated Types

type Rep ItemType :: * -> * #

Methods

from :: ItemType -> Rep ItemType x #

to :: Rep ItemType x -> ItemType #

Arbitrary ItemType Source # 
ToJSON ItemType Source # 
FromJSON ItemType Source # 
type Rep ItemType Source # 
type Rep ItemType = D1 (MetaData "ItemType" "Web.HackerNews.Types" "hackernews-1.2.0.0-C7hKVOmSPnJK48DfCKv8af" False) ((:+:) ((:+:) (C1 (MetaCons "Job" PrefixI False) U1) (C1 (MetaCons "Story" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Comment" PrefixI False) U1) ((:+:) (C1 (MetaCons "Poll" PrefixI False) U1) (C1 (MetaCons "PollOpt" PrefixI False) U1))))

newtype UserName Source #

The username of the item's author.

Constructors

UserName Text 

newtype Time Source #

Creation date of the item, in Unix Time.

Constructors

Time Integer 

Instances

Eq Time Source # 

Methods

(==) :: Time -> Time -> Bool #

(/=) :: Time -> Time -> Bool #

Show Time Source # 

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

Generic Time Source # 

Associated Types

type Rep Time :: * -> * #

Methods

from :: Time -> Rep Time x #

to :: Rep Time x -> Time #

Arbitrary Time Source # 

Methods

arbitrary :: Gen Time #

shrink :: Time -> [Time] #

ToJSON Time Source # 
FromJSON Time Source # 
type Rep Time Source # 
type Rep Time = D1 (MetaData "Time" "Web.HackerNews.Types" "hackernews-1.2.0.0-C7hKVOmSPnJK48DfCKv8af" True) (C1 (MetaCons "Time" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))

newtype ItemText Source #

The comment, story or poll text. HTML.

Constructors

ItemText Text 

newtype Dead Source #

true if the item is dead.

Constructors

Dead Bool 

Instances

Eq Dead Source # 

Methods

(==) :: Dead -> Dead -> Bool #

(/=) :: Dead -> Dead -> Bool #

Show Dead Source # 

Methods

showsPrec :: Int -> Dead -> ShowS #

show :: Dead -> String #

showList :: [Dead] -> ShowS #

Generic Dead Source # 

Associated Types

type Rep Dead :: * -> * #

Methods

from :: Dead -> Rep Dead x #

to :: Rep Dead x -> Dead #

Arbitrary Dead Source # 

Methods

arbitrary :: Gen Dead #

shrink :: Dead -> [Dead] #

ToJSON Dead Source # 
FromJSON Dead Source # 
type Rep Dead Source # 
type Rep Dead = D1 (MetaData "Dead" "Web.HackerNews.Types" "hackernews-1.2.0.0-C7hKVOmSPnJK48DfCKv8af" True) (C1 (MetaCons "Dead" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))

newtype Parent Source #

The item's parent. For comments, either another comment or the relevant story. For pollopts, the relevant poll.

Constructors

Parent ItemId 

Instances

Eq Parent Source # 

Methods

(==) :: Parent -> Parent -> Bool #

(/=) :: Parent -> Parent -> Bool #

Show Parent Source # 
Generic Parent Source # 

Associated Types

type Rep Parent :: * -> * #

Methods

from :: Parent -> Rep Parent x #

to :: Rep Parent x -> Parent #

Arbitrary Parent Source # 
ToJSON Parent Source # 
FromJSON Parent Source # 
type Rep Parent Source # 
type Rep Parent = D1 (MetaData "Parent" "Web.HackerNews.Types" "hackernews-1.2.0.0-C7hKVOmSPnJK48DfCKv8af" True) (C1 (MetaCons "Parent" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ItemId)))

newtype Kids Source #

The ids of the item's comments, in ranked display order.

Constructors

Kids [ItemId] 

Instances

Eq Kids Source # 

Methods

(==) :: Kids -> Kids -> Bool #

(/=) :: Kids -> Kids -> Bool #

Show Kids Source # 

Methods

showsPrec :: Int -> Kids -> ShowS #

show :: Kids -> String #

showList :: [Kids] -> ShowS #

Generic Kids Source # 

Associated Types

type Rep Kids :: * -> * #

Methods

from :: Kids -> Rep Kids x #

to :: Rep Kids x -> Kids #

Arbitrary Kids Source # 

Methods

arbitrary :: Gen Kids #

shrink :: Kids -> [Kids] #

ToJSON Kids Source # 
FromJSON Kids Source # 
type Rep Kids Source # 
type Rep Kids = D1 (MetaData "Kids" "Web.HackerNews.Types" "hackernews-1.2.0.0-C7hKVOmSPnJK48DfCKv8af" True) (C1 (MetaCons "Kids" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ItemId])))

newtype URL Source #

The URL of the story.

Constructors

URL Text 

Instances

Eq URL Source # 

Methods

(==) :: URL -> URL -> Bool #

(/=) :: URL -> URL -> Bool #

Show URL Source # 

Methods

showsPrec :: Int -> URL -> ShowS #

show :: URL -> String #

showList :: [URL] -> ShowS #

Generic URL Source # 

Associated Types

type Rep URL :: * -> * #

Methods

from :: URL -> Rep URL x #

to :: Rep URL x -> URL #

Arbitrary URL Source # 

Methods

arbitrary :: Gen URL #

shrink :: URL -> [URL] #

ToJSON URL Source # 
FromJSON URL Source # 
type Rep URL Source # 
type Rep URL = D1 (MetaData "URL" "Web.HackerNews.Types" "hackernews-1.2.0.0-C7hKVOmSPnJK48DfCKv8af" True) (C1 (MetaCons "URL" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype Score Source #

The story's score, or the votes for a pollopt.

Constructors

Score Int 

Instances

Eq Score Source # 

Methods

(==) :: Score -> Score -> Bool #

(/=) :: Score -> Score -> Bool #

Show Score Source # 

Methods

showsPrec :: Int -> Score -> ShowS #

show :: Score -> String #

showList :: [Score] -> ShowS #

Generic Score Source # 

Associated Types

type Rep Score :: * -> * #

Methods

from :: Score -> Rep Score x #

to :: Rep Score x -> Score #

Arbitrary Score Source # 

Methods

arbitrary :: Gen Score #

shrink :: Score -> [Score] #

ToJSON Score Source # 
FromJSON Score Source # 
type Rep Score Source # 
type Rep Score = D1 (MetaData "Score" "Web.HackerNews.Types" "hackernews-1.2.0.0-C7hKVOmSPnJK48DfCKv8af" True) (C1 (MetaCons "Score" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

newtype Title Source #

The title of the story, poll or job.

Constructors

Title Text 

Instances

Eq Title Source # 

Methods

(==) :: Title -> Title -> Bool #

(/=) :: Title -> Title -> Bool #

Show Title Source # 

Methods

showsPrec :: Int -> Title -> ShowS #

show :: Title -> String #

showList :: [Title] -> ShowS #

Generic Title Source # 

Associated Types

type Rep Title :: * -> * #

Methods

from :: Title -> Rep Title x #

to :: Rep Title x -> Title #

Arbitrary Title Source # 

Methods

arbitrary :: Gen Title #

shrink :: Title -> [Title] #

ToJSON Title Source # 
FromJSON Title Source # 
type Rep Title Source # 
type Rep Title = D1 (MetaData "Title" "Web.HackerNews.Types" "hackernews-1.2.0.0-C7hKVOmSPnJK48DfCKv8af" True) (C1 (MetaCons "Title" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype Parts Source #

A list of related pollopts, in display order.

Constructors

Parts [ItemId] 

Instances

Eq Parts Source # 

Methods

(==) :: Parts -> Parts -> Bool #

(/=) :: Parts -> Parts -> Bool #

Show Parts Source # 

Methods

showsPrec :: Int -> Parts -> ShowS #

show :: Parts -> String #

showList :: [Parts] -> ShowS #

Generic Parts Source # 

Associated Types

type Rep Parts :: * -> * #

Methods

from :: Parts -> Rep Parts x #

to :: Rep Parts x -> Parts #

Arbitrary Parts Source # 

Methods

arbitrary :: Gen Parts #

shrink :: Parts -> [Parts] #

ToJSON Parts Source # 
FromJSON Parts Source # 
type Rep Parts Source # 
type Rep Parts = D1 (MetaData "Parts" "Web.HackerNews.Types" "hackernews-1.2.0.0-C7hKVOmSPnJK48DfCKv8af" True) (C1 (MetaCons "Parts" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ItemId])))

newtype Delay Source #

Delay in minutes between a comment's creation and its visibility to other users.

Constructors

Delay Int 

Instances

Eq Delay Source # 

Methods

(==) :: Delay -> Delay -> Bool #

(/=) :: Delay -> Delay -> Bool #

Show Delay Source # 

Methods

showsPrec :: Int -> Delay -> ShowS #

show :: Delay -> String #

showList :: [Delay] -> ShowS #

Generic Delay Source # 

Associated Types

type Rep Delay :: * -> * #

Methods

from :: Delay -> Rep Delay x #

to :: Rep Delay x -> Delay #

Arbitrary Delay Source # 

Methods

arbitrary :: Gen Delay #

shrink :: Delay -> [Delay] #

ToJSON Delay Source # 
FromJSON Delay Source # 
type Rep Delay Source # 
type Rep Delay = D1 (MetaData "Delay" "Web.HackerNews.Types" "hackernews-1.2.0.0-C7hKVOmSPnJK48DfCKv8af" True) (C1 (MetaCons "Delay" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

newtype Created Source #

Creation date of the user, in Unix Time.

Constructors

Created Int 

Instances

newtype Karma Source #

The user's karma.

Constructors

Karma Int 

Instances

Eq Karma Source # 

Methods

(==) :: Karma -> Karma -> Bool #

(/=) :: Karma -> Karma -> Bool #

Show Karma Source # 

Methods

showsPrec :: Int -> Karma -> ShowS #

show :: Karma -> String #

showList :: [Karma] -> ShowS #

Generic Karma Source # 

Associated Types

type Rep Karma :: * -> * #

Methods

from :: Karma -> Rep Karma x #

to :: Rep Karma x -> Karma #

Arbitrary Karma Source # 

Methods

arbitrary :: Gen Karma #

shrink :: Karma -> [Karma] #

ToJSON Karma Source # 
FromJSON Karma Source # 
type Rep Karma Source # 
type Rep Karma = D1 (MetaData "Karma" "Web.HackerNews.Types" "hackernews-1.2.0.0-C7hKVOmSPnJK48DfCKv8af" True) (C1 (MetaCons "Karma" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

newtype About Source #

The user's optional self-description. HTML.

Constructors

About Text 

Instances

Eq About Source # 

Methods

(==) :: About -> About -> Bool #

(/=) :: About -> About -> Bool #

Show About Source # 

Methods

showsPrec :: Int -> About -> ShowS #

show :: About -> String #

showList :: [About] -> ShowS #

Generic About Source # 

Associated Types

type Rep About :: * -> * #

Methods

from :: About -> Rep About x #

to :: Rep About x -> About #

Arbitrary About Source # 

Methods

arbitrary :: Gen About #

shrink :: About -> [About] #

ToJSON About Source # 
FromJSON About Source # 
type Rep About Source # 
type Rep About = D1 (MetaData "About" "Web.HackerNews.Types" "hackernews-1.2.0.0-C7hKVOmSPnJK48DfCKv8af" True) (C1 (MetaCons "About" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype Submitted Source #

List of the user's stories, polls and comments.

Constructors

Submitted [ItemId]