Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data SitemapInfo = SitemapInfo {}
- data SitemapEntry = SitemapEntry {}
- newtype ParamName = ParamName Text
- newtype ParamValue = ParamValue Text
- data PathPiece
- isEmpty :: PathPiece -> Bool
- class ToHttpApiData a => ToSitemapParamPart a where
- getParamsForIndexing :: MonadIO m => Proxy a -> app -> m [a]
- toParamPart :: MonadIO m => Proxy a -> env -> m [ParamValue]
- class ToHttpApiData a => ToSitemapPathPiece a where
- getPathPiecesForIndexing :: MonadIO m => Proxy a -> app -> m [a]
- toPathPiece :: MonadIO m => Proxy a -> env -> m PathPiece
- sitemapInfoPresent :: Lens' SitemapInfo (Maybe ())
- sitemapInfoEntries :: Lens' SitemapInfo [SitemapEntry]
- sitemapQueryParts :: Lens' SitemapEntry [(ParamName, [ParamValue])]
- sitemapPriority :: Lens' SitemapEntry (Maybe Text)
- sitemapPathPieces :: Lens' SitemapEntry [PathPiece]
- sitemapFrequency :: Lens' SitemapEntry (Maybe Period)
- class HasSitemap a where
- toSitemapInfo :: MonadIO m => Proxy a -> m SitemapInfo
- toSitemapInfoWith :: MonadIO m => env -> Proxy a -> m SitemapInfo
- data SitemapUrl = SitemapUrl {}
- newtype SitemapLoc = SitemapLoc Text
- newtype ServerUrl = ServerUrl Text
- type SitemapIndex = (Int, [SitemapUrl])
- newtype SitemapIx = SitemapIx Int
- sitemapUrlPriority :: Lens' SitemapUrl (Maybe Text)
- sitemapUrlLoc :: Lens' SitemapUrl [SitemapLoc]
- sitemapUrlFrequency :: Lens' SitemapUrl (Maybe Period)
- sitemapEntryToUrlList :: ServerUrl -> SitemapEntry -> SitemapUrl
- sitemapUrlToNodes :: SitemapUrl -> [Node]
- mkNode :: Name -> [Node] -> Node
- mkNodeWithContent :: Name -> Text -> Node
- mkUrlNode :: Name -> [Node] -> SitemapLoc -> Node
- sitemapIndexUrlToNodes :: SitemapUrl -> [Node]
- sitemapUrlsToDocument :: ServerUrl -> [SitemapUrl] -> Document
- sitemapIndexToDocument :: ServerUrl -> [SitemapUrl] -> Document
- sitemapUrlsToRootLBS :: ServerUrl -> [SitemapUrl] -> ByteString
- sitemapUrlsToSitemapMap :: ServerUrl -> [SitemapUrl] -> Map Int ByteString
- renderSitemapWith :: (ServerUrl -> [SitemapUrl] -> Document) -> ServerUrl -> [SitemapUrl] -> ByteString
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
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
.
SitemapEntry | |
|
Instances
Instances
Eq ParamName Source # | |
Ord ParamName Source # | |
Defined in Servant.Seo.Sitemap | |
Show ParamName Source # | |
Generic ParamName Source # | |
ToHttpApiData ParamName Source # | |
Defined in Servant.Seo.Sitemap toUrlPiece :: ParamName -> Text toEncodedUrlPiece :: ParamName -> Builder toHeader :: ParamName -> ByteString toQueryParam :: ParamName -> Text | |
ToMarkup ParamName Source # | |
Defined in Servant.Seo.Sitemap toMarkup :: ParamName -> Markup preEscapedToMarkup :: ParamName -> Markup | |
type Rep ParamName Source # | |
Defined in Servant.Seo.Sitemap |
newtype ParamValue Source #
Instances
Could be either path piece obtained from path :: Symbol
or list of possible captured values provided by user.
Instances
Eq PathPiece Source # | |
Ord PathPiece Source # | |
Defined in Servant.Seo.Sitemap | |
Show PathPiece Source # | |
Generic PathPiece Source # | |
type Rep PathPiece Source # | |
Defined in Servant.Seo.Sitemap type Rep PathPiece = D1 (MetaData "PathPiece" "Servant.Seo.Sitemap" "servant-seo-0.1.0-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]))) |
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
Nothing
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
Nothing
getPathPiecesForIndexing :: MonadIO m => Proxy a -> app -> m [a] Source #
Should be provided by user.
toPathPiece :: MonadIO m => Proxy a -> env -> m PathPiece Source #
Instances
ToSitemapPathPiece SitemapIx Source # | |
Defined in Servant.Seo.Sitemap |
sitemapInfoPresent :: Lens' SitemapInfo (Maybe ()) Source #
sitemapInfoEntries :: Lens' SitemapInfo [SitemapEntry] Source #
sitemapQueryParts :: Lens' SitemapEntry [(ParamName, [ParamValue])] Source #
sitemapPriority :: Lens' SitemapEntry (Maybe Text) Source #
sitemapPathPieces :: Lens' SitemapEntry [PathPiece] Source #
sitemapFrequency :: Lens' SitemapEntry (Maybe Period) 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.
toSitemapInfo :: MonadIO m => Proxy a -> m SitemapInfo Source #
toSitemapInfoWith :: MonadIO m => env -> Proxy a -> m SitemapInfo Source #
Instances
HasSitemap EmptyAPI Source # | |
Defined in Servant.Seo.Sitemap toSitemapInfo :: MonadIO m => Proxy EmptyAPI -> m SitemapInfo Source # toSitemapInfoWith :: MonadIO m => env -> Proxy EmptyAPI -> m SitemapInfo Source # | |
HasSitemap Raw Source # | |
Defined in Servant.Seo.Sitemap toSitemapInfo :: MonadIO m => Proxy Raw -> m SitemapInfo Source # toSitemapInfoWith :: MonadIO m => env -> Proxy Raw -> m SitemapInfo Source # | |
(HasSitemap a, HasSitemap b) => HasSitemap (a :<|> b :: Type) Source # | Collect multiple API branches together. |
Defined in Servant.Seo.Sitemap 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 # |
|
Defined in Servant.Seo.Sitemap toSitemapInfo :: MonadIO m => Proxy (Get (HTML ': []) a) -> m SitemapInfo Source # toSitemapInfoWith :: MonadIO m => env -> Proxy (Get (HTML ': []) a) -> m SitemapInfo Source # | |
HasSitemap sub => HasSitemap (HttpVersion :> sub :: Type) Source # | |
Defined in Servant.Seo.Sitemap 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 |
Defined in Servant.Seo.Sitemap 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 # | |
Defined in Servant.Seo.Sitemap 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 # | |
Defined in Servant.Seo.Sitemap 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 # | |
Defined in Servant.Seo.Sitemap 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 # | |
Defined in Servant.Seo.Sitemap 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 # | |
Defined in Servant.Seo.Sitemap 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 # | |
Defined in Servant.Seo.Sitemap 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 |
Defined in Servant.Seo.Sitemap 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 # | |
Defined in Servant.Seo.Sitemap 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 # | |
Defined in Servant.Seo.Sitemap 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 # | |
Defined in Servant.Seo.Sitemap 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 # | |
Defined in Servant.Seo.Sitemap 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 |
Defined in Servant.Seo.Sitemap 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 |
Defined in Servant.Seo.Sitemap 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 # |
|
Defined in Servant.Seo.Sitemap 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 # | |
Defined in Servant.Seo.Sitemap 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 # | |
Defined in Servant.Seo.Sitemap 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 # | |
Defined in Servant.Seo.Sitemap 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
newtype SitemapLoc Source #
Represents single URL listed in sitemap.xml
.
Instances
Server prefix without trailing slash.
Instances
Eq ServerUrl Source # | |
Ord ServerUrl Source # | |
Defined in Servant.Seo.Sitemap | |
Show ServerUrl Source # | |
IsString ServerUrl Source # | |
Defined in Servant.Seo.Sitemap fromString :: String -> ServerUrl # | |
Generic ServerUrl Source # | |
ToMarkup ServerUrl Source # | |
Defined in Servant.Seo.Sitemap toMarkup :: ServerUrl -> Markup preEscapedToMarkup :: ServerUrl -> Markup | |
type Rep ServerUrl Source # | |
Defined in Servant.Seo.Sitemap |
type SitemapIndex = (Int, [SitemapUrl]) Source #
If sitemap consists of more than 50000 URLs, it should be indexed.
Instances
Eq SitemapIx Source # | |
Ord SitemapIx Source # | |
Defined in Servant.Seo.Sitemap | |
Show SitemapIx Source # | |
Generic SitemapIx Source # | |
FromHttpApiData SitemapIx Source # | |
Defined in Servant.Seo.Sitemap parseUrlPiece :: Text -> Either Text SitemapIx parseHeader :: ByteString -> Either Text SitemapIx parseQueryParam :: Text -> Either Text SitemapIx | |
ToHttpApiData SitemapIx Source # | |
Defined in Servant.Seo.Sitemap toUrlPiece :: SitemapIx -> Text toEncodedUrlPiece :: SitemapIx -> Builder toHeader :: SitemapIx -> ByteString toQueryParam :: SitemapIx -> Text | |
ToSitemapPathPiece SitemapIx Source # | |
Defined in Servant.Seo.Sitemap | |
type Rep SitemapIx Source # | |
Defined in Servant.Seo.Sitemap |
sitemapUrlPriority :: Lens' SitemapUrl (Maybe Text) Source #
sitemapUrlLoc :: Lens' SitemapUrl [SitemapLoc] Source #
sitemapUrlFrequency :: Lens' SitemapUrl (Maybe Period) Source #
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.
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.
sitemapUrlsToRootLBS :: ServerUrl -> [SitemapUrl] -> ByteString Source #
sitemapUrlsToSitemapMap :: ServerUrl -> [SitemapUrl] -> Map Int ByteString Source #
renderSitemapWith :: (ServerUrl -> [SitemapUrl] -> Document) -> ServerUrl -> [SitemapUrl] -> ByteString Source #
>>>
:set -XDerivingStrategies -XGeneralizedNewtypeDeriving
>>>