heddit-0.2: Reddit API bindings
Copyright(c) 2021 Rory Tyler Hayford
LicenseBSD-3-Clause
Maintainerrory.hayford@protonmail.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Network.Reddit.Types.Item

Description

 
Synopsis

Documentation

data Item Source #

Certain endpoints will return either Comments or a Submissions, or both

Instances

Instances details
Eq Item Source # 
Instance details

Defined in Network.Reddit.Types.Item

Methods

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

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

Show Item Source # 
Instance details

Defined in Network.Reddit.Types.Item

Methods

showsPrec :: Int -> Item -> ShowS #

show :: Item -> String #

showList :: [Item] -> ShowS #

Generic Item Source # 
Instance details

Defined in Network.Reddit.Types.Item

Associated Types

type Rep Item :: Type -> Type #

Methods

from :: Item -> Rep Item x #

to :: Rep Item x -> Item #

FromJSON Item Source # 
Instance details

Defined in Network.Reddit.Types.Item

Paginable Item Source # 
Instance details

Defined in Network.Reddit.Types.Item

FromJSON (PostedItem Item) Source # 
Instance details

Defined in Network.Reddit.Types.Item

type Rep Item Source # 
Instance details

Defined in Network.Reddit.Types.Item

type Rep Item = D1 ('MetaData "Item" "Network.Reddit.Types.Item" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "CommentItem" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Comment)) :+: C1 ('MetaCons "SubmissionItem" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Submission)))
type PaginateOptions Item Source # 
Instance details

Defined in Network.Reddit.Types.Item

type PaginateThing Item Source # 
Instance details

Defined in Network.Reddit.Types.Item

data ItemID Source #

Wraps either a CommentID or a SubmissionID. This is required to use Items with Paginators

Instances

Instances details
Eq ItemID Source # 
Instance details

Defined in Network.Reddit.Types.Item

Methods

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

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

Show ItemID Source # 
Instance details

Defined in Network.Reddit.Types.Item

Generic ItemID Source # 
Instance details

Defined in Network.Reddit.Types.Item

Associated Types

type Rep ItemID :: Type -> Type #

Methods

from :: ItemID -> Rep ItemID x #

to :: Rep ItemID x -> ItemID #

FromJSON ItemID Source # 
Instance details

Defined in Network.Reddit.Types.Item

Thing ItemID Source # 
Instance details

Defined in Network.Reddit.Types.Item

Methods

fullname :: ItemID -> Text Source #

type Rep ItemID Source # 
Instance details

Defined in Network.Reddit.Types.Item

type Rep ItemID = D1 ('MetaData "ItemID" "Network.Reddit.Types.Item" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "CommentItemID" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CommentID)) :+: C1 ('MetaCons "SubmissionItemID" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SubmissionID)))

data PostedItem a Source #

Wrapper for parsing new Items, Comments, or Submissions that are returned after requesting their creation

Instances

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

Defined in Network.Reddit.Types.Item

Methods

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

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

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

Defined in Network.Reddit.Types.Item

Generic (PostedItem a) Source # 
Instance details

Defined in Network.Reddit.Types.Item

Associated Types

type Rep (PostedItem a) :: Type -> Type #

Methods

from :: PostedItem a -> Rep (PostedItem a) x #

to :: Rep (PostedItem a) x -> PostedItem a #

FromJSON (PostedItem Submission) Source # 
Instance details

Defined in Network.Reddit.Types.Item

FromJSON (PostedItem Comment) Source # 
Instance details

Defined in Network.Reddit.Types.Item

FromJSON (PostedItem Item) Source # 
Instance details

Defined in Network.Reddit.Types.Item

type Rep (PostedItem a) Source # 
Instance details

Defined in Network.Reddit.Types.Item

type Rep (PostedItem a) = D1 ('MetaData "PostedItem" "Network.Reddit.Types.Item" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'True) (C1 ('MetaCons "PostedItem" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

data Vote Source #

The direction in which to vote

Constructors

Downvote 
Unvote 
Upvote 

Instances

Instances details
Eq Vote Source # 
Instance details

Defined in Network.Reddit.Types.Item

Methods

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

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

Ord Vote Source # 
Instance details

Defined in Network.Reddit.Types.Item

Methods

compare :: Vote -> Vote -> Ordering #

(<) :: Vote -> Vote -> Bool #

(<=) :: Vote -> Vote -> Bool #

(>) :: Vote -> Vote -> Bool #

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

max :: Vote -> Vote -> Vote #

min :: Vote -> Vote -> Vote #

Show Vote Source # 
Instance details

Defined in Network.Reddit.Types.Item

Methods

showsPrec :: Int -> Vote -> ShowS #

show :: Vote -> String #

showList :: [Vote] -> ShowS #

Generic Vote Source # 
Instance details

Defined in Network.Reddit.Types.Item

Associated Types

type Rep Vote :: Type -> Type #

Methods

from :: Vote -> Rep Vote x #

to :: Rep Vote x -> Vote #

type Rep Vote Source # 
Instance details

Defined in Network.Reddit.Types.Item

type Rep Vote = D1 ('MetaData "Vote" "Network.Reddit.Types.Item" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "Downvote" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Unvote" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Upvote" 'PrefixI 'False) (U1 :: Type -> Type)))

data Report Source #

The reason for issuing a report. The length of the contained text must be <= 100 characters

Instances

Instances details
Eq Report Source # 
Instance details

Defined in Network.Reddit.Types.Item

Methods

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

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

Show Report Source # 
Instance details

Defined in Network.Reddit.Types.Item

Generic Report Source # 
Instance details

Defined in Network.Reddit.Types.Item

Associated Types

type Rep Report :: Type -> Type #

Methods

from :: Report -> Rep Report x #

to :: Rep Report x -> Report #

ToHttpApiData Report Source # 
Instance details

Defined in Network.Reddit.Types.Item

type Rep Report Source # 
Instance details

Defined in Network.Reddit.Types.Item

type Rep Report = D1 ('MetaData "Report" "Network.Reddit.Types.Item" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'True) (C1 ('MetaCons "Report" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

mkReport :: MonadThrow m => Text -> m Report Source #

Smart constructor for Reports, which may be no longer than 100 characters in length