servant-seo-0.1.2: Generate Robots.txt and Sitemap.xml specification for your servant API.

Safe HaskellNone
LanguageHaskell2010

Servant.Seo.Sitemap

Contents

Synopsis

Sitemap

SitemapInfo

data SitemapInfo Source #

Intermediate structure representing sitemap.xml file. During compilation API analysis performed. All HTML pages with Get verb would be populated into SitemapInfo and then updated to list of URLs, unless Disallow happened in the path to page. It consists of list of API branches and internal flag.

Instances
Eq SitemapInfo Source # 
Instance details

Defined in Servant.Seo.Sitemap

Ord SitemapInfo Source # 
Instance details

Defined in Servant.Seo.Sitemap

Show SitemapInfo Source # 
Instance details

Defined in Servant.Seo.Sitemap

Generic SitemapInfo Source # 
Instance details

Defined in Servant.Seo.Sitemap

Associated Types

type Rep SitemapInfo :: Type -> Type #

Semigroup SitemapInfo Source # 
Instance details

Defined in Servant.Seo.Sitemap

Monoid SitemapInfo Source # 
Instance details

Defined in Servant.Seo.Sitemap

type Rep SitemapInfo Source # 
Instance details

Defined in Servant.Seo.Sitemap

type Rep SitemapInfo = D1 (MetaData "SitemapInfo" "Servant.Seo.Sitemap" "servant-seo-0.1.2-inplace" False) (C1 (MetaCons "SitemapInfo" PrefixI True) (S1 (MetaSel (Just "_sitemapInfoEntries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [SitemapEntry]) :*: S1 (MetaSel (Just "_sitemapInfoPresent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ()))))

data SitemapEntry Source #

Represents single API branch. Could contain multiple values based on user decision. See ToSitemapParamPart or ToSitemapPathPiece for more details. Also contain optional Frequency and Priority.

Instances
Eq SitemapEntry Source # 
Instance details

Defined in Servant.Seo.Sitemap

Ord SitemapEntry Source # 
Instance details

Defined in Servant.Seo.Sitemap

Show SitemapEntry Source # 
Instance details

Defined in Servant.Seo.Sitemap

Generic SitemapEntry Source # 
Instance details

Defined in Servant.Seo.Sitemap

Associated Types

type Rep SitemapEntry :: Type -> Type #

Semigroup SitemapEntry Source # 
Instance details

Defined in Servant.Seo.Sitemap

Monoid SitemapEntry Source # 
Instance details

Defined in Servant.Seo.Sitemap

type Rep SitemapEntry Source # 
Instance details

Defined in Servant.Seo.Sitemap

type Rep SitemapEntry = D1 (MetaData "SitemapEntry" "Servant.Seo.Sitemap" "servant-seo-0.1.2-inplace" False) (C1 (MetaCons "SitemapEntry" PrefixI True) ((S1 (MetaSel (Just "_sitemapPathPieces") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PathPiece]) :*: S1 (MetaSel (Just "_sitemapQueryParts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(ParamName, [ParamValue])])) :*: (S1 (MetaSel (Just "_sitemapFrequency") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Period)) :*: S1 (MetaSel (Just "_sitemapPriority") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))))

newtype ParamName Source #

Constructors

ParamName Text 
Instances
Eq ParamName Source # 
Instance details

Defined in Servant.Seo.Sitemap

Ord ParamName Source # 
Instance details

Defined in Servant.Seo.Sitemap

Show ParamName Source # 
Instance details

Defined in Servant.Seo.Sitemap

Generic ParamName Source # 
Instance details

Defined in Servant.Seo.Sitemap

Associated Types

type Rep ParamName :: Type -> Type #

ToHttpApiData ParamName Source # 
Instance details

Defined in Servant.Seo.Sitemap

ToMarkup ParamName Source # 
Instance details

Defined in Servant.Seo.Sitemap

Methods

toMarkup :: ParamName -> Markup

preEscapedToMarkup :: ParamName -> Markup

type Rep ParamName Source # 
Instance details

Defined in Servant.Seo.Sitemap

type Rep ParamName = D1 (MetaData "ParamName" "Servant.Seo.Sitemap" "servant-seo-0.1.2-inplace" True) (C1 (MetaCons "ParamName" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype ParamValue Source #

Constructors

ParamValue Text 
Instances
Eq ParamValue Source # 
Instance details

Defined in Servant.Seo.Sitemap

Ord ParamValue Source # 
Instance details

Defined in Servant.Seo.Sitemap

Show ParamValue Source # 
Instance details

Defined in Servant.Seo.Sitemap

Generic ParamValue Source # 
Instance details

Defined in Servant.Seo.Sitemap

Associated Types

type Rep ParamValue :: Type -> Type #

ToHttpApiData ParamValue Source # 
Instance details

Defined in Servant.Seo.Sitemap

ToMarkup ParamValue Source # 
Instance details

Defined in Servant.Seo.Sitemap

Methods

toMarkup :: ParamValue -> Markup

preEscapedToMarkup :: ParamValue -> Markup

type Rep ParamValue Source # 
Instance details

Defined in Servant.Seo.Sitemap

type Rep ParamValue = D1 (MetaData "ParamValue" "Servant.Seo.Sitemap" "servant-seo-0.1.2-inplace" True) (C1 (MetaCons "ParamValue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data PathPiece Source #

Could be either path piece obtained from path :: Symbol or list of possible captured values provided by user.

Instances
Eq PathPiece Source # 
Instance details

Defined in Servant.Seo.Sitemap

Ord PathPiece Source # 
Instance details

Defined in Servant.Seo.Sitemap

Show PathPiece Source # 
Instance details

Defined in Servant.Seo.Sitemap

Generic PathPiece Source # 
Instance details

Defined in Servant.Seo.Sitemap

Associated Types

type Rep PathPiece :: Type -> Type #

type Rep PathPiece Source # 
Instance details

Defined in Servant.Seo.Sitemap

type Rep PathPiece = D1 (MetaData "PathPiece" "Servant.Seo.Sitemap" "servant-seo-0.1.2-inplace" False) (C1 (MetaCons "UrlPathPiece" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: C1 (MetaCons "CaptureValues" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text])))

isEmpty :: PathPiece -> Bool Source #

Checks that path piece is contained.

User dependent decisions for sitemap.

class ToHttpApiData a => ToSitemapParamPart a where Source #

How to get all possible values that should (or should not) be the parts of sitemap from query parameter values.

Example (in combination with Get '[HTML] will produce sitemap URLs):

>>> newtype ArticleId = ArticleId Int deriving newtype (Show, Eq, Enum, Ord, Num, ToHttpApiData)
>>> instance ToSitemapParamPart ArticleId where getParamsForIndexing _ _ = pure [0..100500]

Another example (params that have no affect on sitemap):

>>> newtype SortBy = SortBy Text deriving newtype (Show, Eq, ToHttpApiData)
>>> instance ToSitemapParamPart SortBy where getParamsForIndexing _ _ = pure mempty

Minimal complete definition

Nothing

Methods

getParamsForIndexing :: MonadIO m => Proxy a -> app -> m [a] Source #

Should be provided by user.

toParamPart :: MonadIO m => Proxy a -> env -> m [ParamValue] Source #

class ToHttpApiData a => ToSitemapPathPiece a where Source #

How to get all possible captured values that should (or should not) be the parts of sitemap.

Example (in combination with Get '[HTML] will produce sitemap URLs):

>>> newtype UserId = UserId Int deriving newtype (Show, Eq, Enum, Ord, Num, ToHttpApiData)
>>> instance ToSitemapPathPiece UserId where getPathPiecesForIndexing _ _ = pure [1..200000]

Another example (captured values that have no affect on sitemap):

>>> newtype Username = Username Text deriving newtype (Show, Eq, ToHttpApiData)
>>> instance ToSitemapPathPiece Username where getPathPiecesForIndexing _ _ = pure mempty

Minimal complete definition

Nothing

Methods

getPathPiecesForIndexing :: MonadIO m => Proxy a -> app -> m [a] Source #

Should be provided by user.

toPathPiece :: MonadIO m => Proxy a -> env -> m PathPiece Source #

Transforming API to SitemapInfo

class HasSitemap a where Source #

Servant API extension. It describes how to build SitemapInfo representation from servant API. There are plenty of types that add nothing to it.

WARNING: Do not derive this using DeriveAnyClass as the generated instance will loop indefinitely.

Minimal complete definition

toSitemapInfo | toSitemapInfoWith

Instances
HasSitemap EmptyAPI Source # 
Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy EmptyAPI -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy EmptyAPI -> m SitemapInfo Source #

HasSitemap Raw Source # 
Instance details

Defined in Servant.Seo.Sitemap

(HasSitemap a, HasSitemap b) => HasSitemap (a :<|> b :: Type) Source #

Collect multiple API branches together.

Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy (a :<|> b) -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy (a :<|> b) -> m SitemapInfo Source #

ToMarkup a => HasSitemap (Get (HTML ': ([] :: [Type])) a :: Type) Source #

Get '[HTML] enables sitemap for particular API branch.

Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy (Get (HTML ': []) a) -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy (Get (HTML ': []) a) -> m SitemapInfo Source #

ToMarkup a => HasSitemap (Get (HTML ': ([] :: [Type])) (Headers headers a) :: Type) Source # 
Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy (Get (HTML ': []) (Headers headers a)) -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy (Get (HTML ': []) (Headers headers a)) -> m SitemapInfo Source #

HasSitemap sub => HasSitemap (HttpVersion :> sub :: Type) Source # 
Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy (HttpVersion :> sub) -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy (HttpVersion :> sub) -> m SitemapInfo Source #

(HasSitemap sub, ToSitemapPathPiece a) => HasSitemap (Capture' mods sym a :> sub :: Type) Source #

Extract all possible values under Capture' and append them if sitemap is present for this particular branch.

Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy (Capture' mods sym a :> sub) -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy (Capture' mods sym a :> sub) -> m SitemapInfo Source #

HasSitemap sub => HasSitemap (CaptureAll sym a :> sub :: Type) Source # 
Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy (CaptureAll sym a :> sub) -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy (CaptureAll sym a :> sub) -> m SitemapInfo Source #

HasSitemap api => HasSitemap (Description desc :> api :: Type) Source # 
Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy (Description desc :> api) -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy (Description desc :> api) -> m SitemapInfo Source #

HasSitemap api => HasSitemap (Summary desc :> api :: Type) Source # 
Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy (Summary desc :> api) -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy (Summary desc :> api) -> m SitemapInfo Source #

HasSitemap sub => HasSitemap (Header' mods sym a :> sub :: Type) Source # 
Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy (Header' mods sym a :> sub) -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy (Header' mods sym a :> sub) -> m SitemapInfo Source #

HasSitemap sub => HasSitemap (IsSecure :> sub :: Type) Source # 
Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy (IsSecure :> sub) -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy (IsSecure :> sub) -> m SitemapInfo Source #

HasSitemap sub => HasSitemap (QueryFlag sym :> sub :: Type) Source # 
Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy (QueryFlag sym :> sub) -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy (QueryFlag sym :> sub) -> m SitemapInfo Source #

(ToSitemapParamPart a, HasSitemap sub, KnownSymbol sym) => HasSitemap (QueryParam' mods sym a :> sub :: Type) Source #

Extract all possible values under QueryParam' and append them if sitemap is present for this particular branch.

Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy (QueryParam' mods sym a :> sub) -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy (QueryParam' mods sym a :> sub) -> m SitemapInfo Source #

HasSitemap sub => HasSitemap (RemoteHost :> sub :: Type) Source # 
Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy (RemoteHost :> sub) -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy (RemoteHost :> sub) -> m SitemapInfo Source #

HasSitemap sub => HasSitemap (ReqBody' mods cs a :> sub :: Type) Source # 
Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy (ReqBody' mods cs a :> sub) -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy (ReqBody' mods cs a :> sub) -> m SitemapInfo Source #

HasSitemap sub => HasSitemap (StreamBody' mods fr ct a :> sub :: Type) Source # 
Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy (StreamBody' mods fr ct a :> sub) -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy (StreamBody' mods fr ct a :> sub) -> m SitemapInfo Source #

HasSitemap sub => HasSitemap (Vault :> sub :: Type) Source # 
Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy (Vault :> sub) -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy (Vault :> sub) -> m SitemapInfo Source #

(KnownNat n, KnownNat m, HasSitemap api) => HasSitemap (Priority ((,) n m) :> api :: Type) Source #

Extracts Priority from API branch.

Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m0 => Proxy (Priority (n, m) :> api) -> m0 SitemapInfo Source #

toSitemapInfoWith :: MonadIO m0 => env -> Proxy (Priority (n, m) :> api) -> m0 SitemapInfo Source #

(HasPeriod period, HasSitemap api) => HasSitemap (Frequency period :> api :: Type) Source #

Extracts Frequency from API branch.

Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy (Frequency period :> api) -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy (Frequency period :> api) -> m SitemapInfo Source #

(HasSitemap sub, KnownSymbol sym) => HasSitemap (Disallow sym :> sub :: Type) Source #

Disallow combinator invalidates sitemap for particular API branch.

Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy (Disallow sym :> sub) -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy (Disallow sym :> sub) -> m SitemapInfo Source #

(HasSitemap sub, KnownSymbol sym) => HasSitemap (sym :> sub :: Type) Source # 
Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy (sym :> sub) -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy (sym :> sub) -> m SitemapInfo Source #

HasSitemap sub => HasSitemap (WithNamedContext x c sub :: Type) Source # 
Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy (WithNamedContext x c sub) -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy (WithNamedContext x c sub) -> m SitemapInfo Source #

KnownNat status => HasSitemap (Verb method status cs a :: Type) Source # 
Instance details

Defined in Servant.Seo.Sitemap

Methods

toSitemapInfo :: MonadIO m => Proxy (Verb method status cs a) -> m SitemapInfo Source #

toSitemapInfoWith :: MonadIO m => env -> Proxy (Verb method status cs a) -> m SitemapInfo Source #

Rendering

data SitemapUrl Source #

Populated during SitemapInfo processing. SitemapUrl would be rendered in XML node in runtime.

Example: <url><loc>https://example.com/some/url</loc>.

Instances
Eq SitemapUrl Source # 
Instance details

Defined in Servant.Seo.Sitemap

Ord SitemapUrl Source # 
Instance details

Defined in Servant.Seo.Sitemap

Show SitemapUrl Source # 
Instance details

Defined in Servant.Seo.Sitemap

Generic SitemapUrl Source # 
Instance details

Defined in Servant.Seo.Sitemap

Associated Types

type Rep SitemapUrl :: Type -> Type #

type Rep SitemapUrl Source # 
Instance details

Defined in Servant.Seo.Sitemap

type Rep SitemapUrl = D1 (MetaData "SitemapUrl" "Servant.Seo.Sitemap" "servant-seo-0.1.2-inplace" False) (C1 (MetaCons "SitemapUrl" PrefixI True) (S1 (MetaSel (Just "_sitemapUrlLoc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [SitemapLoc]) :*: (S1 (MetaSel (Just "_sitemapUrlFrequency") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Period)) :*: S1 (MetaSel (Just "_sitemapUrlPriority") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))))

newtype SitemapLoc Source #

Represents single URL listed in sitemap.xml.

Constructors

SitemapLoc Text 
Instances
Eq SitemapLoc Source # 
Instance details

Defined in Servant.Seo.Sitemap

Ord SitemapLoc Source # 
Instance details

Defined in Servant.Seo.Sitemap

Show SitemapLoc Source # 
Instance details

Defined in Servant.Seo.Sitemap

Generic SitemapLoc Source # 
Instance details

Defined in Servant.Seo.Sitemap

Associated Types

type Rep SitemapLoc :: Type -> Type #

ToMarkup SitemapLoc Source # 
Instance details

Defined in Servant.Seo.Sitemap

Methods

toMarkup :: SitemapLoc -> Markup

preEscapedToMarkup :: SitemapLoc -> Markup

type Rep SitemapLoc Source # 
Instance details

Defined in Servant.Seo.Sitemap

type Rep SitemapLoc = D1 (MetaData "SitemapLoc" "Servant.Seo.Sitemap" "servant-seo-0.1.2-inplace" True) (C1 (MetaCons "SitemapLoc" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype ServerUrl Source #

Server prefix without trailing slash.

Constructors

ServerUrl Text 
Instances
Eq ServerUrl Source # 
Instance details

Defined in Servant.Seo.Sitemap

Ord ServerUrl Source # 
Instance details

Defined in Servant.Seo.Sitemap

Show ServerUrl Source # 
Instance details

Defined in Servant.Seo.Sitemap

IsString ServerUrl Source # 
Instance details

Defined in Servant.Seo.Sitemap

Generic ServerUrl Source # 
Instance details

Defined in Servant.Seo.Sitemap

Associated Types

type Rep ServerUrl :: Type -> Type #

ToMarkup ServerUrl Source # 
Instance details

Defined in Servant.Seo.Sitemap

Methods

toMarkup :: ServerUrl -> Markup

preEscapedToMarkup :: ServerUrl -> Markup

type Rep ServerUrl Source # 
Instance details

Defined in Servant.Seo.Sitemap

type Rep ServerUrl = D1 (MetaData "ServerUrl" "Servant.Seo.Sitemap" "servant-seo-0.1.2-inplace" True) (C1 (MetaCons "ServerUrl" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

type SitemapIndex = (Int, [SitemapUrl]) Source #

If sitemap consists of more than 50000 URLs, it should be indexed.

newtype SitemapIx Source #

Constructors

SitemapIx Int 
Instances
Eq SitemapIx Source # 
Instance details

Defined in Servant.Seo.Sitemap

Ord SitemapIx Source # 
Instance details

Defined in Servant.Seo.Sitemap

Show SitemapIx Source # 
Instance details

Defined in Servant.Seo.Sitemap

Generic SitemapIx Source # 
Instance details

Defined in Servant.Seo.Sitemap

Associated Types

type Rep SitemapIx :: Type -> Type #

FromHttpApiData SitemapIx Source # 
Instance details

Defined in Servant.Seo.Sitemap

ToHttpApiData SitemapIx Source # 
Instance details

Defined in Servant.Seo.Sitemap

ToSitemapPathPiece SitemapIx Source # 
Instance details

Defined in Servant.Seo.Sitemap

type Rep SitemapIx Source # 
Instance details

Defined in Servant.Seo.Sitemap

type Rep SitemapIx = D1 (MetaData "SitemapIx" "Servant.Seo.Sitemap" "servant-seo-0.1.2-inplace" True) (C1 (MetaCons "SitemapIx" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

sitemapEntryToUrlList :: ServerUrl -> SitemapEntry -> SitemapUrl Source #

Transform single sitemap entry to list of URLs.

sitemapUrlToNodes :: SitemapUrl -> [Node] Source #

Transform list of URLs to list of XML nodes.

mkNode :: Name -> [Node] -> Node Source #

Several XML rendering helpers.

mkNodeWithContent :: Name -> Text -> Node Source #

mkUrlNode :: Name -> [Node] -> SitemapLoc -> Node Source #

sitemapIndexUrlToNodes :: SitemapUrl -> [Node] Source #

Transform list of URLs to sitemap index XML nodes.

sitemapUrlsToDocument :: ServerUrl -> [SitemapUrl] -> Document Source #

Transform bunch of list of URLs to XML document.

sitemapIndexToDocument :: ServerUrl -> [SitemapUrl] -> Document Source #

Transform list of sitemap index URLs to XML document.

>>> :set -XDerivingStrategies -XGeneralizedNewtypeDeriving
>>>