Copyright | (c) 2021 Rory Tyler Hayford |
---|---|
License | BSD-3-Clause |
Maintainer | rory.hayford@protonmail.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data Username
- mkUsername :: MonadThrow m => Text -> m Username
- newtype UserID = UserID Text
- data Account = Account {}
- data AccountSearchOpts = AccountSearchOpts {}
- data AccountSearchSort
- data Friend = Friend {}
- data FriendList
- data Karma = Karma {}
- data KarmaList
- data Trophy = Trophy {}
- data TrophyList
- data UserSummary = UserSummary {
- userID :: Maybe UserID
- name :: Username
- commentKarma :: Integer
- linkKarma :: Integer
- created :: UTCTime
- profilePicture :: URL
- profileColor :: Maybe RGBText
- profileOver18 :: Bool
- data UserSummaryList
- data Preferences = Preferences {
- defaultCommentSort :: ItemSort
- media :: MediaPreference
- mediaPreview :: MediaPreference
- minCommentScore :: Int
- minLinkScore :: Int
- numComments :: Int
- numSites :: Int
- lang :: Text
- acceptPMs :: AcceptPMs
- activityRelevantAds :: Bool
- allowClicktracking :: Bool
- beta :: Bool
- clickGadget :: Bool
- collapseReadMessages :: Bool
- compress :: Bool
- credditAutorenew :: Maybe Bool
- domainDetails :: Bool
- emailChatRequest :: Bool
- emailCommentReply :: Bool
- emailDigests :: Bool
- emailMessages :: Bool
- emailPostReply :: Bool
- emailPrivateMessage :: Bool
- emailUnsubscribeAll :: Bool
- emailUpvoteComment :: Bool
- emailUpvotePost :: Bool
- emailUserNewFollower :: Bool
- emailUsernameMention :: Bool
- enableDefaultThemes :: Bool
- feedRecommendationsEnabled :: Bool
- hideAds :: Bool
- hideDowns :: Bool
- hideFromRobots :: Bool
- hideUps :: Bool
- highlightControversial :: Bool
- highlightNewComments :: Bool
- ignoreSuggestedSort :: Bool
- inRedesignBeta :: Maybe Bool
- labelNSFW :: Bool
- legacySearch :: Bool
- liveOrangereds :: Bool
- markMessagesRead :: Bool
- monitorMentions :: Bool
- newWindow :: Bool
- nightMode :: Bool
- noProfanity :: Bool
- organic :: Maybe Bool
- over18 :: Bool
- privateFeeds :: Bool
- profileOptOut :: Bool
- publicVotes :: Bool
- research :: Bool
- searchIncludeOver18 :: Bool
- sendCrosspostMessages :: Bool
- sendWelcomeMessages :: Bool
- showFlair :: Bool
- showGoldExpiration :: Bool
- showLinkFlair :: Bool
- showLocationBasedRecommendations :: Bool
- showPresence :: Bool
- showPromote :: Maybe Bool
- showStylesheets :: Bool
- showTrending :: Bool
- showTwitter :: Bool
- storeVisits :: Bool
- thirdPartyDataPersonalizedAds :: Bool
- thirdPartyPersonalizedAds :: Bool
- thirdPartySiteDataPersonalizedAds :: Bool
- thirdPartySiteDataPersonalizedContent :: Bool
- threadedMessages :: Bool
- threadedModmail :: Bool
- topKarmaSubreddits :: Bool
- useGlobalDefaults :: Bool
- videoAutoplay :: Bool
- data MediaPreference
- data AcceptPMs
Documentation
Reddit username
Instances
Eq Username Source # | |
Show Username Source # | |
Generic Username Source # | |
ToJSON Username Source # | |
Defined in Network.Reddit.Types.Account | |
FromJSON Username Source # | |
ToHttpApiData Username Source # | |
Defined in Network.Reddit.Types.Account toUrlPiece :: Username -> Text # toEncodedUrlPiece :: Username -> Builder # toHeader :: Username -> ByteString # toQueryParam :: Username -> Text # | |
type Rep Username Source # | |
Defined in Network.Reddit.Types.Account |
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
A unique, site-wide ID for an account
Account information. Maybe
fields denote data that Reddit sets to null if
the requester does not own the account in question. Note that this does not
include all of the possible fields that may be present in Reddit's response -
which are quite numerous in total and poorly documented
Instances
data AccountSearchOpts Source #
Options for search Listing
s of Account
s
AccountSearchOpts | |
|
Instances
data AccountSearchSort Source #
The item sort for Account
searches
Instances
Eq AccountSearchSort Source # | |
Defined in Network.Reddit.Types.Account (==) :: AccountSearchSort -> AccountSearchSort -> Bool # (/=) :: AccountSearchSort -> AccountSearchSort -> Bool # | |
Show AccountSearchSort Source # | |
Defined in Network.Reddit.Types.Account showsPrec :: Int -> AccountSearchSort -> ShowS # show :: AccountSearchSort -> String # showList :: [AccountSearchSort] -> ShowS # | |
Generic AccountSearchSort Source # | |
Defined in Network.Reddit.Types.Account type Rep AccountSearchSort :: Type -> Type # from :: AccountSearchSort -> Rep AccountSearchSort x # to :: Rep AccountSearchSort x -> AccountSearchSort # | |
ToHttpApiData AccountSearchSort Source # | |
Defined in Network.Reddit.Types.Account toUrlPiece :: AccountSearchSort -> Text # toEncodedUrlPiece :: AccountSearchSort -> Builder # toHeader :: AccountSearchSort -> ByteString # toQueryParam :: AccountSearchSort -> Text # | |
type Rep AccountSearchSort Source # | |
Defined in Network.Reddit.Types.Account |
A user's friend
Instances
Eq Friend Source # | |
Show Friend Source # | |
Generic Friend Source # | |
FromJSON Friend Source # | |
type Rep Friend Source # | |
Defined in Network.Reddit.Types.Account type Rep Friend = D1 ('MetaData "Friend" "Network.Reddit.Types.Account" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "Friend" 'PrefixI 'True) ((S1 ('MetaSel ('Just "username") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Username) :*: S1 ('MetaSel ('Just "userID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 UserID)) :*: (S1 ('MetaSel ('Just "since") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "note") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text))))) |
data FriendList Source #
Wrapper for parsing JSON objects listing Friend
s
Instances
Show FriendList Source # | |
Defined in Network.Reddit.Types.Account showsPrec :: Int -> FriendList -> ShowS # show :: FriendList -> String # showList :: [FriendList] -> ShowS # | |
Generic FriendList Source # | |
Defined in Network.Reddit.Types.Account type Rep FriendList :: Type -> Type # from :: FriendList -> Rep FriendList x # to :: Rep FriendList x -> FriendList # | |
FromJSON FriendList Source # | |
Defined in Network.Reddit.Types.Account parseJSON :: Value -> Parser FriendList # parseJSONList :: Value -> Parser [FriendList] # | |
type Rep FriendList Source # | |
Defined in Network.Reddit.Types.Account type Rep FriendList = D1 ('MetaData "FriendList" "Network.Reddit.Types.Account" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'True) (C1 ('MetaCons "FriendList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq Friend)))) |
Information about a user's karma
Instances
Eq Karma Source # | |
Show Karma Source # | |
Generic Karma Source # | |
FromJSON Karma Source # | |
type Rep Karma Source # | |
Defined in Network.Reddit.Types.Account type Rep Karma = D1 ('MetaData "Karma" "Network.Reddit.Types.Account" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "Karma" 'PrefixI 'True) (S1 ('MetaSel ('Just "subreddit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SubredditName) :*: (S1 ('MetaSel ('Just "commentKarma") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer) :*: S1 ('MetaSel ('Just "linkKarma") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer)))) |
Wrapper for parsing JSON array of Karma
A Reddit award, such as the "one-year club"
Instances
Eq Trophy Source # | |
Show Trophy Source # | |
Generic Trophy Source # | |
FromJSON Trophy Source # | |
type Rep Trophy Source # | |
Defined in Network.Reddit.Types.Account type Rep Trophy = D1 ('MetaData "Trophy" "Network.Reddit.Types.Account" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "Trophy" 'PrefixI 'True) ((S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Name) :*: S1 ('MetaSel ('Just "trophyID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "awardID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "description") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Body)) :*: S1 ('MetaSel ('Just "grantedAt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe UTCTime)))))) |
data TrophyList Source #
Wrapper for parsing JSON objects listing Trophy
s
Instances
Show TrophyList Source # | |
Defined in Network.Reddit.Types.Account showsPrec :: Int -> TrophyList -> ShowS # show :: TrophyList -> String # showList :: [TrophyList] -> ShowS # | |
Generic TrophyList Source # | |
Defined in Network.Reddit.Types.Account type Rep TrophyList :: Type -> Type # from :: TrophyList -> Rep TrophyList x # to :: Rep TrophyList x -> TrophyList # | |
FromJSON TrophyList Source # | |
Defined in Network.Reddit.Types.Account parseJSON :: Value -> Parser TrophyList # parseJSONList :: Value -> Parser [TrophyList] # | |
type Rep TrophyList Source # | |
Defined in Network.Reddit.Types.Account type Rep TrophyList = D1 ('MetaData "TrophyList" "Network.Reddit.Types.Account" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'True) (C1 ('MetaCons "TrophyList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq Trophy)))) |
data UserSummary Source #
A brief summary of a user, with significantly less information than a
Account
UserSummary | |
|
Instances
data UserSummaryList Source #
Wrapper for parsing a JSON object of UserSummary
s which has user IDs as
keys
Instances
Show UserSummaryList Source # | |
Defined in Network.Reddit.Types.Account showsPrec :: Int -> UserSummaryList -> ShowS # show :: UserSummaryList -> String # showList :: [UserSummaryList] -> ShowS # | |
Generic UserSummaryList Source # | |
Defined in Network.Reddit.Types.Account type Rep UserSummaryList :: Type -> Type # from :: UserSummaryList -> Rep UserSummaryList x # to :: Rep UserSummaryList x -> UserSummaryList # | |
FromJSON UserSummaryList Source # | |
Defined in Network.Reddit.Types.Account parseJSON :: Value -> Parser UserSummaryList # parseJSONList :: Value -> Parser [UserSummaryList] # | |
type Rep UserSummaryList Source # | |
Defined in Network.Reddit.Types.Account type Rep UserSummaryList = D1 ('MetaData "UserSummaryList" "Network.Reddit.Types.Account" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'True) (C1 ('MetaCons "UserSummaryList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq UserSummary)))) |
data Preferences Source #
User preferences
Preferences | |
|
Instances
data MediaPreference Source #
How to deal with media previews and thumbnails in your Preferences