{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
module Servant.Seo.UI where
import Control.Lens hiding (Context)
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 :: *) (context :: [*]). (HasServer api context, HasRobots api)
=> Proxy api
-> Context context
-> Proxy ( RobotsAPI :<|> api )
apiWithRobots _ _ = Proxy
serveWithRobots
:: forall (api :: *) (context :: [*]). (HasServer api context, HasRobots api)
=> ServerUrl
-> Proxy api
-> Context context
-> Server api
-> Application
serveWithRobots serverUrl proxy context appServer = serveWithContext extendedProxy context extendedServer
where
extendedProxy :: Proxy (RobotsAPI :<|> api)
extendedProxy = apiWithRobots proxy context
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 :: *) (context :: [*]). (HasServer api context, HasSitemap api)
=> Proxy api
-> Context context
-> Proxy ( SitemapAPI :<|> api )
apiWithSitemap _ _ = Proxy
serveWithSitemap
:: forall (api :: *) (context :: [*]). (HasServer api context, HasSitemap api)
=> ServerUrl
-> Proxy api
-> Context context
-> Server api
-> Application
serveWithSitemap serverUrl proxy context appServer = serveWithContext extendedProxy context extendedServer
where
extendedProxy :: Proxy (SitemapAPI :<|> api)
extendedProxy = apiWithSitemap proxy context
extendedServer :: Server (SitemapAPI :<|> api)
extendedServer = sitemapServer serverUrl proxy context :<|> appServer
sitemapServer
:: forall (api :: *) (context :: [*]). (HasServer api context, HasSitemap api)
=> ServerUrl
-> Proxy api
-> Context context
-> Server SitemapAPI
sitemapServer serverUrl proxy context = serveSitemap serverUrl proxy context
:<|> serveNestedSitemap serverUrl proxy context
serveSitemap
:: forall (api :: *) (context :: [*]). (HasServer api context, HasSitemap api)
=> ServerUrl
-> Proxy api
-> Context context
-> 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 :: *) (context :: [*]). (HasServer api context, HasSitemap api)
=> ServerUrl
-> Proxy api
-> Context context
-> 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 :: *) (context :: [*]). (HasServer api context, HasRobots api, HasSitemap api)
=> ServerUrl
-> Proxy api
-> Context context
-> Server api
-> Application
serveWithSeo serverUrl appProxy appContext appServer = serveWithContext extendedProxy appContext 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 appContext
:<|> appServer
serveWithSeo'
:: forall (api :: *). (HasServer api '[], HasRobots api, HasSitemap api)
=> ServerUrl
-> Proxy api
-> Server api
-> Application
serveWithSeo' serverUrl appProxy appServer = serveWithSeo serverUrl appProxy EmptyContext appServer