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
- getSubreddit :: MonadReddit m => SubredditName -> m Subreddit
- getSubredditRules :: MonadReddit m => SubredditName -> m (Seq SubredditRule)
- getPostRequirements :: MonadReddit m => SubredditName -> m PostRequirements
- getHotSubmissions :: MonadReddit m => SubredditName -> Paginator SubmissionID Submission -> m (Listing SubmissionID Submission)
- getNewSubmissions :: MonadReddit m => SubredditName -> Paginator SubmissionID Submission -> m (Listing SubmissionID Submission)
- getRandomRisingSubmissions :: MonadReddit m => SubredditName -> Paginator SubmissionID Submission -> m (Listing SubmissionID Submission)
- getControversialSubmissions :: MonadReddit m => SubredditName -> Paginator SubmissionID Submission -> m (Listing SubmissionID Submission)
- getRisingSubmissions :: MonadReddit m => SubredditName -> Paginator SubmissionID Submission -> m (Listing SubmissionID Submission)
- getTopSubmissions :: MonadReddit m => SubredditName -> Paginator SubmissionID Submission -> m (Listing SubmissionID Submission)
- getRandomSubmission :: MonadReddit m => SubredditName -> m Submission
- getStickiedSubmission :: MonadReddit m => Maybe Word -> SubredditName -> m Submission
- subscribe :: MonadReddit m => SubredditName -> m ()
- unsubscribe :: MonadReddit m => SubredditName -> m ()
- quarantineOptIn :: MonadReddit m => SubredditName -> m ()
- quarantineOptOut :: MonadReddit m => SubredditName -> m ()
- getDefaultSubreddits :: MonadReddit m => Paginator SubredditID Subreddit -> m (Listing SubredditID Subreddit)
- getNewSubreddits :: MonadReddit m => Paginator SubredditID Subreddit -> m (Listing SubredditID Subreddit)
- getPopularSubreddits :: MonadReddit m => Paginator SubredditID Subreddit -> m (Listing SubredditID Subreddit)
- getPremiumSubreddits :: MonadReddit m => Paginator SubredditID Subreddit -> m (Listing SubredditID Subreddit)
- getGoldSubreddits :: MonadReddit m => Paginator SubredditID Subreddit -> m (Listing SubredditID Subreddit)
- searchSubreddits :: MonadReddit m => Text -> Paginator SubredditID Subreddit -> m (Listing SubredditID Subreddit)
- searchSubredditsByName :: MonadReddit m => Maybe Bool -> Maybe Bool -> Text -> m (Seq SubredditName)
- getRecommendedSubreddits :: (MonadReddit m, Foldable t) => Maybe (t SubredditName) -> t SubredditName -> m (Seq SubredditName)
- followCollection :: MonadReddit m => CollectionID -> m ()
- unfollowCollection :: MonadReddit m => CollectionID -> m ()
- getCollections :: MonadReddit m => SubredditID -> m (Seq Collection)
- getCollectionsWithName :: MonadReddit m => SubredditName -> m (Seq Collection)
- getCollection :: MonadReddit m => CollectionID -> m Collection
- getCollectionByPermalink :: MonadReddit m => URL -> m Collection
- getUserFlairTemplates :: MonadReddit m => SubredditName -> m (Seq FlairTemplate)
- getSubmissionFlairTemplates :: MonadReddit m => SubredditName -> m (Seq FlairTemplate)
- getNewSubmissionFlairChoices :: MonadReddit m => SubredditName -> m (Seq FlairChoice)
- getUserFlairChoices :: MonadReddit m => SubredditName -> m (Seq FlairChoice)
- getSubmissionFlairChoices :: MonadReddit m => SubredditName -> SubmissionID -> m (Seq FlairChoice)
- getWikiPage :: MonadReddit m => SubredditName -> WikiPageName -> m WikiPage
- getWikiPages :: MonadReddit m => SubredditName -> m (Seq WikiPageName)
- getWikiPageRevision :: MonadReddit m => SubredditName -> WikiPageName -> WikiRevisionID -> m WikiPage
- getWikiPageRevisions :: MonadReddit m => SubredditName -> WikiPageName -> Paginator WikiRevisionID WikiRevision -> m (Listing WikiRevisionID WikiRevision)
- editWikiPage :: MonadReddit m => SubredditName -> WikiPageName -> Maybe Text -> Body -> m ()
- createWikiPage :: MonadReddit m => SubredditName -> WikiPageName -> Maybe Text -> Body -> m ()
- getSubredditWidgets :: MonadReddit m => SubredditName -> m SubredditWidgets
- getAllSubredditWidgets :: MonadReddit m => SubredditName -> m (Seq Widget)
- getSubredditEmojis :: MonadReddit m => SubredditName -> m (Seq Emoji)
- data BodyRestriction
- data PostRequirements = PostRequirements [Text] BodyRestriction [Text] [Text] Bool [Text] [Text] (Maybe Word) (Maybe Word)
- data RuleType
- data PostedSubredditRule
- data NewSubredditRule = NewSubredditRule Name RuleType Body (Maybe Text)
- data SubredditRule = SubredditRule Body Body Name UTCTime Word (Maybe Text) (Maybe RuleType)
- newtype SubredditID = SubredditID Text
- data SubredditName
- data Subreddit = Subreddit SubredditID SubredditName Title UTCTime Body (Maybe Body) Body Integer Bool (Maybe Bool) (Maybe Bool) (Maybe Bool) (Maybe Bool) (Maybe Bool) Bool
- mkSubredditName :: MonadThrow m => Text -> m SubredditName
- data ForegroundColor
- data FlairContent
- data FlairType
- data FlairResult = FlairResult Bool Text (HashMap Text Text) (HashMap Text Text)
- data FlairSelection = FlairSelection FlairChoice (Maybe Text) SubredditName
- data CurrentUserFlair
- data UserFlair = UserFlair (Maybe FlairText) (Maybe CSSClass)
- data FlairChoiceList
- data FlairChoice = FlairChoice FlairID FlairText Bool (Maybe CSSClass)
- data PostedFlairTemplate
- data FlairTemplate = FlairTemplate (Maybe FlairID) FlairText Bool (Maybe ForegroundColor) (Maybe RGBText) (Maybe CSSClass) (Maybe Bool) Word Bool FlairContent
- type FlairID = Text
- data FlairList = FlairList (Maybe UserID) (Maybe UserID) (Seq AssignedFlair)
- data AssignedFlair = AssignedFlair Username (Maybe FlairText) (Maybe CSSClass)
- type CSSClass = Text
- data FlairText
- mkFlairText :: MonadThrow m => Text -> m FlairText
- flairlistToListing :: FlairList -> Listing UserID AssignedFlair
- defaultFlairTemplate :: FlairTemplate
- data EmojiName
- data Emoji = Emoji EmojiName Bool Bool Bool (Maybe UserID) (Maybe UploadURL)
- mkEmoji :: EmojiName -> Emoji
- mkEmojiName :: MonadThrow m => Text -> m EmojiName
- data TextAreaWidget = TextAreaWidget (Maybe WidgetID) ShortName Body (Maybe Body) (Maybe WidgetStyles)
- data RulesDisplay
- data RulesWidget = RulesWidget (Maybe WidgetID) ShortName (Seq SubredditRule) RulesDisplay (Maybe WidgetStyles)
- data PostFlairWidgetDisplay
- data PostFlairInfo = PostFlairInfo FlairID Text ForegroundColor RGBText
- data PostFlairWidget = PostFlairWidget (Maybe WidgetID) ShortName (Seq FlairID) (HashMap FlairID PostFlairInfo) PostFlairWidgetDisplay (Maybe WidgetStyles)
- data ModInfo = ModInfo Username (Maybe FlairText) (Maybe ForegroundColor) (Maybe RGBText)
- data ModeratorsWidget = ModeratorsWidget (Maybe WidgetID) (Seq ModInfo) (Maybe Int) (Maybe WidgetStyles)
- data MenuLink = MenuLink Text URL
- data Submenu = Submenu (Seq MenuLink) Text
- data MenuChild
- data MenuWidget = MenuWidget (Maybe WidgetID) (Seq MenuChild)
- data Image = Image Integer Integer UploadURL (Maybe URL)
- data ImageWidget = ImageWidget (Maybe WidgetID) ShortName (Seq Image) (Maybe WidgetStyles)
- data IDCardWidget = IDCardWidget (Maybe WidgetID) ShortName Body Text Text (Maybe Integer) (Maybe Integer) (Maybe WidgetStyles)
- data ImageData = ImageData Name Int Int UploadURL
- data CustomWidget = CustomWidget (Maybe WidgetID) ShortName Body (Seq ImageData) Int (Maybe Body) (Maybe Text) (Maybe URL) (Maybe WidgetStyles)
- data CommunityInfo = CommunityInfo SubredditName (Maybe Integer) (Maybe RGBText) (Maybe URL) (Maybe URL) (Maybe Bool) (Maybe Bool)
- data CommunityListWidget = CommunityListWidget (Maybe WidgetID) ShortName (Seq CommunityInfo) (Maybe WidgetStyles)
- data CalendarConfig = CalendarConfig Word Bool Bool Bool Bool Bool
- data CalendarWidget = CalendarWidget (Maybe WidgetID) ShortName Text CalendarConfig Bool (Maybe WidgetStyles)
- data TextHover = TextHover ShortName (Maybe RGBText) (Maybe RGBText) (Maybe RGBText)
- data ImageHover = ImageHover UploadURL (Maybe Integer) (Maybe Integer)
- data ButtonHover
- data ButtonText = ButtonText ShortName URL RGBText (Maybe RGBText) (Maybe RGBText) (Maybe ButtonHover)
- data ButtonImage = ButtonImage ShortName UploadURL URL Int Int (Maybe ButtonHover)
- data Button
- data ButtonWidget = ButtonWidget (Maybe WidgetID) ShortName (Seq Button) Body (Maybe Body) (Maybe WidgetStyles)
- data WidgetStyles = WidgetStyles (Maybe RGBText) (Maybe RGBText)
- data ShortName
- data WidgetSection
- newtype WidgetID = WidgetID Text
- data Widget
- data SubredditWidgets = SubredditWidgets IDCardWidget ModeratorsWidget (Seq Widget) (Seq Widget) (Seq WidgetID) (Seq WidgetID)
- mkShortName :: MonadThrow m => Text -> m ShortName
- defaultCalendarConfig :: CalendarConfig
- mkCommunityInfo :: SubredditName -> CommunityInfo
- mkPostFlairWidget :: ShortName -> Seq FlairID -> PostFlairWidget
- mkTextAreaWidget :: ShortName -> Body -> TextAreaWidget
- data WikiPermLevel
- data WikiPageSettings = WikiPageSettings WikiPermLevel Bool (Seq Username)
- data WikiPageListing
- data WikiRevisionID
- data WikiRevision = WikiRevision WikiRevisionID WikiPageName UTCTime Username (Maybe Text) (Maybe Bool)
- data WikiPageName
- data WikiPage = WikiPage Body Body Username UTCTime Bool
- mkWikiPageName :: Text -> WikiPageName
Actions
getSubreddit :: MonadReddit m => SubredditName -> m Subreddit Source #
Get information about a Subreddit
. An ErrorWithStatus
will be thrown if
attempting to query information on banned or private Subreddit
s
getSubredditRules :: MonadReddit m => SubredditName -> m (Seq SubredditRule) Source #
Get a Subreddit
's SubredditRule
s
getPostRequirements :: MonadReddit m => SubredditName -> m PostRequirements Source #
Get the requirements that moderators have configured for all submissions on the given subreddit
getHotSubmissions :: MonadReddit m => SubredditName -> Paginator SubmissionID Submission -> m (Listing SubmissionID Submission) Source #
Get "hot" Submission
s for a given Subreddit
getNewSubmissions :: MonadReddit m => SubredditName -> Paginator SubmissionID Submission -> m (Listing SubmissionID Submission) Source #
Get "new" Submission
s for a given Subreddit
getRandomRisingSubmissions :: MonadReddit m => SubredditName -> Paginator SubmissionID Submission -> m (Listing SubmissionID Submission) Source #
Get "rising" Submission
s for a given Subreddit
getControversialSubmissions :: MonadReddit m => SubredditName -> Paginator SubmissionID Submission -> m (Listing SubmissionID Submission) Source #
Get "controversial" Submission
s for a given Subreddit
getRisingSubmissions :: MonadReddit m => SubredditName -> Paginator SubmissionID Submission -> m (Listing SubmissionID Submission) Source #
Get "rising" Submission
s for a given Subreddit
getTopSubmissions :: MonadReddit m => SubredditName -> Paginator SubmissionID Submission -> m (Listing SubmissionID Submission) Source #
Get "top" Submission
s for a given Subreddit
getRandomSubmission :: MonadReddit m => SubredditName -> m Submission Source #
Get a random submission from the subreddit. The sub must support this feature,
or an ErrorWithStatus
exception will be thrown
getStickiedSubmission Source #
:: MonadReddit m | |
=> Maybe Word | Which sticky to fetch. 1 is at the top of the sticky list, and is
the default if this param is |
-> SubredditName | |
-> m Submission |
Get one of the stickied submission, optionally specifying its position in the
sticky list, returning the top one otherwise. Note that this will throw an
ErrorWithStatus
if the sub does not have any stickied submissions
subscribe :: MonadReddit m => SubredditName -> m () Source #
Subscribe to a single subreddit
unsubscribe :: MonadReddit m => SubredditName -> m () Source #
Unsubscribe from a single subreddit
quarantineOptIn :: MonadReddit m => SubredditName -> m () Source #
Allow the authenticated user to access the quarantined subreddit
quarantineOptOut :: MonadReddit m => SubredditName -> m () Source #
Disallow the authenticated user from accessing the quarantined subreddit
Subreddit Listing
s
These actions return Listing
s of subreddits site-wide
corresponding to various filters
getDefaultSubreddits :: MonadReddit m => Paginator SubredditID Subreddit -> m (Listing SubredditID Subreddit) Source #
Get a Listing
of the default Subreddit
s
getNewSubreddits :: MonadReddit m => Paginator SubredditID Subreddit -> m (Listing SubredditID Subreddit) Source #
Get a Listing
of new Subreddit
s site-wide
getPopularSubreddits :: MonadReddit m => Paginator SubredditID Subreddit -> m (Listing SubredditID Subreddit) Source #
Get a Listing
of popular Subreddit
s site-wide
getPremiumSubreddits :: MonadReddit m => Paginator SubredditID Subreddit -> m (Listing SubredditID Subreddit) Source #
Get a Listing
of premium-only Subreddit
s
getGoldSubreddits :: MonadReddit m => Paginator SubredditID Subreddit -> m (Listing SubredditID Subreddit) Source #
Same as getPremiumSubreddits
, provided for compatibility purposes
searchSubreddits :: MonadReddit m => Text -> Paginator SubredditID Subreddit -> m (Listing SubredditID Subreddit) Source #
Search through subreddits based on both their names and descriptions
searchSubredditsByName Source #
:: MonadReddit m | |
=> Maybe Bool | If NSWF subreddits should be included, defaulting to |
-> Maybe Bool | Only exactly match the query, defaulting to |
-> Text | |
-> m (Seq SubredditName) |
Search through subreddits based on both their names
getRecommendedSubreddits Source #
:: (MonadReddit m, Foldable t) | |
=> Maybe (t SubredditName) | Subreddits to omit from the result |
-> t SubredditName | Subreddits to base the recommendations on |
-> m (Seq SubredditName) |
Get a list of recommended subreddits based on the provided subs. Subreddits to exclude from the recommendation may optionally be provided.
Note: Unfortunately, as of this writing, this action appears to only return an empty array for all inputs
followCollection :: MonadReddit m => CollectionID -> m () Source #
Follow the collection for the authenticated user
unfollowCollection :: MonadReddit m => CollectionID -> m () Source #
Unfollow the collection for the authenticated user
Collections
getCollections :: MonadReddit m => SubredditID -> m (Seq Collection) Source #
Get the Collection
s of a subreddit, given the sub ID. Collections obtained
through this action will not have the sortedLinks
field
Note: if you don't know the ID of the subreddit, you can use
getNamedCollections
, although this incurs an additional
network request to get the ID from the name
getCollectionsWithName :: MonadReddit m => SubredditName -> m (Seq Collection) Source #
Get the Collection
s of a subreddit, given the name of the sub. Collections
obtained through this action will not have the sortedLinks
field
Note: this incurs a greater overhead than getCollections
,
which you may want to use if you already know the subredditID
getCollection :: MonadReddit m => CollectionID -> m Collection Source #
Fetch the specifig Collection
, given its ID. This includes its sortedLinks
getCollectionByPermalink :: MonadReddit m => URL -> m Collection Source #
Get a Collection
given its permalink
. This includes its sortedLinks
Permalink URLs should be of the form https://{www.}reddit.com/r/<SUBREDDIT>/collections/<ID>
Flair
getUserFlairTemplates :: MonadReddit m => SubredditName -> m (Seq FlairTemplate) Source #
Get the user FlairTemplate
s on the given subreddit. This will throw an
APIException
(ErrorWithStatus
) if the sub does not allow users to set
their own flair and the authenticated user does not have mod privileges on
the sub
getSubmissionFlairTemplates :: MonadReddit m => SubredditName -> m (Seq FlairTemplate) Source #
Get the submission FlairTemplate
s on the given subreddit
getNewSubmissionFlairChoices :: MonadReddit m => SubredditName -> m (Seq FlairChoice) Source #
Get the available FlairChoice
s for new submissions on the given subreddit
getUserFlairChoices :: MonadReddit m => SubredditName -> m (Seq FlairChoice) Source #
Get the available FlairChoice
s for new submissions on the current subreddit
getSubmissionFlairChoices :: MonadReddit m => SubredditName -> SubmissionID -> m (Seq FlairChoice) Source #
Get the available FlairChoice
s for a particular submission on the given
subreddit
Wiki
getWikiPage :: MonadReddit m => SubredditName -> WikiPageName -> m WikiPage Source #
Get the subreddit WikiPage
specified by name
getWikiPages :: MonadReddit m => SubredditName -> m (Seq WikiPageName) Source #
Get all of the WikiPage
s on the subreddit wiki
getWikiPageRevision :: MonadReddit m => SubredditName -> WikiPageName -> WikiRevisionID -> m WikiPage Source #
Get a specific revision of a WikiPage
, specified by name and WikiRevisionID
getWikiPageRevisions :: MonadReddit m => SubredditName -> WikiPageName -> Paginator WikiRevisionID WikiRevision -> m (Listing WikiRevisionID WikiRevision) Source #
Get a Listing
of the WikiRevision
s for a given wikipage
:: MonadReddit m | |
=> SubredditName | |
-> WikiPageName | |
-> Maybe Text | The reason for the edit, if any |
-> Body | The new content for the page |
-> m () |
Edit the given wikipage, replacing its contents with the new contents provided. This requires moderator privileges or editing privileges for the page in question. If the page corresponding to the given name does not exist, it will be created
:: MonadReddit m | |
=> SubredditName | |
-> WikiPageName | |
-> Maybe Text | The reason for creating the page, if any |
-> Body | The new content for the page |
-> m () |
Create a new wikipage. If a page with the given name already exists, its contents will be replaced
Widgets
getSubredditWidgets :: MonadReddit m => SubredditName -> m SubredditWidgets Source #
Get a given subreddit's widgets
getAllSubredditWidgets :: MonadReddit m => SubredditName -> m (Seq Widget) Source #
Get all of a subreddit's Widget
s as a non-hierarchical list
Emojis
getSubredditEmojis :: MonadReddit m => SubredditName -> m (Seq Emoji) Source #
Get all of the emojis for the given subreddit. Note that this does not include the builtin "snoomojis"
Types
data BodyRestriction Source #
Rules concerning the presence of self-text bodies in posts
Instances
data PostRequirements Source #
Mod-created requirements for posting in a subreddit
Instances
The type of item that a SubredditRule
applies to
Instances
Eq RuleType Source # | |
Ord RuleType Source # | |
Defined in Network.Reddit.Types.Subreddit | |
Show RuleType Source # | |
Generic RuleType Source # | |
FromJSON RuleType Source # | |
ToHttpApiData RuleType Source # | |
Defined in Network.Reddit.Types.Subreddit toUrlPiece :: RuleType -> Text # toEncodedUrlPiece :: RuleType -> Builder # toHeader :: RuleType -> ByteString # toQueryParam :: RuleType -> Text # | |
type Rep RuleType Source # | |
Defined in Network.Reddit.Types.Subreddit type Rep RuleType = D1 ('MetaData "RuleType" "Network.Reddit.Types.Subreddit" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "CommentRule" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LinkRule" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AllRule" 'PrefixI 'False) (U1 :: Type -> Type))) |
data PostedSubredditRule Source #
Wrapper for parsing newly created SubredditRule
s, after POSTing a
NewSubredditRule
. Rather unbelievably, Reddit transmits these new
rules as a JSON object ... in a single element array ... encoded as a string
... inside another object!
Instances
data NewSubredditRule Source #
Represents a new SubredditRule
that can be created by moderators
Instances
data SubredditRule Source #
A Subreddit
rule. If you are a moderator, you can update the shortName
,
description
, violationReason
, and ruleType
fields. See
reorderSubredditRules
. New rules may also
be created with NewSubredditRule
s
Instances
newtype SubredditID Source #
Unique site-wide identifier for a subreddit
Instances
data SubredditName Source #
The name of a subreddit
Instances
Information about a subreddit. Fields prefixed with userIs
below apply to
the currently authenticated user
Subreddit SubredditID SubredditName Title UTCTime Body (Maybe Body) Body Integer Bool (Maybe Bool) (Maybe Bool) (Maybe Bool) (Maybe Bool) (Maybe Bool) Bool |
Instances
mkSubredditName :: MonadThrow m => Text -> m SubredditName Source #
Smart constructor for SubredditName
, which must be between 3 and 20 chars,
and may only include upper/lowercase alphanumeric chars, underscores, and
hyphens
data ForegroundColor Source #
Foreground color for v2 flair
Instances
data FlairContent Source #
The type of content that is allowed in a flair template
Instances
The type of flair, when creating a new template
Instances
Eq FlairType Source # | |
Show FlairType Source # | |
Generic FlairType Source # | |
ToHttpApiData FlairType Source # | |
Defined in Network.Reddit.Types.Flair toUrlPiece :: FlairType -> Text # toEncodedUrlPiece :: FlairType -> Builder # toHeader :: FlairType -> ByteString # toQueryParam :: FlairType -> Text # | |
type Rep FlairType Source # | |
Defined in Network.Reddit.Types.Flair |
data FlairResult Source #
The result of bulk setting of users' flairs as a mod action. The warnings
and errors
fields may be dynamically generated by Reddit, so they are
represented here as HashMap
s
Instances
data FlairSelection Source #
Select a FlairChoice
for a submission or for the user
Instances
data CurrentUserFlair Source #
Wrapper around UserFlair
for fetching the current flair. This uses the same
endpoint as the FlairChoiceList
above
Instances
Show CurrentUserFlair Source # | |
Defined in Network.Reddit.Types.Flair showsPrec :: Int -> CurrentUserFlair -> ShowS # show :: CurrentUserFlair -> String # showList :: [CurrentUserFlair] -> ShowS # | |
Generic CurrentUserFlair Source # | |
Defined in Network.Reddit.Types.Flair type Rep CurrentUserFlair :: Type -> Type # from :: CurrentUserFlair -> Rep CurrentUserFlair x # to :: Rep CurrentUserFlair x -> CurrentUserFlair # | |
FromJSON CurrentUserFlair Source # | |
Defined in Network.Reddit.Types.Flair parseJSON :: Value -> Parser CurrentUserFlair # parseJSONList :: Value -> Parser [CurrentUserFlair] # | |
type Rep CurrentUserFlair Source # | |
Defined in Network.Reddit.Types.Flair type Rep CurrentUserFlair = D1 ('MetaData "CurrentUserFlair" "Network.Reddit.Types.Flair" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'True) (C1 ('MetaCons "CurrentUserFlair" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UserFlair))) |
Flair that is currently assigned to a user
Instances
Eq UserFlair Source # | |
Show UserFlair Source # | |
Generic UserFlair Source # | |
FromJSON UserFlair Source # | |
type Rep UserFlair Source # | |
Defined in Network.Reddit.Types.Flair type Rep UserFlair = D1 ('MetaData "UserFlair" "Network.Reddit.Types.Flair" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "UserFlair" 'PrefixI 'True) (S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe FlairText)) :*: S1 ('MetaSel ('Just "cssClass") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe CSSClass)))) |
data FlairChoiceList Source #
Instances
Show FlairChoiceList Source # | |
Defined in Network.Reddit.Types.Flair showsPrec :: Int -> FlairChoiceList -> ShowS # show :: FlairChoiceList -> String # showList :: [FlairChoiceList] -> ShowS # | |
Generic FlairChoiceList Source # | |
Defined in Network.Reddit.Types.Flair type Rep FlairChoiceList :: Type -> Type # from :: FlairChoiceList -> Rep FlairChoiceList x # to :: Rep FlairChoiceList x -> FlairChoiceList # | |
FromJSON FlairChoiceList Source # | |
Defined in Network.Reddit.Types.Flair parseJSON :: Value -> Parser FlairChoiceList # parseJSONList :: Value -> Parser [FlairChoiceList] # | |
type Rep FlairChoiceList Source # | |
Defined in Network.Reddit.Types.Flair type Rep FlairChoiceList = D1 ('MetaData "FlairChoiceList" "Network.Reddit.Types.Flair" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'True) (C1 ('MetaCons "FlairChoiceList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq FlairChoice)))) |
data FlairChoice Source #
Information about flair that a user can choose. The templateID
corresponds
to the flairID
field of a FlairTemplate
Instances
data PostedFlairTemplate Source #
Wrapper around FlairTemplates
for posting via the API. If the flairID
field
is Nothing
, a new template will be created. Otherwise, the template with the
matching ID will be updated
Instances
data FlairTemplate Source #
Flair "templates" that describe choices for self-assigned flair, for both users and submissions
FlairTemplate (Maybe FlairID) FlairText Bool (Maybe ForegroundColor) (Maybe RGBText) (Maybe CSSClass) (Maybe Bool) Word Bool FlairContent |
Instances
An identifier for a FlairTemplate
Reddit strangely does not use their usual Listing
mechanism for paginating
assigned flairs, but a different data structure
Instances
Eq FlairList Source # | |
Show FlairList Source # | |
Generic FlairList Source # | |
FromJSON FlairList Source # | |
type Rep FlairList Source # | |
Defined in Network.Reddit.Types.Flair type Rep FlairList = D1 ('MetaData "FlairList" "Network.Reddit.Types.Flair" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "FlairList" 'PrefixI 'True) (S1 ('MetaSel ('Just "prev") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe UserID)) :*: (S1 ('MetaSel ('Just "next") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe UserID)) :*: S1 ('MetaSel ('Just "users") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Seq AssignedFlair))))) |
data AssignedFlair Source #
Flair that has been, or will be, assigned to a user
Instances
The text displayed by the FlairTemplate
Instances
Eq FlairText Source # | |
Show FlairText Source # | |
Generic FlairText Source # | |
Semigroup FlairText Source # | |
Monoid FlairText Source # | |
ToJSON FlairText Source # | |
Defined in Network.Reddit.Types.Flair | |
FromJSON FlairText Source # | |
ToHttpApiData FlairText Source # | |
Defined in Network.Reddit.Types.Flair toUrlPiece :: FlairText -> Text # toEncodedUrlPiece :: FlairText -> Builder # toHeader :: FlairText -> ByteString # toQueryParam :: FlairText -> Text # | |
type Rep FlairText Source # | |
Defined in Network.Reddit.Types.Flair |
mkFlairText :: MonadThrow m => Text -> m FlairText Source #
Smart constructor for FlairText
, the length of which not exceed 64
characters
defaultFlairTemplate :: FlairTemplate Source #
A FlairTemplate
with default fields, for convenience when creating new
templates
The name of an individual Emoji
Instances
Eq EmojiName Source # | |
Show EmojiName Source # | |
Generic EmojiName Source # | |
Semigroup EmojiName Source # | |
Monoid EmojiName Source # | |
FromJSON EmojiName Source # | |
ToHttpApiData EmojiName Source # | |
Defined in Network.Reddit.Types.Emoji toUrlPiece :: EmojiName -> Text # toEncodedUrlPiece :: EmojiName -> Builder # toHeader :: EmojiName -> ByteString # toQueryParam :: EmojiName -> Text # | |
type Rep EmojiName Source # | |
Defined in Network.Reddit.Types.Emoji |
A single emoji. This can either be one of Reddit's builtin "snoomojis"
or a custom emoji for a subreddit. See mkEmoji
for creating news ones
Instances
mkEmojiName :: MonadThrow m => Text -> m EmojiName Source #
Smart constructor for EmojiName
s, which may only contain alphanumeric characters,
'_', '-', and '&', and may not exceed 24 characters in length
data TextAreaWidget Source #
A widget composed of text. See mkTextAreaWidget
for constructing a new
widget
Instances
data RulesDisplay Source #
Display style for a RulesWidget
Instances
Eq RulesDisplay Source # | |
Defined in Network.Reddit.Types.Widget (==) :: RulesDisplay -> RulesDisplay -> Bool # (/=) :: RulesDisplay -> RulesDisplay -> Bool # | |
Show RulesDisplay Source # | |
Defined in Network.Reddit.Types.Widget showsPrec :: Int -> RulesDisplay -> ShowS # show :: RulesDisplay -> String # showList :: [RulesDisplay] -> ShowS # | |
Generic RulesDisplay Source # | |
Defined in Network.Reddit.Types.Widget type Rep RulesDisplay :: Type -> Type # from :: RulesDisplay -> Rep RulesDisplay x # to :: Rep RulesDisplay x -> RulesDisplay # | |
ToJSON RulesDisplay Source # | |
Defined in Network.Reddit.Types.Widget toJSON :: RulesDisplay -> Value # toEncoding :: RulesDisplay -> Encoding # toJSONList :: [RulesDisplay] -> Value # toEncodingList :: [RulesDisplay] -> Encoding # | |
FromJSON RulesDisplay Source # | |
Defined in Network.Reddit.Types.Widget parseJSON :: Value -> Parser RulesDisplay # parseJSONList :: Value -> Parser [RulesDisplay] # | |
type Rep RulesDisplay Source # | |
Defined in Network.Reddit.Types.Widget |
data RulesWidget Source #
A widget listing subreddit SubredditRule
s. The rules
field cannot be
updated through widget endpoints, and are excluded during serialization
Instances
data PostFlairWidgetDisplay Source #
The display orientation for PostFlairWidget
s
Instances
Eq PostFlairWidgetDisplay Source # | |
Defined in Network.Reddit.Types.Widget | |
Show PostFlairWidgetDisplay Source # | |
Defined in Network.Reddit.Types.Widget showsPrec :: Int -> PostFlairWidgetDisplay -> ShowS # show :: PostFlairWidgetDisplay -> String # showList :: [PostFlairWidgetDisplay] -> ShowS # | |
Generic PostFlairWidgetDisplay Source # | |
Defined in Network.Reddit.Types.Widget type Rep PostFlairWidgetDisplay :: Type -> Type # | |
ToJSON PostFlairWidgetDisplay Source # | |
Defined in Network.Reddit.Types.Widget toJSON :: PostFlairWidgetDisplay -> Value # toEncoding :: PostFlairWidgetDisplay -> Encoding # toJSONList :: [PostFlairWidgetDisplay] -> Value # | |
FromJSON PostFlairWidgetDisplay Source # | |
Defined in Network.Reddit.Types.Widget | |
type Rep PostFlairWidgetDisplay Source # | |
Defined in Network.Reddit.Types.Widget |
data PostFlairInfo Source #
Information about submission flair templates in a PostFlairWidget
Instances
data PostFlairWidget Source #
A widget listing flair choices for submissions. When creating a new widget,
the FlairID
s in the order
field must be valid template IDs for the given
subreddit. Existing flair templates can be obtained with
getSubmissionFlairTemplates
, which can
then be mapped over to obtain the IDs. Once the flair IDs have been obtained,
mkPostFlairWidget
can be used to construct a widget with default values for
most fields
PostFlairWidget (Maybe WidgetID) ShortName (Seq FlairID) (HashMap FlairID PostFlairInfo) PostFlairWidgetDisplay (Maybe WidgetStyles) |
Instances
Information about a moderator as displayed in a ModeratorsWidget
Instances
Eq ModInfo Source # | |
Show ModInfo Source # | |
Generic ModInfo Source # | |
ToJSON ModInfo Source # | |
Defined in Network.Reddit.Types.Widget | |
FromJSON ModInfo Source # | |
type Rep ModInfo Source # | |
Defined in Network.Reddit.Types.Widget type Rep ModInfo = D1 ('MetaData "ModInfo" "Network.Reddit.Types.Widget" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "ModInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Username) :*: S1 ('MetaSel ('Just "flairText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe FlairText))) :*: (S1 ('MetaSel ('Just "flairTextColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ForegroundColor)) :*: S1 ('MetaSel ('Just "flairBackgroundColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe RGBText))))) |
data ModeratorsWidget Source #
A widget listing the moderators of the subreddit. This widget cannot be
created. It can be updated by modifying the styles
field only
ModeratorsWidget (Maybe WidgetID) (Seq ModInfo) (Maybe Int) (Maybe WidgetStyles) |
Instances
A link in a MenuWidget
or Submenu
Instances
Eq MenuLink Source # | |
Show MenuLink Source # | |
Generic MenuLink Source # | |
ToJSON MenuLink Source # | |
Defined in Network.Reddit.Types.Widget | |
FromJSON MenuLink Source # | |
type Rep MenuLink Source # | |
Defined in Network.Reddit.Types.Widget type Rep MenuLink = D1 ('MetaData "MenuLink" "Network.Reddit.Types.Widget" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "MenuLink" 'PrefixI 'True) (S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "url") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 URL))) |
A submenu child in a MenuWidget
which contains MenuLink
s
Instances
A child widget in a MenuWidget
Instances
Eq MenuChild Source # | |
Show MenuChild Source # | |
Generic MenuChild Source # | |
ToJSON MenuChild Source # | |
Defined in Network.Reddit.Types.Widget | |
FromJSON MenuChild Source # | |
type Rep MenuChild Source # | |
Defined in Network.Reddit.Types.Widget type Rep MenuChild = D1 ('MetaData "MenuChild" "Network.Reddit.Types.Widget" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "SubmenuChild" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Submenu)) :+: C1 ('MetaCons "MenuLinkChild" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 MenuLink))) |
data MenuWidget Source #
A widget representing a menu
Instances
An individual image in an ImageWidget
Instances
Eq Image Source # | |
Show Image Source # | |
Generic Image Source # | |
ToJSON Image Source # | |
Defined in Network.Reddit.Types.Widget | |
FromJSON Image Source # | |
type Rep Image Source # | |
Defined in Network.Reddit.Types.Widget type Rep Image = D1 ('MetaData "Image" "Network.Reddit.Types.Widget" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "Image" 'PrefixI 'True) ((S1 ('MetaSel ('Just "width") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer) :*: S1 ('MetaSel ('Just "height") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer)) :*: (S1 ('MetaSel ('Just "url") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 UploadURL) :*: S1 ('MetaSel ('Just "linkURL") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe URL))))) |
data ImageWidget Source #
A widget composed of various Image
s
Instances
data IDCardWidget Source #
An ID card displaying information about the subreddit
IDCardWidget (Maybe WidgetID) ShortName Body Text Text (Maybe Integer) (Maybe Integer) (Maybe WidgetStyles) |
Instances
Image data that belongs to a CustomWidget
Instances
Eq ImageData Source # | |
Show ImageData Source # | |
Generic ImageData Source # | |
ToJSON ImageData Source # | |
Defined in Network.Reddit.Types.Widget | |
FromJSON ImageData Source # | |
type Rep ImageData Source # | |
Defined in Network.Reddit.Types.Widget type Rep ImageData = D1 ('MetaData "ImageData" "Network.Reddit.Types.Widget" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "ImageData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Name) :*: S1 ('MetaSel ('Just "height") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "width") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "url") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 UploadURL)))) |
data CustomWidget Source #
A custom widget
CustomWidget (Maybe WidgetID) ShortName Body (Seq ImageData) Int (Maybe Body) (Maybe Text) (Maybe URL) (Maybe WidgetStyles) |
Instances
data CommunityInfo Source #
Information about a single subreddit in a CommunityListWidget
. When
creating a new widget, only the name
field will be serialized
CommunityInfo SubredditName (Maybe Integer) (Maybe RGBText) (Maybe URL) (Maybe URL) (Maybe Bool) (Maybe Bool) |
Instances
data CommunityListWidget Source #
A widget listing related subreddits
Instances
data CalendarConfig Source #
Configuration options for a CalendarWidget
Instances
data CalendarWidget Source #
A widget representing a calendar
Instances
The state of a TextButton
when hovering over it
Instances
Eq TextHover Source # | |
Show TextHover Source # | |
Generic TextHover Source # | |
ToJSON TextHover Source # | |
Defined in Network.Reddit.Types.Widget | |
FromJSON TextHover Source # | |
type Rep TextHover Source # | |
Defined in Network.Reddit.Types.Widget type Rep TextHover = D1 ('MetaData "TextHover" "Network.Reddit.Types.Widget" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "TextHover" 'PrefixI 'True) ((S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ShortName) :*: S1 ('MetaSel ('Just "color") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe RGBText))) :*: (S1 ('MetaSel ('Just "fillColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe RGBText)) :*: S1 ('MetaSel ('Just "textColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe RGBText))))) |
data ImageHover Source #
The state of an ImageButton
when hovering over it
Instances
data ButtonHover Source #
The state of the Button
when hovering over it
Instances
data ButtonText Source #
Data for a TextButton
Instances
data ButtonImage Source #
Data for an ImageButton
Instances
An individual button in a ButtonWidget
Instances
Eq Button Source # | |
Show Button Source # | |
Generic Button Source # | |
ToJSON Button Source # | |
Defined in Network.Reddit.Types.Widget | |
FromJSON Button Source # | |
type Rep Button Source # | |
Defined in Network.Reddit.Types.Widget type Rep Button = D1 ('MetaData "Button" "Network.Reddit.Types.Widget" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "ImageButton" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ButtonImage)) :+: C1 ('MetaCons "TextButton" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ButtonText))) |
data ButtonWidget Source #
A widget containing buttons
Instances
data WidgetStyles Source #
Style options for an individual widget
Instances
A "short name" for any widget. This name must be less than 30 characters long
data WidgetSection Source #
The section in which certain Widget
s appear
Instances
Eq WidgetSection Source # | |
Defined in Network.Reddit.Types.Widget (==) :: WidgetSection -> WidgetSection -> Bool # (/=) :: WidgetSection -> WidgetSection -> Bool # | |
Show WidgetSection Source # | |
Defined in Network.Reddit.Types.Widget showsPrec :: Int -> WidgetSection -> ShowS # show :: WidgetSection -> String # showList :: [WidgetSection] -> ShowS # | |
Generic WidgetSection Source # | |
Defined in Network.Reddit.Types.Widget type Rep WidgetSection :: Type -> Type # from :: WidgetSection -> Rep WidgetSection x # to :: Rep WidgetSection x -> WidgetSection # | |
ToHttpApiData WidgetSection Source # | |
Defined in Network.Reddit.Types.Widget toUrlPiece :: WidgetSection -> Text # toEncodedUrlPiece :: WidgetSection -> Builder # toHeader :: WidgetSection -> ByteString # toQueryParam :: WidgetSection -> Text # | |
type Rep WidgetSection Source # | |
A widget ID. These are usually prefixed with the type of widget it corresponds
to, e.g. rules-2qh1i
for a RulesWidget
Instances
Eq WidgetID Source # | |
Show WidgetID Source # | |
Generic WidgetID Source # | |
ToJSON WidgetID Source # | |
Defined in Network.Reddit.Types.Widget | |
FromJSON WidgetID Source # | |
ToHttpApiData WidgetID Source # | |
Defined in Network.Reddit.Types.Widget toUrlPiece :: WidgetID -> Text # toEncodedUrlPiece :: WidgetID -> Builder # toHeader :: WidgetID -> ByteString # toQueryParam :: WidgetID -> Text # | |
type Rep WidgetID Source # | |
Defined in Network.Reddit.Types.Widget |
Represents one of various kinds of widgets
Instances
data SubredditWidgets Source #
An organized collection of a subreddit's widgets
SubredditWidgets IDCardWidget ModeratorsWidget (Seq Widget) (Seq Widget) (Seq WidgetID) (Seq WidgetID) |
Instances
mkShortName :: MonadThrow m => Text -> m ShortName Source #
Smart constructor for ShortName
s, which must be <= 30 characters long
defaultCalendarConfig :: CalendarConfig Source #
A calendar config with default values
mkCommunityInfo :: SubredditName -> CommunityInfo Source #
Convenience function for creating a new CommunityInfo
, where
all but one of the fields should be Nothing
mkPostFlairWidget :: ShortName -> Seq FlairID -> PostFlairWidget Source #
Make a new PostFlairWidget
with default values for most fields
mkTextAreaWidget :: ShortName -> Body -> TextAreaWidget Source #
Create a new TextAreaWidget
, with default values for most fields
data WikiPermLevel Source #
Editing permission level configured for a single WikiPage
Instances
data WikiPageSettings Source #
The settings that moderators have configured for a single WikiPage
Instances
data WikiPageListing Source #
Wrapper for listings of WikiPage
s, which have their own RedditKind
Instances
Show WikiPageListing Source # | |
Defined in Network.Reddit.Types.Wiki showsPrec :: Int -> WikiPageListing -> ShowS # show :: WikiPageListing -> String # showList :: [WikiPageListing] -> ShowS # | |
Generic WikiPageListing Source # | |
Defined in Network.Reddit.Types.Wiki type Rep WikiPageListing :: Type -> Type # from :: WikiPageListing -> Rep WikiPageListing x # to :: Rep WikiPageListing x -> WikiPageListing # | |
FromJSON WikiPageListing Source # | |
Defined in Network.Reddit.Types.Wiki parseJSON :: Value -> Parser WikiPageListing # parseJSONList :: Value -> Parser [WikiPageListing] # | |
type Rep WikiPageListing Source # | |
Defined in Network.Reddit.Types.Wiki type Rep WikiPageListing = D1 ('MetaData "WikiPageListing" "Network.Reddit.Types.Wiki" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'True) (C1 ('MetaCons "WikiPageListing" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq WikiPageName)))) |
data WikiRevisionID Source #
ID for a wikipage revision
Instances
data WikiRevision Source #
Information regarding a single WikiPage
revision
Instances
data WikiPageName Source #
The name of an individual wiki page. The name forms part of the URL, and should not contain spaces or uppercase characters
Instances
An individual subreddit wikipage along with its revision information
Instances
Eq WikiPage Source # | |
Show WikiPage Source # | |
Generic WikiPage Source # | |
FromJSON WikiPage Source # | |
type Rep WikiPage Source # | |
Defined in Network.Reddit.Types.Wiki type Rep WikiPage = D1 ('MetaData "WikiPage" "Network.Reddit.Types.Wiki" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "WikiPage" 'PrefixI 'True) ((S1 ('MetaSel ('Just "content") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Body) :*: S1 ('MetaSel ('Just "contentHTML") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Body)) :*: (S1 ('MetaSel ('Just "revisionBy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Username) :*: (S1 ('MetaSel ('Just "revisionDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "mayRevise") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))) |
mkWikiPageName :: Text -> WikiPageName Source #
Smart constructor for WikiPageName
s. Lowercases the contained text, and
replaces each space with a single underscore