lebd/src/Handler/Entries.hs

41 lines
1.2 KiB
Haskell

{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Handler.Entries where
import Import
import Yesod.AtomFeed ( atomLink )
import Model.Cache ( getCached )
import Model.Entry ( entryTitle )
import Widget.Entry ( entryR, hEntry )
import Widget.Feed ( hFeed )
import qualified Data.Text as T
import qualified Model.Entry.Kind as K
getEntriesR :: K.EntryKind -> Handler Html
getEntriesR kind = do
entries <- runDB $ selectList [EntryKind ==. kind] [Desc EntryPublished]
title <- asks $ siteTitle . appSettings
defaultLayout $ do
setTitle . toHtml . K.pluralise $ kind
atomLink (FeedKindR kind) $ T.concat [K.pluralise kind, " ~ ", title]
hFeed entries
getEntryR :: a -> EntryId -> Handler Html
getEntryR _ = renderEntry <=< getCached
getEntryWithSlugR :: a -> EntryId -> b -> Handler Html
getEntryWithSlugR kind = const . getEntryR kind
renderEntry :: (Entity Entry) -> Handler Html
renderEntry entry = do
let correctRoute = entryR entry
actualRoute <- getCurrentRoute
when (actualRoute /= Just correctRoute) $
redirectWith movedPermanently301 correctRoute
defaultLayout $ do
setTitle . toHtml . entryTitle . entityVal $ entry
hEntry entry