Safe Haskell | None |
---|---|
Language | Haskell2010 |
XML
Content-Type representing text/xml
. Used for serving /sitemap.xml
.
Instances
Accept XML Source # | text/xml |
Defined in Servant.Seo.Combinators contentType :: Proxy XML -> MediaType contentTypes :: Proxy XML -> NonEmpty MediaType | |
MimeRender XML ByteString Source # | id |
Defined in Servant.Seo.Combinators mimeRender :: Proxy XML -> ByteString -> ByteString | |
MimeRender XML ByteString Source # | BSL.fromStrict |
Defined in Servant.Seo.Combinators mimeRender :: Proxy XML -> ByteString -> ByteString0 | |
MimeRender XML Text Source # | BSL.fromStrict . Text.encodeUtf8 |
Defined in Servant.Seo.Combinators mimeRender :: Proxy XML -> Text -> ByteString |
Disallow
data Disallow (sym :: Symbol) Source #
Mark path as disallowed for indexing.
Example:
>>>
-- GET /admin/crm
>>>
type API = Disallow "admin" :> "crm" :> Get '[HTML] CrmPage
Code above will be transformed into Disallow /admin
.
Note: Disallow
impacts sitemap.xml
excluding underlying URLs from resulted sitemap.
Instances
(HasRobots sub, KnownSymbol sym) => HasRobots (Disallow sym :> sub :: Type) Source # | Generate new |
Defined in Servant.Seo.Robots | |
(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 # | |
(KnownSymbol sym, HasServer api context) => HasServer (Disallow sym :> api :: Type) context Source # |
|
Defined in Servant.Seo.Combinators | |
type ServerT (Disallow sym :> api :: Type) m Source # | |
Defined in Servant.Seo.Combinators |
Frequency
data Frequency (period :: Period) Source #
Frequency
optional parameter for sitemap.xml
. Shows to bots how often page will be changed.
Used with Period
.
>>>
type API = Frequency 'Yearly :> "about.php" :> Get '[HTML] AboutPage
Code above will be transformed in corresponding XML: <url><loc>https://example.com/about.php</loc><freq>yearly</freq></url>
.
Instances
(HasPeriod period, HasRobots api) => HasRobots (Frequency period :> api :: Type) Source # |
|
Defined in Servant.Seo.Robots | |
(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 # | |
(HasPeriod period, HasServer api context) => HasServer (Frequency period :> api :: Type) context Source # |
|
Defined in Servant.Seo.Combinators route :: Proxy (Frequency period :> api) -> Context context -> Delayed env (Server (Frequency period :> api)) -> Router env hoistServerWithContext :: Proxy (Frequency period :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Frequency period :> api) m -> ServerT (Frequency period :> api) n | |
type ServerT (Frequency period :> api :: Type) m Source # | |
Defined in Servant.Seo.Combinators |
Period
Instances
Enum Period Source # | |
Defined in Servant.Seo.Combinators | |
Eq Period Source # | |
Ord Period Source # | |
Show Period Source # | |
Generic Period Source # | |
HasPeriod Never Source # | |
HasPeriod Yearly Source # | |
HasPeriod Monthly Source # | |
HasPeriod Weekly Source # | |
HasPeriod Daily Source # | |
HasPeriod Hourly Source # | |
HasPeriod Always Source # | |
type Rep Period Source # | |
Defined in Servant.Seo.Combinators type Rep Period = D1 (MetaData "Period" "Servant.Seo.Combinators" "servant-seo-0.1.0-inplace" False) ((C1 (MetaCons "Never" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Yearly" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Monthly" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Weekly" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Daily" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Hourly" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Always" PrefixI False) (U1 :: Type -> Type)))) |
Priority
data Priority (priority :: (Nat, Nat)) Source #
Priority
optional parameter for sitemap.xml
. Set priority on listed page to bots.
Possible values are between '(0,0)
and '(1,0)
.
>>>
type API = Priority '(1,0) :> "news.php" :> Get '[HTML] NewsPage
Code above will be transformed in corresponding XML: <url><loc>https://example.com/news.php</loc><priority>1.0</priority></url>
.
Instances
HasRobots api => HasRobots (Priority priority :> api :: Type) Source # |
|
Defined in Servant.Seo.Robots | |
(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 # | |
HasServer api context => HasServer (Priority priority :> api :: Type) context Source # | |
Defined in Servant.Seo.Combinators route :: Proxy (Priority priority :> api) -> Context context -> Delayed env (Server (Priority priority :> api)) -> Router env hoistServerWithContext :: Proxy (Priority priority :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Priority priority :> api) m -> ServerT (Priority priority :> api) n | |
type ServerT (Priority priority :> api :: Type) m Source # | |
Defined in Servant.Seo.Combinators |
>>>
:set -XDerivingStrategies -XGeneralizedNewtypeDeriving
>>>
import Servant.HTML.Blaze (HTML)
>>>
import Text.Blaze (ToMarkup)
>>>
newtype CrmPage = CrmPage Text deriving newtype (ToMarkup)
>>>
newtype AboutPage = AboutPage Text deriving newtype (ToMarkup)
>>>
newtype NewsPage = NewsPage Text deriving newtype (ToMarkup)