lebd/src/Handler/Common.hs

69 lines
2.2 KiB
Haskell

{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
-- | Common handler functions.
module Handler.Common where
import Data.FileEmbed (embedFile)
import Yesod.Sitemap
import Import
import Model.Entry.Kind ( EntryKind, allEntryKinds )
import Widget.Entry ( entryR )
-- These handlers embed files in the executable at compile time to avoid a
-- runtime dependency, and for efficiency.
getFaviconR :: Handler TypedContent
getFaviconR = do cacheSeconds $ 60 * 60 * 24 * 30 -- cache for a month
return $ TypedContent "image/x-icon"
$ toContent $(embedFile "config/favicon.ico")
getKeybaseR :: Handler TypedContent
getKeybaseR = return $ TypedContent typePlain
$ toContent $(embedFile "config/keybase.txt")
getRobotsR :: Handler Text
getRobotsR = robots SitemapR
getSitemapR :: Handler TypedContent
getSitemapR = do
categories <- runDB $ selectList [] [Asc CategoryTag]
entries <- runDB $ selectList [] [Desc EntryPublished]
sitemap $ do
yield SitemapUrl
{ sitemapLoc = HomeR
, sitemapLastMod = Nothing
, sitemapChangeFreq = Just Daily
, sitemapPriority = Nothing
}
yieldMany $ categoryToSitemapUrl <$> categories
yieldMany $ kindToSitemapUrl <$> allEntryKinds
yieldMany $ entryToSitemapUrl <$> entries
categoryToSitemapUrl :: Entity Category -> SitemapUrl (Route App)
categoryToSitemapUrl (Entity _ cat) = SitemapUrl
{ sitemapLoc = CategoryR $ categoryTag cat
, sitemapLastMod = Nothing
, sitemapChangeFreq = Nothing
, sitemapPriority = Nothing
}
kindToSitemapUrl :: EntryKind -> SitemapUrl (Route App)
kindToSitemapUrl kind = SitemapUrl
{ sitemapLoc = EntriesR kind
, sitemapLastMod = Nothing
, sitemapChangeFreq = Nothing
, sitemapPriority = Nothing
}
entryToSitemapUrl :: Entity Entry -> SitemapUrl (Route App)
entryToSitemapUrl entry = SitemapUrl
{ sitemapLoc = entryR entry
, sitemapLastMod = Just . entryUpdated . entityVal $ entry
, sitemapChangeFreq = Nothing
, sitemapPriority = Nothing
}