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.Internal

Description

 
Synopsis

Documentation

class Thing a where Source #

"Thing"s are the base class of Reddit's OOP model. Each thing has several properties, but here we are only interested in one, the "fullname". This is a combination of a thing's type (here represented as a RedditKind), and its unique ID

Methods

fullname :: a -> Text Source #

A fullname is an identifier with a "type prefix" attached. See RedditKind for possible prefixes. This prefixed form is required in various places by the Reddit API

Instances

Instances details
Thing SubredditID Source # 
Instance details

Defined in Network.Reddit.Types.Subreddit

Thing UserID Source # 
Instance details

Defined in Network.Reddit.Types.Account

Methods

fullname :: UserID -> Text Source #

Thing LiveUpdateID Source # 
Instance details

Defined in Network.Reddit.Types.Live

Thing LiveThreadID Source # 
Instance details

Defined in Network.Reddit.Types.Live

Thing ResultID Source # 
Instance details

Defined in Network.Reddit.Types.Submission

Thing SubmissionID Source # 
Instance details

Defined in Network.Reddit.Types.Submission

Thing CommentID Source # 
Instance details

Defined in Network.Reddit.Types.Comment

Thing PrivateMessageID Source # 
Instance details

Defined in Network.Reddit.Types.Message

Thing MessageID Source # 
Instance details

Defined in Network.Reddit.Types.Message

Thing ItemID Source # 
Instance details

Defined in Network.Reddit.Types.Item

Methods

fullname :: ItemID -> Text Source #

Thing ModActionID Source # 
Instance details

Defined in Network.Reddit.Types.Moderation

Thing MuteID Source # 
Instance details

Defined in Network.Reddit.Types.Moderation

Methods

fullname :: MuteID -> Text Source #

Thing RelID Source # 
Instance details

Defined in Network.Reddit.Types.Moderation

Methods

fullname :: RelID -> Text Source #

Thing WikiRevisionID Source # 
Instance details

Defined in Network.Reddit.Types.Wiki

(Foldable t, Thing a) => Thing (t a) Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Methods

fullname :: t a -> Text Source #

class Paginable a where Source #

Represents requests that can take additional options in a Paginator. This can be used to filter/sort Listing endpoints

Minimal complete definition

defaultOpts

Associated Types

type PaginateOptions (a :: Type) Source #

type PaginateThing (a :: Type) Source #

Methods

defaultOpts :: PaginateOptions a Source #

Default PaginateOptions for this type

getFullname :: a -> PaginateThing a Source #

Get the fullname of the Thing type associated with this type, if any

optsToForm :: PaginateOptions a -> Form Source #

Convert the PaginateOptions options to a Form

Instances

Instances details
Paginable Subreddit Source # 
Instance details

Defined in Network.Reddit.Types.Subreddit

Paginable Account Source # 
Instance details

Defined in Network.Reddit.Types.Account

Paginable LiveUpdate Source # 
Instance details

Defined in Network.Reddit.Types.Live

Paginable LiveThread Source # 
Instance details

Defined in Network.Reddit.Types.Live

Paginable AssignedFlair Source # 
Instance details

Defined in Network.Reddit.Types.Flair

Paginable Search Source # 
Instance details

Defined in Network.Reddit.Types.Submission

Paginable Submission Source # 
Instance details

Defined in Network.Reddit.Types.Submission

Paginable Comment Source # 
Instance details

Defined in Network.Reddit.Types.Comment

Paginable Message Source # 
Instance details

Defined in Network.Reddit.Types.Message

Paginable Item Source # 
Instance details

Defined in Network.Reddit.Types.Item

Paginable ModAction Source # 
Instance details

Defined in Network.Reddit.Types.Moderation

Paginable Ban Source # 
Instance details

Defined in Network.Reddit.Types.Moderation

Associated Types

type PaginateOptions Ban Source #

type PaginateThing Ban Source #

Paginable MuteInfo Source # 
Instance details

Defined in Network.Reddit.Types.Moderation

Paginable RelInfo Source # 
Instance details

Defined in Network.Reddit.Types.Moderation

Paginable ModItem Source # 
Instance details

Defined in Network.Reddit.Types.Moderation

Paginable WikiRevision Source # 
Instance details

Defined in Network.Reddit.Types.Wiki

data Paginator t a Source #

This represents the protocol that Reddit uses to control paginating and filtering entries. These can be applied to Listing endpoints. The first four fields below are common parameters that are applied to each Listing. The opts field takes extended PaginateOptions based on the second type parameter

Constructors

Paginator 

Fields

  • before :: Maybe t

    The pagination controls. These should be Thing instances, in order to provide the fullname params that Reddit requires

  • after :: Maybe t
     
  • limit :: Word

    The maximum number of items to return in an individual slice. Defaults to 25, with a maximum of 100

  • showAll :: Bool

    A control to disable filtering, e.g. hiding links that one has voted on. At the moment, turning this option on is a no-op

  • srDetail :: Bool

    Whether or not to expand subreddits

  • opts :: PaginateOptions a

    Additional options, depending on the type parameter a

Instances

Instances details
(HasField' name (Paginator t a) s, a ~ b, s ~ u) => HasField name (Paginator t a) (Paginator t b) s u Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Methods

field :: Lens (Paginator t a) (Paginator t b) s u #

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

Defined in Network.Reddit.Types.Internal

Methods

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

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

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

Defined in Network.Reddit.Types.Internal

Methods

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

show :: Paginator t a -> String #

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

Generic (Paginator t a) Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep (Paginator t a) :: Type -> Type #

Methods

from :: Paginator t a -> Rep (Paginator t a) x #

to :: Rep (Paginator t a) x -> Paginator t a #

(Thing t, Paginable a) => ToForm (Paginator t a) Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Methods

toForm :: Paginator t a -> Form #

type Rep (Paginator t a) Source # 
Instance details

Defined in Network.Reddit.Types.Internal

data Listing t a Source #

Certain API endpoints are listings, which can be paginated and filtered using a Paginator

Constructors

Listing 

Fields

Instances

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

Defined in Network.Reddit.Types.Internal

Methods

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

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

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

Defined in Network.Reddit.Types.Internal

Methods

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

show :: Listing t a -> String #

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

Generic (Listing t a) Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep (Listing t a) :: Type -> Type #

Methods

from :: Listing t a -> Rep (Listing t a) x #

to :: Rep (Listing t a) x -> Listing t a #

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

Defined in Network.Reddit.Types.Internal

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 Network.Reddit.Types.Internal

Methods

mempty :: Listing t a #

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

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

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

Defined in Network.Reddit.Types.Internal

type Rep (Listing t a) Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep (Listing t a) = D1 ('MetaData "Listing" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "Listing" 'PrefixI 'True) (S1 ('MetaSel ('Just "before") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe t)) :*: (S1 ('MetaSel ('Just "after") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe t)) :*: S1 ('MetaSel ('Just "children") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Seq a)))))

data Username Source #

Reddit username

Instances

Instances details
Eq Username Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show Username Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic Username Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep Username :: Type -> Type #

Methods

from :: Username -> Rep Username x #

to :: Rep Username x -> Username #

ToJSON Username Source # 
Instance details

Defined in Network.Reddit.Types.Internal

FromJSON Username Source # 
Instance details

Defined in Network.Reddit.Types.Internal

ToHttpApiData Username Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep Username Source # 
Instance details

Defined in Network.Reddit.Types.Internal

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

pattern DeletedUser :: Username Source #

Pattern for "[deleted]" username

mkUsername :: MonadThrow m => Text -> m Username Source #

Smart constructor for Username, which must be between 3 and 20 chars, and may only include upper/lowercase alphanumeric chars, underscores, or hyphens

usernameToDisplayName :: Username -> Text Source #

Prefix the username with "u_"

isUserDeleted :: Username -> Bool Source #

Test if a user has the "[deleted]" username. Also see the DeletedUser pattern synonym

newtype CIText a Source #

This exists to derive case-insensitive Eq instances for types that are isomorphic to Text

Constructors

CIText a 

Instances

Instances details
Coercible a Text => Eq (CIText a) Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Methods

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

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

type family HKD f a where ... Source #

Equations

HKD Identity a = a 
HKD f a = f a 

data ItemOpts Source #

Options that can be applied to comments or submissions

Instances

Instances details
Eq ItemOpts Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show ItemOpts Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic ItemOpts Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep ItemOpts :: Type -> Type #

Methods

from :: ItemOpts -> Rep ItemOpts x #

to :: Rep ItemOpts x -> ItemOpts #

ToForm ItemOpts Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Methods

toForm :: ItemOpts -> Form #

type Rep ItemOpts Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep ItemOpts = D1 ('MetaData "ItemOpts" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "ItemOpts" 'PrefixI 'True) ((S1 ('MetaSel ('Just "itemSort") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ItemSort)) :*: S1 ('MetaSel ('Just "itemType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ItemType))) :*: (S1 ('MetaSel ('Just "itemTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Time)) :*: S1 ('MetaSel ('Just "context") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Word)))))

defaultItemOpts :: ItemOpts Source #

Defaults for fetching items, like comments or submissions

data ItemSort Source #

How to sort items in certain Listings. Not every option is guaranteed to be accepted by a given endpoint

Instances

Instances details
Eq ItemSort Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show ItemSort Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic ItemSort Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep ItemSort :: Type -> Type #

Methods

from :: ItemSort -> Rep ItemSort x #

to :: Rep ItemSort x -> ItemSort #

ToJSON ItemSort Source # 
Instance details

Defined in Network.Reddit.Types.Internal

FromJSON ItemSort Source # 
Instance details

Defined in Network.Reddit.Types.Internal

ToHttpApiData ItemSort Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep ItemSort Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep ItemSort = D1 ('MetaData "ItemSort" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (((C1 ('MetaCons "Hot" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "New" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Top" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Controversial" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Old" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Random" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "QA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Live" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Confidence" 'PrefixI 'False) (U1 :: Type -> Type)))))

data ItemReport Source #

A user- or moderator-generated report on a submission

Constructors

ItemReport 

Fields

Instances

Instances details
Eq ItemReport Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show ItemReport Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic ItemReport Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep ItemReport :: Type -> Type #

FromJSON ItemReport Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep ItemReport Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep ItemReport = D1 ('MetaData "ItemReport" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "ItemReport" 'PrefixI 'True) (S1 ('MetaSel ('Just "reason") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "count") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word)))

data Distinction Source #

Sigils that a moderator can add to distinguish comments or submissions. Note that the Admin and Special distinctions require special privileges to use

Constructors

Moderator

Adds "[M]"

Undistinguished

Removes an existing distinction when sent

Admin

Adds "[A]"

Special

User-specific distinction

Instances

Instances details
Eq Distinction Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show Distinction Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic Distinction Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep Distinction :: Type -> Type #

FromJSON Distinction Source # 
Instance details

Defined in Network.Reddit.Types.Internal

ToHttpApiData Distinction Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep Distinction Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep Distinction = D1 ('MetaData "Distinction" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) ((C1 ('MetaCons "Moderator" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Undistinguished" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Admin" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Special" 'PrefixI 'False) (U1 :: Type -> Type)))

data Time Source #

Time range when fetching comments or submissions

Constructors

Hour 
Day 
Week 
Month 
Year 
AllTime 

Instances

Instances details
Eq Time Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Methods

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

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

Show Time Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

Generic Time Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep Time :: Type -> Type #

Methods

from :: Time -> Rep Time x #

to :: Rep Time x -> Time #

ToHttpApiData Time Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep Time Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep Time = D1 ('MetaData "Time" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) ((C1 ('MetaCons "Hour" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Day" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Week" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Month" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Year" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AllTime" 'PrefixI 'False) (U1 :: Type -> Type))))

data ItemType Source #

Type of comments, for filtering in Listings

Constructors

Comments 
Submissions 

Instances

Instances details
Eq ItemType Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show ItemType Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic ItemType Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep ItemType :: Type -> Type #

Methods

from :: ItemType -> Rep ItemType x #

to :: Rep ItemType x -> ItemType #

ToHttpApiData ItemType Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep ItemType Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep ItemType = D1 ('MetaData "ItemType" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "Comments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Submissions" 'PrefixI 'False) (U1 :: Type -> Type))

data UploadURL Source #

A URL pointing to a resource hosted by Reddit. These should only be obtained by parsing the JSON of existing resources or through particular actions that perform the upload transaction and return the URL, e.g. uploadWidgetImage

Instances

Instances details
Eq UploadURL Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show UploadURL Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic UploadURL Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep UploadURL :: Type -> Type #

ToJSON UploadURL Source # 
Instance details

Defined in Network.Reddit.Types.Internal

FromJSON UploadURL Source # 
Instance details

Defined in Network.Reddit.Types.Internal

ToHttpApiData UploadURL Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep UploadURL Source # 
Instance details

Defined in Network.Reddit.Types.Internal

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

data SubredditType Source #

The privacy level for the subreddit

Instances

Instances details
Eq SubredditType Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show SubredditType Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic SubredditType Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep SubredditType :: Type -> Type #

FromJSON SubredditType Source # 
Instance details

Defined in Network.Reddit.Types.Internal

ToHttpApiData SubredditType Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep SubredditType Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep SubredditType = D1 ('MetaData "SubredditType" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (((C1 ('MetaCons "Public" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Restricted" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Private" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Archived" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "GoldRestricted" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EmployeesOnly" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GoldOnly" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UserSubreddit" 'PrefixI 'False) (U1 :: Type -> Type))))

type Body = Text Source #

Type synonym for bodies of submissions, comments, messages, etc...

type Title = Text Source #

Type synonym for titles of submissions, etc...

type URL = Text Source #

Type synonym for URLs

type Subject = Text Source #

Type synonym for subjects of messages, etc...

type RGBText = Text Source #

Type synonym RGB color strings

type Name = Text Source #

Type synonym for names of items

type Domain = Text Source #

Type synonym for domains

type Modifier = [Char] -> [Char] Source #

Type synonym for fieldLabelModifiers in FromJSON instances

type RawBody m = ConduitM () ByteString m () Source #

Type synonym the raw body of an HTTP response

Exceptions

data ClientException Source #

Exceptions generated within the Reddit API client

Instances

Instances details
Eq ClientException Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show ClientException Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic ClientException Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep ClientException :: Type -> Type #

Exception ClientException Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep ClientException Source # 
Instance details

Defined in Network.Reddit.Types.Internal

data APIException Source #

Exceptions returned from API endpoints

Constructors

ErrorWithStatus StatusMessage 
ErrorWithMessage ErrorMessage 
InvalidCredentials OAauthError 
InvalidPOST POSTError

Sent if errors occur when posting JSON

JSONParseError Text ByteString

With the response body, for further debugging

Redirected (Maybe Request)

If the API action should not allow automatic redirects, this error returns the possible redirected request

UserIsBanned BannedUser

Thrown when attempting to get account information on a banned user

WebsocketError Text SomeException

Thrown when exceptions occur during websocket handling

UploadFailed

When an error occurs uploading media to Reddit's servers

Instances

Instances details
Show APIException Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic APIException Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep APIException :: Type -> Type #

FromJSON APIException Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Exception APIException Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep APIException Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep APIException = D1 ('MetaData "APIException" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (((C1 ('MetaCons "ErrorWithStatus" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 StatusMessage)) :+: C1 ('MetaCons "ErrorWithMessage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ErrorMessage))) :+: (C1 ('MetaCons "InvalidCredentials" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OAauthError)) :+: C1 ('MetaCons "InvalidPOST" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 POSTError)))) :+: ((C1 ('MetaCons "JSONParseError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString)) :+: C1 ('MetaCons "Redirected" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Request)))) :+: (C1 ('MetaCons "UserIsBanned" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 BannedUser)) :+: (C1 ('MetaCons "WebsocketError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SomeException)) :+: C1 ('MetaCons "UploadFailed" 'PrefixI 'False) (U1 :: Type -> Type)))))

data OAauthError Source #

An error which occurs when attempting to authenticate via OAuth

Constructors

OAauthError 

Fields

Instances

Instances details
Eq OAauthError Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show OAauthError Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic OAauthError Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep OAauthError :: Type -> Type #

FromJSON OAauthError Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep OAauthError Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep OAauthError = D1 ('MetaData "OAauthError" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "OAauthError" 'PrefixI 'True) (S1 ('MetaSel ('Just "errorType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "description") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text))))

data ErrorMessage Source #

A specific error message

Instances

Instances details
Eq ErrorMessage Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show ErrorMessage Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic ErrorMessage Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep ErrorMessage :: Type -> Type #

FromJSON ErrorMessage Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep ErrorMessage Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep ErrorMessage = D1 ('MetaData "ErrorMessage" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (((C1 ('MetaCons "EmptyError" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OtherErrorMessage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Value])) :+: C1 ('MetaCons "Ratelimited" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)))) :+: ((C1 ('MetaCons "CommentDeleted" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BadSRName" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SubredditNotExists" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SubredditRequired" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "AlreadySubmitted" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoURL" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NoName" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoText" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TooShort" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BadCaptcha" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UserRequired" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InsufficientCoins" 'PrefixI 'False) (U1 :: Type -> Type)))))

type StatusCode = Int Source #

Type synonym for status codes in responses

data StatusMessage Source #

Details about a non-200 HTTP response

Constructors

StatusMessage 

Instances

Instances details
Eq StatusMessage Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show StatusMessage Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic StatusMessage Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep StatusMessage :: Type -> Type #

FromJSON StatusMessage Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep StatusMessage Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep StatusMessage = D1 ('MetaData "StatusMessage" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "StatusMessage" 'PrefixI 'True) (S1 ('MetaSel ('Just "statusCode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 StatusCode) :*: S1 ('MetaSel ('Just "message") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)))

data POSTError Source #

Details about a non-200 response when sending a POST request

Constructors

POSTError 

Fields

Instances

Instances details
Eq POSTError Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show POSTError Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic POSTError Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep POSTError :: Type -> Type #

FromJSON POSTError Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep POSTError Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep POSTError = D1 ('MetaData "POSTError" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "POSTError" 'PrefixI 'True) ((S1 ('MetaSel ('Just "fields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Text]) :*: S1 ('MetaSel ('Just "explanation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "message") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "reason") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))))

data BannedUser Source #

Information about a banned user

Constructors

BannedUser 

Fields

Instances

Instances details
Eq BannedUser Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Show BannedUser Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Generic BannedUser Source # 
Instance details

Defined in Network.Reddit.Types.Internal

Associated Types

type Rep BannedUser :: Type -> Type #

FromJSON BannedUser Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep BannedUser Source # 
Instance details

Defined in Network.Reddit.Types.Internal

type Rep BannedUser = D1 ('MetaData "BannedUser" "Network.Reddit.Types.Internal" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "BannedUser" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Username) :*: (S1 ('MetaSel ('Just "totalKarma") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer) :*: S1 ('MetaSel ('Just "isSuspended") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool))))

Utilities

dropTypePrefix :: RedditKind -> Text -> Parser Text Source #

Drop the leading textual representation of a RedditKind from a Reddit identifier, or return the entire identifier if there is no prefix

withKind :: FromJSON b => RedditKind -> [Char] -> (b -> Parser a) -> Value -> Parser a Source #

Ensures that the kind field of a JSON object corresponds to the expected RedditKind of the response and runs a parsing function on its data field

textKind :: RedditKind -> Text Source #

Convert a RedditKind to its textual representation

prependType :: RedditKind -> Text -> Text Source #

Opposite of dropTypePrefix: joins the textual representation of a RedditKind to an identifier with an underscore

tshow :: Show a => a -> Text Source #

Show some Text

editedP :: Value -> Parser (Maybe UTCTime) Source #

Parse the edited field in comments or submissions, which can either be false or a Unix timestamp

validateName :: (MonadThrow m, Coercible a Text) => Maybe [Char] -> Maybe (Int, Int) -> Text -> Text -> m a Source #

Verify that some name corresponds to specifiable Reddit naming rules

joinParams :: (Foldable t, ToHttpApiData a) => t a -> Text Source #

Make a comma-separated sequence of query params

nothingTxtNull :: FromJSON a => Text -> Parser (Maybe a) Source #

Return Nothing if a text field is empty

textObject :: [Pair] -> Text Source #

Encode a list of Pairs to strict Text

textEncode :: ToJSON a => a -> Text Source #

Encode a ToJSON instance to strict Text

withKinds :: FromJSON b => [RedditKind] -> [Char] -> (b -> Parser a) -> Value -> Parser a Source #

Like withKind, but can be used in the exceptional circumstances that a container of values have heterogeneous kinds

breakOnType :: Coercible a Text => Text -> Text -> Parser a Source #

Split a JSON identifier on "_"; if it matches the given type prefix, returning the remaining text. Otherwise, return the identifier whole if there is no remaining text

breakOnTypeLenient :: Coercible a Text => Text -> Text -> Parser a Source #

Split a JSON identifier on "_"; if it matches the given type prefix, returning the remaining text. If there are no matches, return the text whole. This is useful if Reddit does not consistently prefix values with the type identifier

getVals :: FromJSON b => HashMap Text Value -> Parser (Seq b) Source #

Get all of the values from a HashMap and place them in a Seq, discarding the keys

mkTextForm :: [(Text, Text)] -> Form Source #

Make a form from [(Text, Text)] pairs