reddit-0.3.0.0: Library for interfacing with Reddit's API
Safe HaskellNone
LanguageHaskell2010

Reddit.Types

Documentation

data Comment Source #

Instances

Instances details
Eq Comment Source # 
Instance details

Defined in Reddit.Types.Comment

Methods

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

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

Read Comment Source # 
Instance details

Defined in Reddit.Types.Comment

Show Comment Source # 
Instance details

Defined in Reddit.Types.Comment

FromJSON Comment Source # 
Instance details

Defined in Reddit.Types.Comment

Thing Comment Source # 
Instance details

Defined in Reddit.Types.Comment

FromJSON (POSTWrapped Comment) Source # 
Instance details

Defined in Reddit.Types.Comment

newtype CommentID Source #

Constructors

CommentID Text 

Instances

Instances details
Eq CommentID Source # 
Instance details

Defined in Reddit.Types.Comment

Ord CommentID Source # 
Instance details

Defined in Reddit.Types.Comment

Read CommentID Source # 
Instance details

Defined in Reddit.Types.Comment

Show CommentID Source # 
Instance details

Defined in Reddit.Types.Comment

FromJSON CommentID Source # 
Instance details

Defined in Reddit.Types.Comment

ToQuery CommentID Source # 
Instance details

Defined in Reddit.Types.Comment

Methods

toQuery :: Text -> CommentID -> [(Text, Text)] #

Thing CommentID Source # 
Instance details

Defined in Reddit.Types.Comment

FromJSON (POSTWrapped CommentID) Source # 
Instance details

Defined in Reddit.Types.Comment

data Listing t a Source #

Constructors

Listing 

Fields

Instances

Instances details
Functor (Listing t) Source # 
Instance details

Defined in Reddit.Types.Listing

Methods

fmap :: (a -> b) -> Listing t a -> Listing t b #

(<$) :: a -> Listing t b -> Listing t a #

(Eq t, Eq a) => Eq (Listing t a) Source # 
Instance details

Defined in Reddit.Types.Listing

Methods

(==) :: Listing t a -> Listing t a -> Bool #

(/=) :: Listing t a -> Listing t a -> Bool #

(Read t, Read a) => Read (Listing t a) Source # 
Instance details

Defined in Reddit.Types.Listing

(Show t, Show a) => Show (Listing t a) Source # 
Instance details

Defined in Reddit.Types.Listing

Methods

showsPrec :: Int -> Listing t a -> ShowS #

show :: Listing t a -> String #

showList :: [Listing t a] -> ShowS #

Ord t => Semigroup (Listing t a) Source # 
Instance details

Defined in Reddit.Types.Listing

Methods

(<>) :: Listing t a -> Listing t a -> Listing t a #

sconcat :: NonEmpty (Listing t a) -> Listing t a #

stimes :: Integral b => b -> Listing t a -> Listing t a #

Ord t => Monoid (Listing t a) Source # 
Instance details

Defined in Reddit.Types.Listing

Methods

mempty :: Listing t a #

mappend :: Listing t a -> Listing t a -> Listing t a #

mconcat :: [Listing t a] -> Listing t a #

(FromJSON t, FromJSON a) => FromJSON (Listing t a) Source # 
Instance details

Defined in Reddit.Types.Listing

data LoginDetails Source #

Instances

Instances details
Show LoginDetails Source # 
Instance details

Defined in Reddit.Types.Reddit

Receivable LoginDetails Source # 
Instance details

Defined in Reddit.Types.Reddit

data Message Source #

Instances

Instances details
Eq Message Source # 
Instance details

Defined in Reddit.Types.Message

Methods

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

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

Read Message Source # 
Instance details

Defined in Reddit.Types.Message

Show Message Source # 
Instance details

Defined in Reddit.Types.Message

FromJSON Message Source # 
Instance details

Defined in Reddit.Types.Message

ToQuery Message Source # 
Instance details

Defined in Reddit.Types.Message

Methods

toQuery :: Text -> Message -> [(Text, Text)] #

Thing Message Source # 
Instance details

Defined in Reddit.Types.Message

data MessageID Source #

Constructors

MessageID Text 

Instances

Instances details
Eq MessageID Source # 
Instance details

Defined in Reddit.Types.Message

Ord MessageID Source # 
Instance details

Defined in Reddit.Types.Message

Read MessageID Source # 
Instance details

Defined in Reddit.Types.Message

Show MessageID Source # 
Instance details

Defined in Reddit.Types.Message

FromJSON MessageID Source # 
Instance details

Defined in Reddit.Types.Message

ToQuery MessageID Source # 
Instance details

Defined in Reddit.Types.Message

Methods

toQuery :: Text -> MessageID -> [(Text, Text)] #

Thing MessageID Source # 
Instance details

Defined in Reddit.Types.Message

FromJSON (POSTWrapped MessageID) Source # 
Instance details

Defined in Reddit.Types.Message

data MessageKind Source #

data Modhash Source #

Instances

Instances details
Eq Modhash Source # 
Instance details

Defined in Reddit.Types.Reddit

Methods

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

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

Read Modhash Source # 
Instance details

Defined in Reddit.Types.Reddit

Show Modhash Source # 
Instance details

Defined in Reddit.Types.Reddit

FromJSON Modhash Source # 
Instance details

Defined in Reddit.Types.Reddit

data Options a Source #

Constructors

Options 

Instances

Instances details
Eq a => Eq (Options a) Source # 
Instance details

Defined in Reddit.Types.Options

Methods

(==) :: Options a -> Options a -> Bool #

(/=) :: Options a -> Options a -> Bool #

Read a => Read (Options a) Source # 
Instance details

Defined in Reddit.Types.Options

Show a => Show (Options a) Source # 
Instance details

Defined in Reddit.Types.Options

Methods

showsPrec :: Int -> Options a -> ShowS #

show :: Options a -> String #

showList :: [Options a] -> ShowS #

Default (Options a) Source # 
Instance details

Defined in Reddit.Types.Options

Methods

def :: Options a #

data Post Source #

Instances

Instances details
Eq Post Source # 
Instance details

Defined in Reddit.Types.Post

Methods

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

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

Read Post Source # 
Instance details

Defined in Reddit.Types.Post

Show Post Source # 
Instance details

Defined in Reddit.Types.Post

Methods

showsPrec :: Int -> Post -> ShowS #

show :: Post -> String #

showList :: [Post] -> ShowS #

FromJSON Post Source # 
Instance details

Defined in Reddit.Types.Post

Thing Post Source # 
Instance details

Defined in Reddit.Types.Post

Methods

fullName :: Post -> Text Source #

newtype PostID Source #

Constructors

PostID Text 

Instances

Instances details
Eq PostID Source # 
Instance details

Defined in Reddit.Types.Post

Methods

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

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

Ord PostID Source # 
Instance details

Defined in Reddit.Types.Post

Read PostID Source # 
Instance details

Defined in Reddit.Types.Post

Show PostID Source # 
Instance details

Defined in Reddit.Types.Post

FromJSON PostID Source # 
Instance details

Defined in Reddit.Types.Post

ToQuery PostID Source # 
Instance details

Defined in Reddit.Types.Post

Methods

toQuery :: Text -> PostID -> [(Text, Text)] #

Thing PostID Source # 
Instance details

Defined in Reddit.Types.Post

Methods

fullName :: PostID -> Text Source #

FromJSON (POSTWrapped PostID) Source # 
Instance details

Defined in Reddit.Types.Post

type Reddit a = RedditT IO a Source #

data RedditT m a Source #

Instances

Instances details
MonadTrans RedditT Source # 
Instance details

Defined in Reddit.Types.Reddit

Methods

lift :: Monad m => m a -> RedditT m a #

Monad m => Monad (RedditT m) Source # 
Instance details

Defined in Reddit.Types.Reddit

Methods

(>>=) :: RedditT m a -> (a -> RedditT m b) -> RedditT m b #

(>>) :: RedditT m a -> RedditT m b -> RedditT m b #

return :: a -> RedditT m a #

Monad m => Functor (RedditT m) Source # 
Instance details

Defined in Reddit.Types.Reddit

Methods

fmap :: (a -> b) -> RedditT m a -> RedditT m b #

(<$) :: a -> RedditT m b -> RedditT m a #

Monad m => Applicative (RedditT m) Source # 
Instance details

Defined in Reddit.Types.Reddit

Methods

pure :: a -> RedditT m a #

(<*>) :: RedditT m (a -> b) -> RedditT m a -> RedditT m b #

liftA2 :: (a -> b -> c) -> RedditT m a -> RedditT m b -> RedditT m c #

(*>) :: RedditT m a -> RedditT m b -> RedditT m b #

(<*) :: RedditT m a -> RedditT m b -> RedditT m a #

MonadIO m => MonadIO (RedditT m) Source # 
Instance details

Defined in Reddit.Types.Reddit

Methods

liftIO :: IO a -> RedditT m a #

data Subreddit Source #

Instances

Instances details
Eq Subreddit Source # 
Instance details

Defined in Reddit.Types.Subreddit

Show Subreddit Source # 
Instance details

Defined in Reddit.Types.Subreddit

FromJSON Subreddit Source # 
Instance details

Defined in Reddit.Types.Subreddit

Thing Subreddit Source # 
Instance details

Defined in Reddit.Types.Subreddit

class Thing a Source #

Minimal complete definition

fullName

Instances

Instances details
Thing Subreddit Source # 
Instance details

Defined in Reddit.Types.Subreddit

Thing SubredditID Source # 
Instance details

Defined in Reddit.Types.Subreddit

Thing UserID Source # 
Instance details

Defined in Reddit.Types.User

Methods

fullName :: UserID -> Text Source #

Thing BanID Source # 
Instance details

Defined in Reddit.Types.Moderation

Methods

fullName :: BanID -> Text Source #

Thing Post Source # 
Instance details

Defined in Reddit.Types.Post

Methods

fullName :: Post -> Text Source #

Thing PostID Source # 
Instance details

Defined in Reddit.Types.Post

Methods

fullName :: PostID -> Text Source #

Thing Comment Source # 
Instance details

Defined in Reddit.Types.Comment

Thing CommentID Source # 
Instance details

Defined in Reddit.Types.Comment

Thing MessageKind Source # 
Instance details

Defined in Reddit.Types.Message

Thing MessageID Source # 
Instance details

Defined in Reddit.Types.Message

Thing Message Source # 
Instance details

Defined in Reddit.Types.Message

data User Source #

Instances

Instances details
Eq User Source # 
Instance details

Defined in Reddit.Types.User

Methods

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

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

Show User Source # 
Instance details

Defined in Reddit.Types.User

Methods

showsPrec :: Int -> User -> ShowS #

show :: User -> String #

showList :: [User] -> ShowS #

FromJSON User Source # 
Instance details

Defined in Reddit.Types.User

newtype Username Source #

Constructors

Username Text 

Instances

Instances details
Eq Username Source # 
Instance details

Defined in Reddit.Types.User

Ord Username Source # 
Instance details

Defined in Reddit.Types.User

Read Username Source # 
Instance details

Defined in Reddit.Types.User

Show Username Source # 
Instance details

Defined in Reddit.Types.User

FromJSON Username Source # 
Instance details

Defined in Reddit.Types.User

ToQuery Username Source # 
Instance details

Defined in Reddit.Types.User

Methods

toQuery :: Text -> Username -> [(Text, Text)] #