Add a class type for Markdown and implement HTML rendering for Pages

This commit is contained in:
Tissevert 2020-06-20 16:23:33 +02:00
parent 19b3694d06
commit 937a6858e0
8 changed files with 50 additions and 35 deletions

View File

@ -10,14 +10,14 @@ import qualified Data.Map as Map (alter)
import Data.Time (defaultTimeLocale, getCurrentTimeZone, parseTimeM, timeZoneOffsetString) import Data.Time (defaultTimeLocale, getCurrentTimeZone, parseTimeM, timeZoneOffsetString)
import Data.Time.Clock.POSIX (POSIXTime, utcTimeToPOSIXSeconds) import Data.Time.Clock.POSIX (POSIXTime, utcTimeToPOSIXSeconds)
import Foreign.C.Types (CTime) import Foreign.C.Types (CTime)
import Markdown (Markdown(..), Metadata) import Markdown (Markdown(..), MarkdownContent(..), Metadata)
import qualified Markdown (at) import qualified Markdown (at)
import System.Posix.Files (getFileStatus, modificationTime) import System.Posix.Files (getFileStatus, modificationTime)
import Text.ParserCombinators.Parsec (ParseError) import Text.ParserCombinators.Parsec (ParseError)
newtype Article = Article { newtype Article = Article Markdown
getMarkdown :: Markdown instance MarkdownContent Article where
} getMarkdown (Article markdown) = markdown
setDate :: String -> CTime -> Metadata -> Metadata setDate :: String -> CTime -> Metadata -> Metadata
setDate tzOffset defaultDate = Map.alter timeStamp "date" setDate tzOffset defaultDate = Map.alter timeStamp "date"

View File

@ -6,7 +6,7 @@ module Collection (
, title , title
) where ) where
import Article(Article(..)) import Article(Article)
import Blog (Blog(..), Path(..)) import Blog (Blog(..), Path(..))
import Control.Monad.IO.Class (MonadIO(..)) import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Reader (MonadReader(..), ReaderT, asks) import Control.Monad.Reader (MonadReader(..), ReaderT, asks)
@ -15,7 +15,7 @@ import Data.Map ((!))
import qualified Data.Map as Map (elems, filterWithKey, toList) import qualified Data.Map as Map (elems, filterWithKey, toList)
import Data.Ord (Down(..)) import Data.Ord (Down(..))
import qualified Data.Set as Set (member) import qualified Data.Set as Set (member)
import Markdown (Markdown(metadata)) import Markdown (Markdown(metadata), MarkdownContent(..))
import Pretty ((.$)) import Pretty ((.$))
import System.Directory (createDirectoryIfMissing) import System.Directory (createDirectoryIfMissing)
import System.FilePath ((</>)) import System.FilePath ((</>))

View File

@ -1,10 +1,11 @@
{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
module DOM ( module DOM (
htmlDocument HasContent(..)
, htmlDocument
) where ) where
import Article (Article(..)) import Article (Article)
import qualified Article (preview) import qualified Article (preview)
import ArticlesList ( import ArticlesList (
ArticlesList(..), description, getArticles, otherURL, rssLinkTexts ArticlesList(..), description, getArticles, otherURL, rssLinkTexts
@ -21,7 +22,8 @@ import Lucid (
, head_, header_, href_, li_, link_, id_, meta_, pre_, rel_, script_, src_ , head_, header_, href_, li_, link_, id_, meta_, pre_, rel_, script_, src_
, title_, toHtml, toHtmlRaw, type_, ul_ , title_, toHtml, toHtmlRaw, type_, ul_
) )
import Markdown (Markdown(..)) import Markdown (Markdown(..), MarkdownContent(..))
import Page (Page)
import Prelude hiding (head, lookup) import Prelude hiding (head, lookup)
import Pretty ((.$)) import Pretty ((.$))
import System.FilePath.Posix ((<.>)) import System.FilePath.Posix ((<.>))
@ -32,7 +34,10 @@ class HasCard a => HasContent a where
content :: a -> HtmlGenerator () content :: a -> HtmlGenerator ()
instance HasContent Article where instance HasContent Article where
content = markdown True . Article.getMarkdown content = markdown True . getMarkdown
instance HasContent Page where
content = markdown True . getMarkdown
instance HasContent ArticlesList where instance HasContent ArticlesList where
content al@(ArticlesList {full}) = do content al@(ArticlesList {full}) = do

View File

@ -18,6 +18,7 @@ import qualified Data.Map as Map (lookup)
import Data.Text (Text, pack) import Data.Text (Text, pack)
import Lucid (HtmlT, content_, meta_) import Lucid (HtmlT, content_, meta_)
import Lucid.Base (makeAttribute) import Lucid.Base (makeAttribute)
import Markdown (MarkdownContent(..))
import qualified Markdown (Markdown(..)) import qualified Markdown (Markdown(..))
import Page (Page(..)) import Page (Page(..))
import Pretty ((.$)) import Pretty ((.$))
@ -49,16 +50,24 @@ make element siteURL = do
maybeImage = maybe (return ()) (og "image" . sitePrefix) maybeImage = maybe (return ()) (og "image" . sitePrefix)
sitePrefix = pack . (siteURL </>) sitePrefix = pack . (siteURL </>)
mDImage :: (Renderer m, MarkdownContent a ) => a -> m (Maybe String)
mDImage = return . Map.lookup "featuredImage" . Markdown.metadata . getMarkdown
mDTitle :: (Renderer m, MarkdownContent a) => a -> m String
mDTitle = return . Markdown.title . getMarkdown
mDUrlPath :: (Renderer m, MarkdownContent a) => a -> m String
mDUrlPath a = return $ Markdown.path (getMarkdown a) <.> "html"
instance HasCard Article where instance HasCard Article where
cardType _ = return "article" cardType _ = return "article"
description (Article (Markdown.Markdown {Markdown.metadata})) = description (Article (Markdown.Markdown {Markdown.metadata})) =
fmap pack . getDescription $ Map.lookup "summary" metadata fmap pack . getDescription $ Map.lookup "summary" metadata
where where
getDescription = maybe (asks $name.$("A new article on " <>)) return getDescription = maybe (asks $name.$("A new article on " <>)) return
image (Article (Markdown.Markdown {Markdown.metadata})) = image = mDImage
return $ Map.lookup "featuredImage" metadata title = mDTitle
title = return . Markdown.title . Article.getMarkdown urlPath = mDUrlPath
urlPath (Article markdown) = return $ Markdown.path markdown <.> "html"
instance HasCard Page where instance HasCard Page where
cardType _ = return "website" cardType _ = return "website"
@ -66,10 +75,9 @@ instance HasCard Page where
fmap pack . getDescription $ Map.lookup "summary" metadata fmap pack . getDescription $ Map.lookup "summary" metadata
where where
getDescription = maybe (title page) return getDescription = maybe (title page) return
image (Page (Markdown.Markdown {Markdown.metadata})) = image = mDImage
return $ Map.lookup "featuredImage" metadata title = mDTitle
title = return . Markdown.title . Page.getMarkdown urlPath = mDUrlPath
urlPath (Page markdown) = return $ Markdown.path markdown <.> "html"
instance HasCard ArticlesList where instance HasCard ArticlesList where
cardType _ = return "website" cardType _ = return "website"

View File

@ -4,7 +4,6 @@ module HTML (
generate generate
) where ) where
import Article(Article(..))
import ArticlesList (ArticlesList(..)) import ArticlesList (ArticlesList(..))
import Blog (Blog(..), Path(..)) import Blog (Blog(..), Path(..))
import Collection (Collection(..)) import Collection (Collection(..))
@ -13,9 +12,9 @@ import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Reader (ReaderT, asks) import Control.Monad.Reader (ReaderT, asks)
import qualified Data.Map as Map (elems) import qualified Data.Map as Map (elems)
import qualified Data.Text.Lazy.IO as TextIO (writeFile) import qualified Data.Text.Lazy.IO as TextIO (writeFile)
import DOM (htmlDocument) import DOM (HasContent, htmlDocument)
import Lucid (renderTextT) import Lucid (renderTextT)
import Markdown (Markdown(..)) import Markdown (Markdown(..), MarkdownContent(..))
import Pretty ((.$)) import Pretty ((.$))
import System.FilePath.Posix ((</>), (<.>)) import System.FilePath.Posix ((</>), (<.>))
@ -27,11 +26,11 @@ articlesLists collection@(Collection {basePath}) = [
file bool = if bool then "all" else "index" file bool = if bool then "all" else "index"
path bool = basePath </> file bool <.> "html" path bool = basePath </> file bool <.> "html"
generateArticles :: [Article] -> ReaderT Blog IO () generateMarkdown :: (HasContent a, MarkdownContent a) => [a] -> ReaderT Blog IO ()
generateArticles = mapM_ $ \article -> do generateMarkdown = mapM_ $ \content -> do
let relativePath = Markdown.path (Article.getMarkdown article) <.> "html" let relativePath = Markdown.path (getMarkdown content) <.> "html"
filePath <- (</> relativePath) <$> (asks $Blog.path.$root) filePath <- (</> relativePath) <$> (asks $Blog.path.$root)
(renderTextT $ htmlDocument article) >>= liftIO . TextIO.writeFile filePath (renderTextT $ htmlDocument content) >>= liftIO . TextIO.writeFile filePath
generateCollection :: Collection -> ReaderT Blog IO () generateCollection :: Collection -> ReaderT Blog IO ()
generateCollection (Collection {featured = []}) = return () generateCollection (Collection {featured = []}) = return ()
@ -42,5 +41,6 @@ generateCollection collection =
generate :: ReaderT Blog IO () generate :: ReaderT Blog IO ()
generate = do generate = do
asks articles >>= generateArticles . Map.elems asks articles >>= generateMarkdown . Map.elems
Collection.getAll >>= mapM_ generateCollection Collection.getAll >>= mapM_ generateCollection
asks pages >>= generateMarkdown . Map.elems

View File

@ -4,7 +4,6 @@ module JSON (
exportBlog exportBlog
) where ) where
import qualified Article (Article(..))
import Blog (Blog, Path, Skin, URL, Wording) import Blog (Blog, Path, Skin, URL, Wording)
import qualified Blog (Blog(..)) import qualified Blog (Blog(..))
import Data.Aeson (Options(..), ToJSON(..), genericToEncoding, defaultOptions) import Data.Aeson (Options(..), ToJSON(..), genericToEncoding, defaultOptions)
@ -12,9 +11,8 @@ import Data.Map (Map, mapWithKey)
import qualified Data.Map as Map (filter, keys) import qualified Data.Map as Map (filter, keys)
import qualified Data.Set as Set (elems, member) import qualified Data.Set as Set (elems, member)
import GHC.Generics import GHC.Generics
import Markdown (Markdown) import Markdown (Markdown, MarkdownContent(..))
import qualified Markdown (Markdown(..)) import qualified Markdown (Markdown(..))
import qualified Page (Page(..))
data MarkdownExport = MarkdownExport { data MarkdownExport = MarkdownExport {
title :: String title :: String
@ -50,9 +48,9 @@ instance ToJSON BlogExport where
exportBlog :: Blog -> BlogExport exportBlog :: Blog -> BlogExport
exportBlog blog = BlogExport { exportBlog blog = BlogExport {
articles = getArticles $ Article.getMarkdown <$> Blog.articles blog articles = getArticles $ getMarkdown <$> Blog.articles blog
, hasRSS = Blog.hasRSS blog , hasRSS = Blog.hasRSS blog
, pages = getPages $ Page.getMarkdown <$> Blog.pages blog , pages = getPages $ getMarkdown <$> Blog.pages blog
, path = Blog.path blog , path = Blog.path blog
, skin = Blog.skin blog , skin = Blog.skin blog
, tags = Set.elems <$> Blog.tags blog , tags = Set.elems <$> Blog.tags blog

View File

@ -1,6 +1,7 @@
{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NamedFieldPuns #-}
module Markdown ( module Markdown (
Markdown(..) Markdown(..)
, MarkdownContent(..)
, Metadata , Metadata
, at , at
, getKey , getKey
@ -27,6 +28,9 @@ data Markdown = Markdown {
, body :: [String] , body :: [String]
} }
class MarkdownContent a where
getMarkdown :: a -> Markdown
parser :: Parser Markdown parser :: Parser Markdown
parser = do parser = do
(title, metadata) <- skipMany eol *> (headerP <|> reverseHeaderP) (title, metadata) <- skipMany eol *> (headerP <|> reverseHeaderP)

View File

@ -3,13 +3,13 @@ module Page (
, at , at
) where ) where
import Markdown (Markdown(..)) import Markdown (Markdown(..), MarkdownContent(..))
import qualified Markdown as Markdown (at) import qualified Markdown as Markdown (at)
import Text.ParserCombinators.Parsec (ParseError) import Text.ParserCombinators.Parsec (ParseError)
newtype Page = Page { newtype Page = Page Markdown
getMarkdown :: Markdown instance MarkdownContent Page where
} getMarkdown (Page markdown) = markdown
at :: FilePath -> IO (Either ParseError (String, Page)) at :: FilePath -> IO (Either ParseError (String, Page))
at filePath = fmap makePage <$> Markdown.at filePath at filePath = fmap makePage <$> Markdown.at filePath