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

Safe HaskellNone
LanguageHaskell2010

Servant.Seo.Combinators

Contents

Synopsis

XML

data XML Source #

Content-Type representing text/xml. Used for serving /sitemap.xml.

Instances
Accept XML Source #
text/xml
Instance details

Defined in Servant.Seo.Combinators

Methods

contentType :: Proxy XML -> MediaType

contentTypes :: Proxy XML -> NonEmpty MediaType

MimeRender XML ByteString Source #
id
Instance details

Defined in Servant.Seo.Combinators

MimeRender XML ByteString Source #
BSL.fromStrict
Instance details

Defined in Servant.Seo.Combinators

MimeRender XML Text Source #
BSL.fromStrict . Text.encodeUtf8
Instance details

Defined in Servant.Seo.Combinators

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 DisallowedPathPiece from path piece marked as Disallow.

Instance details

Defined in Servant.Seo.Robots

Methods

toRobots :: Proxy (Disallow sym :> sub) -> RobotsInfo 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 #

(KnownSymbol sym, HasServer api context) => HasServer (Disallow sym :> api :: Type) context Source #

Disallow does not change specification at all.

Instance details

Defined in Servant.Seo.Combinators

Associated Types

type ServerT (Disallow sym :> api) m :: Type

Methods

route :: Proxy (Disallow sym :> api) -> Context context -> Delayed env (Server (Disallow sym :> api)) -> Router env

hoistServerWithContext :: Proxy (Disallow sym :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Disallow sym :> api) m -> ServerT (Disallow sym :> api) n

type ServerT (Disallow sym :> api :: Type) m Source # 
Instance details

Defined in Servant.Seo.Combinators

type ServerT (Disallow sym :> api :: Type) m = ServerT (sym :> api) m

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 #

Frequency as part of sitemap.xml spec has no impact on robots.txt.

Instance details

Defined in Servant.Seo.Robots

Methods

toRobots :: Proxy (Frequency period :> api) -> RobotsInfo 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 #

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

Frequency does not change specification at all.

Instance details

Defined in Servant.Seo.Combinators

Associated Types

type ServerT (Frequency period :> api) m :: Type

Methods

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 # 
Instance details

Defined in Servant.Seo.Combinators

type ServerT (Frequency period :> api :: Type) m = ServerT api m

Period

data Period Source #

Period is a type parameter for Frequency.

Instances
Enum Period Source # 
Instance details

Defined in Servant.Seo.Combinators

Eq Period Source # 
Instance details

Defined in Servant.Seo.Combinators

Methods

(==) :: Period -> Period -> Bool #

(/=) :: Period -> Period -> Bool #

Ord Period Source # 
Instance details

Defined in Servant.Seo.Combinators

Show Period Source # 
Instance details

Defined in Servant.Seo.Combinators

Generic Period Source # 
Instance details

Defined in Servant.Seo.Combinators

Associated Types

type Rep Period :: Type -> Type #

Methods

from :: Period -> Rep Period x #

to :: Rep Period x -> Period #

HasPeriod Never Source # 
Instance details

Defined in Servant.Seo.Combinators

HasPeriod Yearly Source # 
Instance details

Defined in Servant.Seo.Combinators

HasPeriod Monthly Source # 
Instance details

Defined in Servant.Seo.Combinators

HasPeriod Weekly Source # 
Instance details

Defined in Servant.Seo.Combinators

HasPeriod Daily Source # 
Instance details

Defined in Servant.Seo.Combinators

HasPeriod Hourly Source # 
Instance details

Defined in Servant.Seo.Combinators

HasPeriod Always Source # 
Instance details

Defined in Servant.Seo.Combinators

type Rep Period Source # 
Instance details

Defined in Servant.Seo.Combinators

type Rep Period = D1 (MetaData "Period" "Servant.Seo.Combinators" "servant-seo-0.1.2-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))))

class HasPeriod a where Source #

Methods

getPeriod :: Proxy a -> Period Source #

Instances
HasPeriod Never Source # 
Instance details

Defined in Servant.Seo.Combinators

HasPeriod Yearly Source # 
Instance details

Defined in Servant.Seo.Combinators

HasPeriod Monthly Source # 
Instance details

Defined in Servant.Seo.Combinators

HasPeriod Weekly Source # 
Instance details

Defined in Servant.Seo.Combinators

HasPeriod Daily Source # 
Instance details

Defined in Servant.Seo.Combinators

HasPeriod Hourly Source # 
Instance details

Defined in Servant.Seo.Combinators

HasPeriod Always Source # 
Instance details

Defined in Servant.Seo.Combinators

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 #

Priority as part of sitemap.xml spec has no impact on robots.txt.

Instance details

Defined in Servant.Seo.Robots

Methods

toRobots :: Proxy (Priority priority :> api) -> RobotsInfo 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 #

HasServer api context => HasServer (Priority priority :> api :: Type) context Source # 
Instance details

Defined in Servant.Seo.Combinators

Associated Types

type ServerT (Priority priority :> api) m :: Type

Methods

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 # 
Instance details

Defined in Servant.Seo.Combinators

type ServerT (Priority priority :> api :: Type) m = ServerT api m
>>> :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)