{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
module Servant.Seo.UI where
import Control.Lens
import qualified Data.ByteString.Lazy as BSL
import Data.Coerce (coerce)
import qualified Data.List as List
import qualified Data.Map.Strict as Map
import Data.Text (Text)
import qualified Data.Text as Text
import Servant
import Servant.Seo.Combinators
import Servant.Seo.Robots
import Servant.Seo.Sitemap
type RobotsAPI = "robots.txt" :> Get '[PlainText] Text
apiWithRobots
:: forall (api :: *). (HasServer api '[], HasRobots api)
=> Proxy api
-> Proxy ( RobotsAPI :<|> api )
apiWithRobots _ = Proxy
serveWithRobots
:: forall (api :: *). (HasServer api '[], HasRobots api)
=> ServerUrl
-> Proxy api
-> Server api
-> Application
serveWithRobots serverUrl proxy appServer = serve extendedProxy extendedServer
where
extendedProxy :: Proxy (RobotsAPI :<|> api)
extendedProxy = apiWithRobots proxy
extendedServer :: Server (RobotsAPI :<|> api)
extendedServer = serveRobots serverUrl (toRobots proxy) :<|> appServer
serveRobots :: ServerUrl -> RobotsInfo -> Handler Text
serveRobots serverUrl robots = robots
^. robotsDisallowedPaths
. to (fmap (Text.append "Disallow " . coerce))
. to addUserAgent
. to (addSitemap serverUrl)
. to Text.unlines
. to pure
where
addSitemap (ServerUrl url) r = if robots ^. robotsSitemapPath . to (== Nothing)
then r
else r <> ["", "Sitemap: " <> url <> "/sitemap.xml"]
addUserAgent r = ["User-agent: *"] <> r
type SitemapAPI
= "sitemap.xml" :> Get '[XML] BSL.ByteString
:<|> "sitemap" :> Capture ":sitemap" SitemapIx :> "sitemap.xml" :> Get '[XML] BSL.ByteString
apiWithSitemap
:: forall (api :: *). (HasServer api '[], HasSitemap api)
=> Proxy api
-> Proxy ( SitemapAPI :<|> api )
apiWithSitemap _ = Proxy
serveWithSitemap
:: forall (api :: *). (HasServer api '[], HasSitemap api)
=> ServerUrl
-> Proxy api
-> Server api
-> Application
serveWithSitemap serverUrl proxy appServer = serve extendedProxy extendedServer
where
extendedProxy :: Proxy (SitemapAPI :<|> api)
extendedProxy = apiWithSitemap proxy
extendedServer :: Server (SitemapAPI :<|> api)
extendedServer = sitemapServer serverUrl proxy :<|> appServer
sitemapServer
:: forall (api :: *). (HasServer api '[], HasSitemap api)
=> ServerUrl
-> Proxy api
-> Server SitemapAPI
sitemapServer serverUrl proxy = serveSitemap serverUrl proxy
:<|> serveNestedSitemap serverUrl proxy
serveSitemap
:: forall (api :: *). (HasServer api '[], HasSitemap api)
=> ServerUrl
-> Proxy api
-> Handler BSL.ByteString
serveSitemap serverUrl proxy = do
sitemap <- toSitemapInfo proxy
pure $ sitemapUrlsToRootLBS serverUrl (urls sitemap)
where
urls x = x ^. sitemapInfoEntries . to (fmap (sitemapEntryToUrlList serverUrl))
serveNestedSitemap
:: forall (api :: *). (HasServer api '[], HasSitemap api)
=> ServerUrl
-> Proxy api
-> SitemapIx
-> Handler BSL.ByteString
serveNestedSitemap serverUrl proxy (SitemapIx sitemapIndex) = do
sitemap <- toSitemapInfo proxy
let urls = getUrls sitemap
if urls & concatMap _sitemapUrlLoc & length & (<= 50000)
then throwError err404
else case Map.lookup sitemapIndex (urlgroups urls) of
Nothing -> throwError err404
Just content -> pure content
where
getUrls x = x ^. sitemapInfoEntries
. to (fmap (sitemapEntryToUrlList serverUrl))
. to List.sort
urlgroups xs = sitemapUrlsToSitemapMap serverUrl xs
serveWithSeo
:: forall (api :: *). (HasServer api '[], HasRobots api, HasSitemap api)
=> ServerUrl
-> Proxy api
-> Server api
-> Application
serveWithSeo serverUrl appProxy appServer = serve extendedProxy extendedServer
where
extendedProxy :: Proxy (RobotsAPI :<|> SitemapAPI :<|> api)
extendedProxy = Proxy
extendedServer :: Server (RobotsAPI :<|> SitemapAPI :<|> api)
extendedServer = serveRobots serverUrl (toRobots (Proxy :: Proxy (SitemapAPI :<|> api)))
:<|> sitemapServer serverUrl appProxy
:<|> appServer