mirror of
https://github.com/srid/rib.git
synced 2024-11-29 19:09:55 +03:00
commit
4bb9f22817
12
CHANGELOG.md
12
CHANGELOG.md
@ -2,12 +2,13 @@
|
|||||||
|
|
||||||
## 0.5.0.0 (UNRELEASED)
|
## 0.5.0.0 (UNRELEASED)
|
||||||
|
|
||||||
This release comes with major API refactor. Key changes:
|
This release comes with a major API refactor. Key changes:
|
||||||
|
|
||||||
- Support for both Pandoc and MMark parsers
|
- Added MMark support, as an alternative to Pandoc
|
||||||
- Add `Rib.Markup.Markup` type class to polymorphically select the parser
|
- Allows using arbitrary records to load metadata
|
||||||
- Add top-level `Rib` import namespace to ease of use
|
- This replaces the previous complex metadata API
|
||||||
- Replace complex metadata handling using straightforward aeson `Value` parsing
|
- Added `Document` type that uses the custom metadata record
|
||||||
|
- Add top-level `Rib` import namespace for ease of use
|
||||||
- Remove the following:
|
- Remove the following:
|
||||||
- JSON cache
|
- JSON cache
|
||||||
- `Rib.Simple`
|
- `Rib.Simple`
|
||||||
@ -17,6 +18,7 @@ Other changes:
|
|||||||
|
|
||||||
- Use type-safe path types using the [path](http://hackage.haskell.org/package/path) library.
|
- Use type-safe path types using the [path](http://hackage.haskell.org/package/path) library.
|
||||||
- Fix #40: Gracefully handle rendering/ parsing errors, without dying.
|
- Fix #40: Gracefully handle rendering/ parsing errors, without dying.
|
||||||
|
- Misc error reporting improvements
|
||||||
|
|
||||||
## 0.4.1.0
|
## 0.4.1.0
|
||||||
|
|
||||||
|
51
README.md
51
README.md
@ -31,15 +31,19 @@ using Rib:
|
|||||||
-- itself. Second, the metadata associated with each document.
|
-- itself. Second, the metadata associated with each document.
|
||||||
|
|
||||||
-- | A generated page is either an index of documents, or an individual document.
|
-- | A generated page is either an index of documents, or an individual document.
|
||||||
data Page doc
|
--
|
||||||
= Page_Index [Document doc]
|
-- The `Document` type takes two type variables:
|
||||||
| Page_Doc (Document doc)
|
-- 1. The first type variable specifies the parser to use: MMark or Pandoc
|
||||||
|
-- 2. The second type variable should be your metadata record
|
||||||
|
data Page
|
||||||
|
= Page_Index [Document MMark DocMeta]
|
||||||
|
| Page_Doc (Document MMark DocMeta)
|
||||||
|
|
||||||
-- | Type representing the metadata in our Markdown documents
|
-- | Type representing the metadata in our Markdown documents
|
||||||
--
|
--
|
||||||
-- Note that if a field is not optional (i.e., not Maybe) it must be present.
|
-- Note that if a field is not optional (i.e., not Maybe) it must be present.
|
||||||
data Meta
|
data DocMeta
|
||||||
= Meta
|
= DocMeta
|
||||||
{ title :: Text,
|
{ title :: Text,
|
||||||
description :: Maybe Text
|
description :: Maybe Text
|
||||||
}
|
}
|
||||||
@ -60,51 +64,46 @@ main = Rib.run [reldir|a|] [reldir|b|] $ do
|
|||||||
-- Copy over the static files
|
-- Copy over the static files
|
||||||
Rib.buildStaticFiles [[relfile|static/**|]]
|
Rib.buildStaticFiles [[relfile|static/**|]]
|
||||||
-- Build individual markdown files, generating .html for each.
|
-- Build individual markdown files, generating .html for each.
|
||||||
--
|
posts <- Rib.buildHtmlMulti [relfile|*.md|] (renderPage . Page_Doc)
|
||||||
-- NOTE: We use TypeApplications to specify the type of the `doc` type
|
|
||||||
-- variable, as used in the `Markup doc` constraint in the functions below.
|
|
||||||
-- There are currently two possible values: `MMark` (if you choose to use the
|
|
||||||
-- `mmark` parser) and `Pandoc` (if using pandoc).
|
|
||||||
posts <- Rib.buildHtmlMulti @MMark [relfile|*.md|] (renderPage . Page_Doc)
|
|
||||||
-- Build an index.html linking to the aforementioned files.
|
-- Build an index.html linking to the aforementioned files.
|
||||||
Rib.buildHtml [relfile|index.html|]
|
Rib.buildHtml [relfile|index.html|]
|
||||||
$ renderPage
|
$ renderPage
|
||||||
$ Page_Index posts
|
$ Page_Index posts
|
||||||
where
|
where
|
||||||
-- Define your site HTML here
|
-- Define your site HTML here
|
||||||
renderPage :: Markup doc => Page doc -> Html ()
|
renderPage :: Page -> Html ()
|
||||||
renderPage page = with html_ [lang_ "en"] $ do
|
renderPage page = with html_ [lang_ "en"] $ do
|
||||||
head_ $ do
|
head_ $ do
|
||||||
meta_ [httpEquiv_ "Content-Type", content_ "text/html; charset=utf-8"]
|
meta_ [httpEquiv_ "Content-Type", content_ "text/html; charset=utf-8"]
|
||||||
title_ $ case page of
|
title_ $ case page of
|
||||||
Page_Index _ -> "My website!"
|
Page_Index _ -> "My website!"
|
||||||
Page_Doc doc -> toHtml $ title $ Rib.getDocumentMeta doc
|
Page_Doc doc -> toHtml $ title $ Rib._document_meta doc
|
||||||
style_ [type_ "text/css"] $ Clay.render pageStyle
|
style_ [type_ "text/css"] $ Clay.render pageStyle
|
||||||
body_
|
body_
|
||||||
$ with div_ [id_ "thesite"]
|
$ with div_ [id_ "thesite"]
|
||||||
$ do
|
$ do
|
||||||
-- Main content
|
|
||||||
with a_ [href_ "/"] "Back to Home"
|
with a_ [href_ "/"] "Back to Home"
|
||||||
hr_ []
|
hr_ []
|
||||||
case page of
|
case page of
|
||||||
Page_Index docs ->
|
Page_Index docs ->
|
||||||
div_ $ forM_ docs $ \doc -> li_ $ do
|
div_ $ forM_ docs $ \doc -> with li_ [class_ "links"] $ do
|
||||||
let meta = Rib.getDocumentMeta doc
|
let meta = Rib._document_meta doc
|
||||||
b_ $ with a_ [href_ (Rib.getDocumentUrl doc)] $ toHtml $ title meta
|
b_ $ with a_ [href_ (Rib.getDocumentUrl doc)] $ toHtml $ title meta
|
||||||
case description meta of
|
maybe mempty Rib.renderMarkdown $
|
||||||
Just s -> em_ $ small_ $ toHtml s
|
description meta
|
||||||
Nothing -> mempty
|
|
||||||
Page_Doc doc ->
|
Page_Doc doc ->
|
||||||
with article_ [class_ "post"] $ do
|
with article_ [class_ "post"] $ do
|
||||||
h1_ $ toHtml $ title $ Rib.getDocumentMeta doc
|
h1_ $ toHtml $ title $ Rib._document_meta doc
|
||||||
Rib.renderDoc doc
|
Rib._document_html doc
|
||||||
-- Define your site CSS here
|
-- Define your site CSS here
|
||||||
pageStyle :: Css
|
pageStyle :: Css
|
||||||
pageStyle = div # "#thesite" ? do
|
pageStyle = "div#thesite" ? do
|
||||||
marginLeft $ pct 20
|
margin (em 4) (pc 20) (em 1) (pc 20)
|
||||||
marginTop $ em 4
|
"li.links" ? do
|
||||||
"h1" ? do
|
listStyleType none
|
||||||
fontSize $ em 2.3
|
marginTop $ em 1
|
||||||
|
"b" ? fontSize (em 1.2)
|
||||||
|
"p" ? sym margin (px 0)
|
||||||
```
|
```
|
||||||
|
|
||||||
(View full [`Main.hs`](https://github.com/srid/rib-sample/blob/master/Main.hs) at rib-sample)
|
(View full [`Main.hs`](https://github.com/srid/rib-sample/blob/master/Main.hs) at rib-sample)
|
||||||
|
@ -25,13 +25,14 @@ library
|
|||||||
exposed-modules:
|
exposed-modules:
|
||||||
Rib
|
Rib
|
||||||
Rib.App
|
Rib.App
|
||||||
Rib.Markup
|
Rib.Document
|
||||||
Rib.Markup.MMark
|
Rib.Markup.MMark
|
||||||
Rib.Markup.Pandoc
|
Rib.Markup.Pandoc
|
||||||
Rib.Server
|
Rib.Server
|
||||||
Rib.Shake
|
Rib.Shake
|
||||||
other-modules:
|
other-modules:
|
||||||
Prelude
|
Prelude
|
||||||
|
Rib.Markup
|
||||||
hs-source-dirs: src
|
hs-source-dirs: src
|
||||||
default-language: Haskell2010
|
default-language: Haskell2010
|
||||||
ghc-options:
|
ghc-options:
|
||||||
|
@ -3,7 +3,7 @@ module Rib
|
|||||||
( module Rib.App,
|
( module Rib.App,
|
||||||
module Rib.Shake,
|
module Rib.Shake,
|
||||||
module Rib.Server,
|
module Rib.Server,
|
||||||
module Rib.Markup,
|
Document(..),
|
||||||
MMark,
|
MMark,
|
||||||
renderMarkdown,
|
renderMarkdown,
|
||||||
Pandoc,
|
Pandoc,
|
||||||
@ -12,7 +12,7 @@ module Rib
|
|||||||
where
|
where
|
||||||
|
|
||||||
import Rib.App
|
import Rib.App
|
||||||
import Rib.Markup
|
import Rib.Document
|
||||||
import Rib.Markup.MMark (MMark, renderMarkdown)
|
import Rib.Markup.MMark (MMark, renderMarkdown)
|
||||||
import Rib.Markup.Pandoc (Pandoc, renderPandoc)
|
import Rib.Markup.Pandoc (Pandoc, renderPandoc)
|
||||||
import Rib.Server
|
import Rib.Server
|
||||||
|
95
src/Rib/Document.hs
Normal file
95
src/Rib/Document.hs
Normal file
@ -0,0 +1,95 @@
|
|||||||
|
{-# LANGUAGE DataKinds #-}
|
||||||
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
|
{-# LANGUAGE LambdaCase #-}
|
||||||
|
{-# LANGUAGE OverloadedLabels #-}
|
||||||
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
|
{-# LANGUAGE TypeApplications #-}
|
||||||
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
|
{-# LANGUAGE TypeOperators #-}
|
||||||
|
{-# LANGUAGE ViewPatterns #-}
|
||||||
|
|
||||||
|
module Rib.Document
|
||||||
|
( -- * Document type
|
||||||
|
Document (..),
|
||||||
|
mkDocumentFrom,
|
||||||
|
)
|
||||||
|
where
|
||||||
|
|
||||||
|
import Control.Monad.Except hiding (fail)
|
||||||
|
import Data.Aeson
|
||||||
|
import Lucid (Html)
|
||||||
|
import Named
|
||||||
|
import Path
|
||||||
|
import Rib.Markup
|
||||||
|
import qualified Text.Show
|
||||||
|
|
||||||
|
-- | A document written in a lightweight markup language (LML)
|
||||||
|
--
|
||||||
|
-- The type variable `repr` indicates the representation type of the Markup
|
||||||
|
-- parser to be used.
|
||||||
|
data Document repr meta
|
||||||
|
= Document
|
||||||
|
{ -- | Path to the document; relative to the source directory.
|
||||||
|
_document_path :: Path Rel File,
|
||||||
|
-- | Parsed representation of the document.
|
||||||
|
_document_val :: repr,
|
||||||
|
-- | HTML rendering of the parsed representation.
|
||||||
|
_document_html :: Html (),
|
||||||
|
-- | Metadata associated with the document as an aeson Value. If no metadata
|
||||||
|
-- is provided this will be Nothing.
|
||||||
|
_document_metaValue :: Maybe Value,
|
||||||
|
-- | The parsed metadata.
|
||||||
|
_document_meta :: meta
|
||||||
|
}
|
||||||
|
deriving (Generic, Show)
|
||||||
|
|
||||||
|
data DocumentError repr
|
||||||
|
= DocumentError_MarkupError (MarkupError repr)
|
||||||
|
| DocumentError_MetadataMissing
|
||||||
|
| DocumentError_MetadataBadJSON String
|
||||||
|
|
||||||
|
instance Markup repr => Show (DocumentError repr) where
|
||||||
|
show = \case
|
||||||
|
DocumentError_MarkupError e -> toString (showMarkupError @repr e)
|
||||||
|
DocumentError_MetadataMissing -> "Metadata missing"
|
||||||
|
DocumentError_MetadataBadJSON msg -> "Bad metadata JSON: " <> msg
|
||||||
|
|
||||||
|
-- | Parse, render to HTML and extract metadata from the given file.
|
||||||
|
--
|
||||||
|
-- Return the Document type containing converted values.
|
||||||
|
mkDocumentFrom ::
|
||||||
|
forall m b repr meta.
|
||||||
|
(MonadError (DocumentError repr) m, MonadIO m, Markup repr, FromJSON meta) =>
|
||||||
|
-- | File path, used only to identify (not access) the document
|
||||||
|
"relpath" :! Path Rel File ->
|
||||||
|
-- | Actual file path, for access and reading
|
||||||
|
"path" :! Path b File ->
|
||||||
|
m (Document repr meta)
|
||||||
|
mkDocumentFrom k@(arg #relpath -> k') f = do
|
||||||
|
v <-
|
||||||
|
liftEither
|
||||||
|
. first DocumentError_MarkupError
|
||||||
|
=<< liftIO (readDoc k f)
|
||||||
|
html <-
|
||||||
|
liftEither
|
||||||
|
$ first DocumentError_MarkupError
|
||||||
|
$ renderDoc v
|
||||||
|
let metaValueM = extractMeta v
|
||||||
|
metaValue <-
|
||||||
|
maybeToEither
|
||||||
|
DocumentError_MetadataMissing
|
||||||
|
metaValueM
|
||||||
|
meta <-
|
||||||
|
liftEither
|
||||||
|
$ first DocumentError_MetadataBadJSON
|
||||||
|
$ resultToEither
|
||||||
|
$ fromJSON metaValue
|
||||||
|
pure $ Document k' v html metaValueM meta
|
||||||
|
where
|
||||||
|
maybeToEither e = \case
|
||||||
|
Nothing -> throwError e
|
||||||
|
Just v -> pure v
|
||||||
|
resultToEither = \case
|
||||||
|
Error e -> Left e
|
||||||
|
Success v -> Right v
|
@ -10,10 +10,6 @@
|
|||||||
module Rib.Markup
|
module Rib.Markup
|
||||||
( -- * Type class
|
( -- * Type class
|
||||||
Markup (..),
|
Markup (..),
|
||||||
|
|
||||||
-- * Document type
|
|
||||||
Document (..),
|
|
||||||
getDocumentMeta,
|
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
@ -22,28 +18,6 @@ import Lucid (Html)
|
|||||||
import Named
|
import Named
|
||||||
import Path
|
import Path
|
||||||
|
|
||||||
-- | A document written in a lightweight markup language (LML)
|
|
||||||
--
|
|
||||||
-- The type variable `repr` indicates the representation type of the Markup
|
|
||||||
-- parser to be used.
|
|
||||||
data Document repr
|
|
||||||
= Document
|
|
||||||
{ -- | Path to the document; relative to the source directory.
|
|
||||||
_document_path :: Path Rel File,
|
|
||||||
_document_val :: repr,
|
|
||||||
-- | Metadata associated with the document as an aeson Value. If no metadata
|
|
||||||
-- is provided this will be Nothing.
|
|
||||||
_document_meta :: Maybe Value
|
|
||||||
}
|
|
||||||
deriving (Generic, Show)
|
|
||||||
|
|
||||||
getDocumentMeta :: FromJSON meta => Document repr -> meta
|
|
||||||
getDocumentMeta (Document fp _ mmeta) = case mmeta of
|
|
||||||
Nothing -> error $ toText $ "No metadata in document: " <> toFilePath fp -- TODO: handle errors gracefully
|
|
||||||
Just meta -> case fromJSON meta of
|
|
||||||
Error e -> error $ toText e
|
|
||||||
Success v -> v
|
|
||||||
|
|
||||||
-- | Class for denoting Markup representations.
|
-- | Class for denoting Markup representations.
|
||||||
--
|
--
|
||||||
-- See `Rib.Markup.Pandoc` and `Rib.Markup.MMark` for two available instances.
|
-- See `Rib.Markup.Pandoc` and `Rib.Markup.MMark` for two available instances.
|
||||||
@ -59,18 +33,25 @@ class Markup repr where
|
|||||||
Path Rel File ->
|
Path Rel File ->
|
||||||
-- | Markup text to parse
|
-- | Markup text to parse
|
||||||
Text ->
|
Text ->
|
||||||
Either (MarkupError repr) (Document repr)
|
Either (MarkupError repr) repr
|
||||||
|
|
||||||
-- | Like `reproc` but take the actual filepath instead of text.
|
-- | Like `parseDoc` but take the actual filepath instead of text.
|
||||||
readDoc ::
|
readDoc ::
|
||||||
|
forall b.
|
||||||
-- | File path, used to identify the document only.
|
-- | File path, used to identify the document only.
|
||||||
"relpath" :! Path Rel File ->
|
"relpath" :! Path Rel File ->
|
||||||
-- | Actual path to the file to parse.
|
-- | Actual path to the file to parse.
|
||||||
"path" :! Path b File ->
|
"path" :! Path b File ->
|
||||||
IO (Either (MarkupError repr) (Document repr))
|
IO (Either (MarkupError repr) repr)
|
||||||
|
|
||||||
|
extractMeta ::
|
||||||
|
repr ->
|
||||||
|
Maybe Value
|
||||||
|
|
||||||
-- | Render the document as Lucid HTML
|
-- | Render the document as Lucid HTML
|
||||||
renderDoc :: Document repr -> Html ()
|
renderDoc ::
|
||||||
|
repr ->
|
||||||
|
Either (MarkupError repr) (Html ())
|
||||||
|
|
||||||
-- | Convert `MarkupError` to string
|
-- | Convert `MarkupError` to string
|
||||||
showMarkupError :: MarkupError repr -> Text
|
showMarkupError :: MarkupError repr -> Text
|
||||||
|
@ -22,6 +22,7 @@ module Rib.Markup.MMark
|
|||||||
where
|
where
|
||||||
|
|
||||||
import Control.Foldl (Fold (..))
|
import Control.Foldl (Fold (..))
|
||||||
|
import Control.Monad.Except
|
||||||
import Lucid (Html)
|
import Lucid (Html)
|
||||||
import Named
|
import Named
|
||||||
import Path
|
import Path
|
||||||
@ -39,25 +40,23 @@ instance Markup MMark where
|
|||||||
|
|
||||||
parseDoc f s = case MMark.parse (toFilePath f) s of
|
parseDoc f s = case MMark.parse (toFilePath f) s of
|
||||||
Left e -> Left e
|
Left e -> Left e
|
||||||
Right doc ->
|
Right doc -> Right $ MMark.useExtensions exts $ useTocExt doc
|
||||||
let doc' = MMark.useExtensions exts $ useTocExt doc
|
|
||||||
meta = MMark.projectYaml doc
|
|
||||||
in Right $ Document f doc' meta
|
|
||||||
|
|
||||||
readDoc (Arg k) (Arg f) = do
|
readDoc (Arg k) (Arg f) = do
|
||||||
content <- readFileText (toFilePath f)
|
content <- readFileText (toFilePath f)
|
||||||
pure $ parseDoc k content
|
pure $ parseDoc k content
|
||||||
|
|
||||||
renderDoc = MMark.render . _document_val
|
extractMeta = MMark.projectYaml
|
||||||
|
|
||||||
|
renderDoc = Right . MMark.render
|
||||||
|
|
||||||
showMarkupError = toText . M.errorBundlePretty
|
showMarkupError = toText . M.errorBundlePretty
|
||||||
|
|
||||||
-- | Parse and render the markup directly to HTML
|
-- | Parse and render the markup directly to HTML
|
||||||
renderMarkdown :: Text -> Html ()
|
renderMarkdown :: Text -> Html ()
|
||||||
renderMarkdown =
|
renderMarkdown s = either (error . showMarkupError @MMark) id $ runExcept $ do
|
||||||
renderDoc
|
doc <- liftEither $ parseDoc @MMark [relfile|<memory>.md|] s
|
||||||
. either (error . showMarkupError @MMark) id
|
liftEither $ renderDoc doc
|
||||||
. parseDoc @MMark [relfile|<memory>.md|]
|
|
||||||
|
|
||||||
-- | Get the first image in the document if one exists
|
-- | Get the first image in the document if one exists
|
||||||
getFirstImg :: MMark -> Maybe URI
|
getFirstImg :: MMark -> Maybe URI
|
||||||
|
@ -61,8 +61,7 @@ instance Markup Pandoc where
|
|||||||
$ liftEither
|
$ liftEither
|
||||||
$ detectReader k
|
$ detectReader k
|
||||||
withExcept RibPandocError_PandocError $
|
withExcept RibPandocError_PandocError $
|
||||||
mkDoc k
|
parsePure r s
|
||||||
<$> parsePure r s
|
|
||||||
|
|
||||||
readDoc (Arg k) (Arg f) = runExceptT $ do
|
readDoc (Arg k) (Arg f) = runExceptT $ do
|
||||||
content <- readFileText $ toFilePath f
|
content <- readFileText $ toFilePath f
|
||||||
@ -70,19 +69,23 @@ instance Markup Pandoc where
|
|||||||
withExceptT RibPandocError_UnknownFormat $
|
withExceptT RibPandocError_UnknownFormat $
|
||||||
detectReader k
|
detectReader k
|
||||||
withExceptT RibPandocError_PandocError $
|
withExceptT RibPandocError_PandocError $
|
||||||
mkDoc k
|
parse r content
|
||||||
<$> parse r content
|
|
||||||
|
|
||||||
renderDoc = render . _document_val
|
extractMeta (Pandoc meta _) = flattenMeta meta
|
||||||
|
|
||||||
|
renderDoc =
|
||||||
|
fmap toHtmlRaw
|
||||||
|
. first RibPandocError_PandocError
|
||||||
|
. liftEither
|
||||||
|
. render'
|
||||||
|
|
||||||
showMarkupError = toText @String . show
|
showMarkupError = toText @String . show
|
||||||
|
|
||||||
-- | Parse and render the markup directly to HTML
|
-- | Parse and render the markup directly to HTML
|
||||||
renderPandoc :: Path Rel File -> Text -> Html ()
|
renderPandoc :: Path Rel File -> Text -> Html ()
|
||||||
renderPandoc f =
|
renderPandoc f s = either (error . show) id $ runExcept $ do
|
||||||
renderDoc
|
doc <- liftEither $ parseDoc @Pandoc f s
|
||||||
. either (error . showMarkupError @Pandoc) id
|
liftEither $ renderDoc doc
|
||||||
. parseDoc @Pandoc f
|
|
||||||
|
|
||||||
-- | Pure version of `parse`
|
-- | Pure version of `parse`
|
||||||
parsePure ::
|
parsePure ::
|
||||||
@ -100,7 +103,7 @@ parsePure r =
|
|||||||
-- Supports the [includeCode](https://github.com/owickstrom/pandoc-include-code) extension.
|
-- Supports the [includeCode](https://github.com/owickstrom/pandoc-include-code) extension.
|
||||||
parse ::
|
parse ::
|
||||||
(MonadIO m, MonadError PandocError m) =>
|
(MonadIO m, MonadError PandocError m) =>
|
||||||
-- | Document format. Example: `Text.Pandoc.Readers.readMarkdown`
|
-- | Markup format. Example: `Text.Pandoc.Readers.readMarkdown`
|
||||||
(ReaderOptions -> Text -> PandocIO Pandoc) ->
|
(ReaderOptions -> Text -> PandocIO Pandoc) ->
|
||||||
-- | Source text to parse
|
-- | Source text to parse
|
||||||
Text ->
|
Text ->
|
||||||
@ -112,18 +115,14 @@ parse r s = do
|
|||||||
settings = def {readerExtensions = exts}
|
settings = def {readerExtensions = exts}
|
||||||
includeSources = includeCode $ Just $ Format "html5"
|
includeSources = includeCode $ Just $ Format "html5"
|
||||||
|
|
||||||
-- | Like `render` but returns the raw HTML string, or the rendering error.
|
-- | Render a Pandoc document as HTML
|
||||||
render' :: Pandoc -> Either PandocError Text
|
render' :: Pandoc -> Either PandocError (Html ())
|
||||||
render' = runPure . writeHtml5String settings
|
render' = fmap toHtmlRaw . runPure . writeHtml5String settings
|
||||||
where
|
where
|
||||||
settings = def {writerExtensions = exts}
|
settings = def {writerExtensions = exts}
|
||||||
|
|
||||||
-- | Render a Pandoc document as Lucid HTML
|
|
||||||
render :: Pandoc -> Html ()
|
|
||||||
render = either (error . show) toHtmlRaw . render'
|
|
||||||
|
|
||||||
-- | Like `renderInlines` but returns the raw HTML string, or the rendering error.
|
-- | Like `renderInlines` but returns the raw HTML string, or the rendering error.
|
||||||
renderInlines' :: [Inline] -> Either PandocError Text
|
renderInlines' :: [Inline] -> Either PandocError (Html ())
|
||||||
renderInlines' = render' . Pandoc mempty . pure . Plain
|
renderInlines' = render' . Pandoc mempty . pure . Plain
|
||||||
|
|
||||||
-- | Render a list of Pandoc `Text.Pandoc.Inline` values as Lucid HTML
|
-- | Render a list of Pandoc `Text.Pandoc.Inline` values as Lucid HTML
|
||||||
@ -192,12 +191,6 @@ detectReader f = do
|
|||||||
-- MonadError instead.
|
-- MonadError instead.
|
||||||
catchInMonadError ef = either (throwError . ef) pure
|
catchInMonadError ef = either (throwError . ef) pure
|
||||||
|
|
||||||
mkDoc :: Path Rel File -> Pandoc -> Document Pandoc
|
|
||||||
mkDoc f v = Document f v $ getMetadata v
|
|
||||||
|
|
||||||
getMetadata :: Pandoc -> Maybe Value
|
|
||||||
getMetadata (Pandoc meta _) = flattenMeta meta
|
|
||||||
|
|
||||||
-- | Flatten a Pandoc 'Meta' into a well-structured JSON object.
|
-- | Flatten a Pandoc 'Meta' into a well-structured JSON object.
|
||||||
--
|
--
|
||||||
-- Renders Pandoc text objects into plain strings along the way.
|
-- Renders Pandoc text objects into plain strings along the way.
|
||||||
|
@ -12,9 +12,8 @@ import Development.Shake.FilePath ((-<.>))
|
|||||||
import Network.Wai.Application.Static (defaultFileServerSettings, ssListing, ssLookupFile, staticApp)
|
import Network.Wai.Application.Static (defaultFileServerSettings, ssListing, ssLookupFile, staticApp)
|
||||||
import qualified Network.Wai.Handler.Warp as Warp
|
import qualified Network.Wai.Handler.Warp as Warp
|
||||||
import Path hiding ((-<.>))
|
import Path hiding ((-<.>))
|
||||||
import Rib.Markup (Document (..))
|
import Rib.Document (Document (_document_path))
|
||||||
import WaiAppStatic.Types (StaticSettings)
|
import WaiAppStatic.Types (StaticSettings)
|
||||||
import Prelude
|
|
||||||
|
|
||||||
-- | WAI Settings suited for serving statically generated websites.
|
-- | WAI Settings suited for serving statically generated websites.
|
||||||
staticSiteServerSettings :: FilePath -> StaticSettings
|
staticSiteServerSettings :: FilePath -> StaticSettings
|
||||||
@ -32,11 +31,8 @@ staticSiteServerSettings root =
|
|||||||
--
|
--
|
||||||
-- You may also pass source paths as long as they map directly to destination
|
-- You may also pass source paths as long as they map directly to destination
|
||||||
-- path except for file extension.
|
-- path except for file extension.
|
||||||
getDocumentUrl ::
|
getDocumentUrl :: Document t meta -> Text
|
||||||
-- | Relative path to a page (extension is ignored)
|
getDocumentUrl doc = toText $ toFilePath ([absdir|/|] </> (_document_path doc)) -<.> ".html"
|
||||||
Document t ->
|
|
||||||
Text
|
|
||||||
getDocumentUrl (Document f _ _) = toText $ toFilePath ([absdir|/|] </> f) -<.> ".html"
|
|
||||||
|
|
||||||
-- | Run a HTTP server to serve a directory of static files
|
-- | Run a HTTP server to serve a directory of static files
|
||||||
--
|
--
|
||||||
|
@ -23,13 +23,15 @@ module Rib.Shake
|
|||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
|
import Data.Aeson
|
||||||
import Development.Shake
|
import Development.Shake
|
||||||
import Lucid (Html)
|
import Lucid (Html)
|
||||||
import qualified Lucid
|
import qualified Lucid
|
||||||
import Named
|
import Named
|
||||||
import Path
|
import Path
|
||||||
import Path.IO
|
import Path.IO
|
||||||
import Rib.Markup
|
import Rib.Document
|
||||||
|
import Rib.Markup (Markup)
|
||||||
|
|
||||||
data Dirs = Dirs (Path Rel Dir, Path Rel Dir)
|
data Dirs = Dirs (Path Rel Dir, Path Rel Dir)
|
||||||
deriving (Typeable)
|
deriving (Typeable)
|
||||||
@ -62,14 +64,14 @@ buildStaticFiles staticFilePatterns = do
|
|||||||
|
|
||||||
-- | Convert the given pattern of source files into their HTML.
|
-- | Convert the given pattern of source files into their HTML.
|
||||||
buildHtmlMulti ::
|
buildHtmlMulti ::
|
||||||
forall t.
|
forall repr meta.
|
||||||
Markup t =>
|
(Markup repr, FromJSON meta) =>
|
||||||
-- | Source file patterns
|
-- | Source file patterns
|
||||||
Path Rel File ->
|
Path Rel File ->
|
||||||
-- | How to render the given document to HTML
|
-- | How to render the given document to HTML
|
||||||
(Document t -> Html ()) ->
|
(Document repr meta -> Html ()) ->
|
||||||
-- | List of relative path to generated HTML and the associated document
|
-- | List of relative path to generated HTML and the associated document
|
||||||
Action [Document t]
|
Action [Document repr meta]
|
||||||
buildHtmlMulti pat r = do
|
buildHtmlMulti pat r = do
|
||||||
xs <- readDocMulti pat
|
xs <- readDocMulti pat
|
||||||
void $ forP xs $ \x -> do
|
void $ forP xs $ \x -> do
|
||||||
@ -79,22 +81,25 @@ buildHtmlMulti pat r = do
|
|||||||
|
|
||||||
-- | Like `readDoc'` but operates on multiple files
|
-- | Like `readDoc'` but operates on multiple files
|
||||||
readDocMulti ::
|
readDocMulti ::
|
||||||
forall t.
|
forall repr meta.
|
||||||
Markup t =>
|
(Markup repr, FromJSON meta) =>
|
||||||
-- | Source file patterns
|
-- | Source file patterns
|
||||||
Path Rel File ->
|
Path Rel File ->
|
||||||
Action [Document t]
|
Action [Document repr meta]
|
||||||
readDocMulti pat = do
|
readDocMulti pat = do
|
||||||
input <- ribInputDir
|
input <- ribInputDir
|
||||||
fs <- getDirectoryFiles' input [pat]
|
fs <- getDirectoryFiles' input [pat]
|
||||||
forP fs $ \f -> do
|
forP fs $ \f -> do
|
||||||
need $ toFilePath <$> [input </> f]
|
need $ toFilePath <$> [input </> f]
|
||||||
result <-
|
result <- runExceptT $
|
||||||
liftIO $
|
mkDocumentFrom
|
||||||
readDoc
|
! #relpath f
|
||||||
! #relpath f
|
! #path (input </> f)
|
||||||
! #path (input </> f)
|
-- TODO: Make error reporting nice, without Shake's stack trace ugliness.
|
||||||
pure $ either (error . showMarkupError @t) id result
|
case result of
|
||||||
|
Left e ->
|
||||||
|
fail $ "Error converting " <> toFilePath f <> " to HTML: " <> show e
|
||||||
|
Right v -> pure v
|
||||||
|
|
||||||
-- | Build a single HTML file with the given value
|
-- | Build a single HTML file with the given value
|
||||||
buildHtml :: Path Rel File -> Html () -> Action ()
|
buildHtml :: Path Rel File -> Html () -> Action ()
|
||||||
|
Loading…
Reference in New Issue
Block a user