Safe Haskell | None |
---|---|
Language | Haskell2010 |
Web.Sitemap.Gen
Contents
Description
The Web.Sitemap.Gen
module contains types & rendering functions
to generate XML compliant with the sitemaps.org specification.
For more information see https://www.sitemaps.org/protocol.html
Synopsis
- newtype Sitemap = Sitemap {
- sitemapUrls :: [SitemapUrl]
- renderSitemap :: XmlOutput x => Sitemap -> x
- data SitemapUrl = SitemapUrl {}
- renderSitemapUrl :: SitemapUrl -> Xml Elem
- data ChangeFrequency
- renderChangeFrequency :: ChangeFrequency -> Xml Elem
- newtype SitemapIndex = SitemapIndex {
- indexEntries :: [IndexEntry]
- renderSitemapIndex :: XmlOutput x => SitemapIndex -> x
- data IndexEntry = IndexEntry {}
- renderIndexEntry :: IndexEntry -> Xml Elem
- sitemapNamespace :: Namespace
- formatSitemapTime :: UTCTime -> Text
- renderLastModified :: UTCTime -> Xml Elem
Sitemaps
A Sitemap
contains multiple SitemapUrl
elements which describe
crawlable locations for search engines.
Constructors
Sitemap | |
Fields
|
Instances
Eq Sitemap Source # | |
Read Sitemap Source # | |
Show Sitemap Source # | |
Generic Sitemap Source # | |
type Rep Sitemap Source # | |
Defined in Web.Sitemap.Gen type Rep Sitemap = D1 (MetaData "Sitemap" "Web.Sitemap.Gen" "sitemap-gen-0.1.0.0-38twZSkxbtk4P5or3XePQL" True) (C1 (MetaCons "Sitemap" PrefixI True) (S1 (MetaSel (Just "sitemapUrls") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [SitemapUrl]))) |
renderSitemap :: XmlOutput x => Sitemap -> x Source #
Render a Sitemap into a output format supported by the xmlgen
package.
In most cases you will want to generate a ByteString
.
data SitemapUrl Source #
A SitemapUrl
describes a single URL in a Sitemap
.
Constructors
SitemapUrl | |
Fields
|
Instances
renderSitemapUrl :: SitemapUrl -> Xml Elem Source #
Render a SitemapUrl
as a url
XML element.
data ChangeFrequency Source #
Describes how often a SitemapUrl' is updated. This is considered a hint for crawlers and may or may not be respected.
Constructors
Always | The page changes every time it is visited. |
Hourly | |
Daily | |
Weekly | |
Monthly | |
Yearly | |
Never | The page is archived and will never change from now on. |
Instances
renderChangeFrequency :: ChangeFrequency -> Xml Elem Source #
Build the XML text content for a ChangeFrequency
.
Sitemap Indexes
newtype SitemapIndex Source #
A SitemapIndex
allows informing crawlers of multiple sitemap files
hosted on the same domain.
Constructors
SitemapIndex | |
Fields
|
Instances
Eq SitemapIndex Source # | |
Defined in Web.Sitemap.Gen | |
Read SitemapIndex Source # | |
Defined in Web.Sitemap.Gen Methods readsPrec :: Int -> ReadS SitemapIndex # readList :: ReadS [SitemapIndex] # | |
Show SitemapIndex Source # | |
Defined in Web.Sitemap.Gen Methods showsPrec :: Int -> SitemapIndex -> ShowS # show :: SitemapIndex -> String # showList :: [SitemapIndex] -> ShowS # | |
Generic SitemapIndex Source # | |
Defined in Web.Sitemap.Gen Associated Types type Rep SitemapIndex :: Type -> Type # | |
type Rep SitemapIndex Source # | |
Defined in Web.Sitemap.Gen type Rep SitemapIndex = D1 (MetaData "SitemapIndex" "Web.Sitemap.Gen" "sitemap-gen-0.1.0.0-38twZSkxbtk4P5or3XePQL" True) (C1 (MetaCons "SitemapIndex" PrefixI True) (S1 (MetaSel (Just "indexEntries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [IndexEntry]))) |
renderSitemapIndex :: XmlOutput x => SitemapIndex -> x Source #
Render a SitemapIndex
into an output format supported by the
xmlgen
package.
data IndexEntry Source #
A single sitemap entry for a sitemap index.
Constructors
IndexEntry | |
Fields
|
Instances
Eq IndexEntry Source # | |
Defined in Web.Sitemap.Gen | |
Read IndexEntry Source # | |
Defined in Web.Sitemap.Gen Methods readsPrec :: Int -> ReadS IndexEntry # readList :: ReadS [IndexEntry] # readPrec :: ReadPrec IndexEntry # readListPrec :: ReadPrec [IndexEntry] # | |
Show IndexEntry Source # | |
Defined in Web.Sitemap.Gen Methods showsPrec :: Int -> IndexEntry -> ShowS # show :: IndexEntry -> String # showList :: [IndexEntry] -> ShowS # | |
Generic IndexEntry Source # | |
Defined in Web.Sitemap.Gen Associated Types type Rep IndexEntry :: Type -> Type # | |
type Rep IndexEntry Source # | |
Defined in Web.Sitemap.Gen type Rep IndexEntry = D1 (MetaData "IndexEntry" "Web.Sitemap.Gen" "sitemap-gen-0.1.0.0-38twZSkxbtk4P5or3XePQL" False) (C1 (MetaCons "IndexEntry" PrefixI True) (S1 (MetaSel (Just "indexLocation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "indexLastModified") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe UTCTime)))) |
renderIndexEntry :: IndexEntry -> Xml Elem Source #
Render an IndexEntry
as a sitemap
element.
Utilities
sitemapNamespace :: Namespace Source #
An XML Namespace for the sitemaps.org v0.9
schema.