diff --git a/CHANGELOG.md b/CHANGELOG.md index 72c76b7..2222f7b 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -1,17 +1,18 @@ # Change Log for rib -## 0.6.0.0 - UNRELEASED +## 0.6.0.0 - Advance nixpkgs; require Shake >=0.18.4 -- Significant API simplication: no more type class! - - Allows user to specify their own markup parser as a Haskell function - - Dropped namings "Document" and "Markup" in favour of "Source" +- Major API simplication: no more type class! + - Allow user to specify their own source parser as a Haskell function + - Removed types `Document` and `Markup` in favour of `Source` - Expose `ribInputDir` and `ribOutputDir` for use in custom Shake actions - Bug fixes: - #63: create intermediate directories when generating post HTML - #70: Don't crash on Shake errors - Fix unnecessary rebuild of all files when only one file changed - #66: Use caching (via Shake's `cacheActionWith`), to avoid writing HTML to disk until it has changed. + ## 0.5.0.0 This release comes with a major API refactor. Key changes: diff --git a/src/Rib/App.hs b/src/Rib/App.hs index 3b4341b..74750a5 100644 --- a/src/Rib/App.hs +++ b/src/Rib/App.hs @@ -5,7 +5,7 @@ -- | CLI interface for Rib. -- --- Typically you would call `Rib.App.run` passing your Shake build action. +-- Mostly you would only need `Rib.App.run`, passing it your Shake build action. module Rib.App ( App (..), run, diff --git a/src/Rib/Parser/MMark.hs b/src/Rib/Parser/MMark.hs index 7417508..8e48858 100644 --- a/src/Rib/Parser/MMark.hs +++ b/src/Rib/Parser/MMark.hs @@ -8,6 +8,7 @@ {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} +-- | Parsing Markdown using the mmark parser. module Rib.Parser.MMark ( -- * Parsing parse, @@ -44,7 +45,7 @@ render = MMark.render -- | Pure version of `parse` parsePure :: - -- | Filepath corresponding to the text to be parsed (used in parse errors) + -- | Filepath corresponding to the text to be parsed (used only in parse errors) FilePath -> -- | Text to be parsed Text -> diff --git a/src/Rib/Parser/Pandoc.hs b/src/Rib/Parser/Pandoc.hs index 824740c..706e2b6 100644 --- a/src/Rib/Parser/Pandoc.hs +++ b/src/Rib/Parser/Pandoc.hs @@ -48,7 +48,7 @@ parsePure textReader s = first show $ runExcept $ do runPure' $ textReader readerSettings s --- `SourceReader` for parsing a lightweight markup language using Pandoc +-- | `SourceReader` for parsing a lightweight markup language using Pandoc parse :: -- | The pandoc text reader function to use, eg: `readMarkdown` (ReaderOptions -> Text -> PandocIO Pandoc) -> @@ -69,6 +69,7 @@ render doc = $ fmap toHtmlRaw $ writeHtml5String writerSettings doc +-- | Extract the Pandoc metadata as JSON value extractMeta :: Pandoc -> Maybe (Either Text Value) extractMeta (Pandoc meta _) = flattenMeta meta diff --git a/src/Rib/Shake.hs b/src/Rib/Shake.hs index ae35234..7e9613b 100644 --- a/src/Rib/Shake.hs +++ b/src/Rib/Shake.hs @@ -6,15 +6,17 @@ {-# LANGUAGE ViewPatterns #-} -- | Combinators for working with Shake. --- --- See the source of `Rib.Simple.buildAction` for example usage. module Rib.Shake ( -- * Basic helpers - readSource, buildStaticFiles, buildHtmlMulti, buildHtml, buildHtml_, + + -- * Reading only + readSource, + + -- * Writing only writeHtml, -- * Misc @@ -34,6 +36,7 @@ import Path.IO import Relude import Rib.Source +-- | RibSettings is initialized with the values passed to `Rib.App.run` data RibSettings = RibSettings { _ribSettings_inputDir :: Path Rel Dir, @@ -41,6 +44,7 @@ data RibSettings } deriving (Typeable) +-- | Get rib settings from a shake Action monad. ribSettings :: Action RibSettings ribSettings = getShakeExtra >>= \case Just v -> pure v @@ -61,7 +65,7 @@ ribOutputDir = do liftIO $ createDirIfMissing True output return output --- | Shake action to copy static files as is +-- | Shake action to copy static files as is. buildStaticFiles :: [Path Rel File] -> Action () buildStaticFiles staticFilePatterns = do input <- ribInputDir @@ -77,7 +81,7 @@ buildStaticFiles staticFilePatterns = do readSource :: -- | How to parse the source SourceReader repr -> - -- | Path to the source file relative to `ribInputDir` + -- | Path to the source file (relative to `ribInputDir`) Path Rel File -> Action repr readSource sourceReader k = do @@ -96,9 +100,9 @@ readSource sourceReader k = do -- | Convert the given pattern of source files into their HTML. buildHtmlMulti :: - -- | How to parse the source + -- | How to parse the source file SourceReader repr -> - -- | Source file patterns + -- | Source file patterns (relative to `ribInputDir`) [Path Rel File] -> -- | How to render the given source to HTML (Source repr -> Html ()) -> @@ -116,8 +120,9 @@ buildHtmlMulti parser pats r = do -- Also explicitly takes the output file path. buildHtml :: SourceReader repr -> - -- | Path to the HTML file, relative to `ribOutputDir` + -- | Path to the output HTML file (relative to `ribOutputDir`) Path Rel File -> + -- | Path to the source file (relative to `ribInputDir`) Path Rel File -> (Source repr -> Html ()) -> Action (Source repr) @@ -126,6 +131,7 @@ buildHtml parser outfile k r = do writeHtml outfile $ r src pure src +-- | Like `buildHtml` but discards its result. buildHtml_ :: SourceReader repr -> Path Rel File -> diff --git a/src/Rib/Source.hs b/src/Rib/Source.hs index 0439a66..a2c3376 100644 --- a/src/Rib/Source.hs +++ b/src/Rib/Source.hs @@ -14,8 +14,8 @@ module Rib.Source -- * Source properties sourcePath, - sourceVal, sourceUrl, + sourceVal, ) where @@ -27,15 +27,14 @@ import Relude -- | A source file on disk data Source repr = Source - { -- | Path to the source; relative to `ribInputDir` - _source_path :: Path Rel File, - -- | Path to the generated HTML file; relative to `ribOutputDir` + { _source_path :: Path Rel File, + -- | Path to the generated HTML file (relative to `Rib.Shake.ribOutputDir`) _source_builtPath :: Path Rel File, - -- | Parsed representation of the source. _source_val :: repr } deriving (Generic, Functor) +-- | Path to the source file (relative to `Rib.Shake.ribInputDir`) sourcePath :: Source repr -> Path Rel File sourcePath = _source_path @@ -49,6 +48,7 @@ sourceUrl = stripIndexHtml . relPathToUrl . _source_builtPath then T.dropEnd (T.length $ "index.html") s else s +-- | Parsed representation of the source. sourceVal :: Source repr -> repr sourceVal = _source_val