mirror of
https://github.com/srid/rib.git
synced 2024-11-30 03:45:00 +03:00
Detach Document type from Markup type class
Separation of concerns! Makes it simpler reason about what's happening.
This commit is contained in:
parent
ef83dac0f1
commit
94dcc31991
@ -2,6 +2,7 @@
|
|||||||
{-# LANGUAGE DataKinds #-}
|
{-# LANGUAGE DataKinds #-}
|
||||||
{-# LANGUAGE DeriveGeneric #-}
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
|
{-# LANGUAGE OverloadedLabels #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
{-# LANGUAGE TypeApplications #-}
|
{-# LANGUAGE TypeApplications #-}
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
@ -13,9 +14,11 @@ module Rib.Markup
|
|||||||
|
|
||||||
-- * Document type
|
-- * Document type
|
||||||
Document (..),
|
Document (..),
|
||||||
|
mkDocumentFrom,
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
|
import Control.Monad.Except hiding (fail)
|
||||||
import Data.Aeson
|
import Data.Aeson
|
||||||
import Lucid (Html)
|
import Lucid (Html)
|
||||||
import Named
|
import Named
|
||||||
@ -39,6 +42,27 @@ data Document repr
|
|||||||
}
|
}
|
||||||
deriving (Generic, Show)
|
deriving (Generic, Show)
|
||||||
|
|
||||||
|
mkDocumentFrom ::
|
||||||
|
forall b repr.
|
||||||
|
Markup repr =>
|
||||||
|
-- | 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 ->
|
||||||
|
IO (Either (MarkupError repr) (Document repr))
|
||||||
|
mkDocumentFrom (Arg k) (Arg f) = runExceptT $ do
|
||||||
|
-- HACK: this looks bad
|
||||||
|
v :: repr <-
|
||||||
|
liftEither
|
||||||
|
=<< ( lift $
|
||||||
|
readDoc @repr @b
|
||||||
|
! #relpath k
|
||||||
|
! #path f
|
||||||
|
)
|
||||||
|
let meta = extractMeta v
|
||||||
|
h <- liftEither $ renderDoc v
|
||||||
|
pure $ Document k v h meta
|
||||||
|
|
||||||
-- | 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.
|
||||||
@ -54,19 +78,24 @@ 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 `parseDoc` 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 ::
|
renderDoc ::
|
||||||
Document repr ->
|
repr ->
|
||||||
Either (MarkupError repr) (Html ())
|
Either (MarkupError repr) (Html ())
|
||||||
|
|
||||||
-- | Convert `MarkupError` to string
|
-- | Convert `MarkupError` to string
|
||||||
|
@ -40,16 +40,15 @@ 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' (MMark.render 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 = Right . MMark.render . _document_val
|
extractMeta = MMark.projectYaml
|
||||||
|
|
||||||
|
renderDoc = Right . MMark.render
|
||||||
|
|
||||||
showMarkupError = toText . M.errorBundlePretty
|
showMarkupError = toText . M.errorBundlePretty
|
||||||
|
|
||||||
|
@ -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,21 +69,21 @@ 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
|
|
||||||
|
extractMeta (Pandoc meta _) = flattenMeta meta
|
||||||
|
|
||||||
renderDoc =
|
renderDoc =
|
||||||
fmap toHtmlRaw
|
fmap toHtmlRaw
|
||||||
. first RibPandocError_PandocError
|
. first RibPandocError_PandocError
|
||||||
. liftEither
|
. liftEither
|
||||||
. render'
|
. render'
|
||||||
. _document_val
|
|
||||||
|
|
||||||
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 s = either (error . showMarkupError @Pandoc) id $ runExcept $ do
|
renderPandoc f s = either (error . show) id $ runExcept $ do
|
||||||
doc <- liftEither $ parseDoc @Pandoc f s
|
doc <- liftEither $ parseDoc @Pandoc f s
|
||||||
liftEither $ renderDoc doc
|
liftEither $ renderDoc doc
|
||||||
|
|
||||||
@ -104,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 ->
|
||||||
@ -192,14 +191,6 @@ detectReader f = do
|
|||||||
-- MonadError instead.
|
-- MonadError instead.
|
||||||
catchInMonadError ef = either (throwError . ef) pure
|
catchInMonadError ef = either (throwError . ef) pure
|
||||||
|
|
||||||
mkDoc :: MonadError PandocError m => Path Rel File -> Pandoc -> m (Document Pandoc)
|
|
||||||
mkDoc f v = do
|
|
||||||
h <- liftEither $ render' v
|
|
||||||
pure $ Document f v h $ 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.
|
||||||
|
@ -91,7 +91,7 @@ readDocMulti pat = do
|
|||||||
need $ toFilePath <$> [input </> f]
|
need $ toFilePath <$> [input </> f]
|
||||||
result <-
|
result <-
|
||||||
liftIO $
|
liftIO $
|
||||||
readDoc
|
mkDocumentFrom
|
||||||
! #relpath f
|
! #relpath f
|
||||||
! #path (input </> f)
|
! #path (input </> f)
|
||||||
case result of
|
case result of
|
||||||
|
Loading…
Reference in New Issue
Block a user