Skip to content

Commit

Permalink
Release 0.7 (#111)
Browse files Browse the repository at this point in the history
* Prep release

* Update README example
  • Loading branch information
srid authored Mar 3, 2020
1 parent 6148df9 commit 224161a
Show file tree
Hide file tree
Showing 7 changed files with 92 additions and 44 deletions.
2 changes: 1 addition & 1 deletion CHANGELOG.md
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
# Change Log for rib

## 0.7.0.0 (UNRELEASED)
## 0.7.0.0

- Dependency upgrades
- mmark: 0.0.7.2
Expand Down
2 changes: 1 addition & 1 deletion DEVELOPMENT.md
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ nix-shell --arg rib ../rib --run 'ghcid -T main'

1. Create a `release-x.y` branch
1. Finalize ChangeLog.md
1. Run `cabal haddock` and sanity check the haddocks
1. Run `nix-shell --run 'cabal haddock'` and sanity check the haddocks
1. Commit all changes, and push a release PR.
1. Generated sdist using `cabal sdist`
1. [Upload a package candidate](https://hackage.haskell.org/packages/candidates/upload)
Expand Down
115 changes: 77 additions & 38 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@
[![built with nix](https://builtwithnix.org/badge.svg)](https://builtwithnix.org)
[![Zulip chat](https://img.shields.io/badge/zulip-join_chat-brightgreen.svg)](https://funprog.zulipchat.com/#narrow/stream/218047-Rib)

Rib is a Haskell library for writing your own **static site generator**.
Rib is a Haskell **static site generator** that aims to reuse existing libraries instead of reinventing the wheel.

How does it compare to Hakyll?

Expand Down Expand Up @@ -41,68 +41,107 @@ Here is how your code may look like if you were to generate your static site
using Rib:

```haskell
-- | This will be our type representing generated pages.
-- | Route corresponding to each generated static page.
--
-- Each `Source` specifies the parser type to use. Rib provides `MMark` and
-- `Pandoc`; but you may define your own as well.
data Page
= Page_Index [Source MMark]
| Page_Single (Source MMark)
-- The `a` parameter specifies the data (typically Markdown document) used to
-- generated the final page text.
data Route a where
Route_Index :: Route ()
Route_Article :: ArticleRoute a -> Route a

-- | You may even have sub routes.
data ArticleRoute a where
ArticleRoute_Index :: ArticleRoute [(Route MMark, MMark)]
ArticleRoute_Article :: Path Rel File -> ArticleRoute MMark

-- | The `IsRoute` instance allows us to determine the target .html path for
-- each route. This affects what `routeUrl` will return.
instance IsRoute Route where
routeFile = \case
Route_Index ->
pure [relfile|index.html|]
Route_Article r ->
fmap ([reldir|article|] </>) $ case r of
ArticleRoute_Article srcPath ->
replaceExtension ".html" srcPath
ArticleRoute_Index ->
pure [relfile|index.html|]

-- | The "Config" type generated from the Dhall type.
--
-- Use `Rib.Parser.Dhall` to parse it (see below).
makeHaskellTypes
[ SingleConstructor "Config" "Config" "./src-dhall/Config.dhall"
]

-- | Main entry point to our generator.
--
-- `Rib.run` handles CLI arguments, and takes three parameters here.
--
-- 1. Directory `a`, from which static files will be read.
-- 2. Directory `b`, under which target files will be generated.
-- 1. Directory `content`, from which static files will be read.
-- 2. Directory `dest`, under which target files will be generated.
-- 3. Shake action to run.
--
-- In the shake build action you would expect to use the utility functions
-- In the shake action you would expect to use the utility functions
-- provided by Rib to do the actual generation of your static site.
main :: IO ()
main = Rib.run [reldir|a|] [reldir|b|] generateSite
main = Rib.run [reldir|content|] [reldir|dest|] generateSite

-- | Shake action for generating the static site
generateSite :: Action ()
generateSite = do
-- Copy over the static files
Rib.buildStaticFiles [[relfile|static/**|]]
-- Read the site config
config :: Config <-
Dhall.parse
[[relfile|src-dhall/Config.dhall|]]
[relfile|config.dhall|]
let writeHtmlRoute :: Route a -> a -> Action ()
writeHtmlRoute r = writeRoute r . Lucid.renderText . renderPage config r
-- Build individual sources, generating .html for each.
-- The function `buildHtmlMulti` takes the following arguments:
-- - Function that will parse the file (here we use mmark)
-- - File patterns to build
-- - Function that will generate the HTML (see below)
srcs <-
Rib.forEvery [[relfile|*.md|]] $ \srcPath ->
Rib.buildHtml srcPath MMark.parse $ renderPage . Page_Single
-- Write an index.html linking to the aforementioned files.
Rib.writeHtml [relfile|index.html|] $
renderPage (Page_Index srcs)
articles <-
Rib.forEvery [[relfile|*.md|]] $ \srcPath -> do
let r = Route_Article $ ArticleRoute_Article srcPath
doc <- MMark.parse srcPath
writeHtmlRoute r doc
pure (r, doc)
writeHtmlRoute (Route_Article ArticleRoute_Index) articles
writeHtmlRoute Route_Index ()

-- | Define your site HTML here
renderPage :: Page -> Html ()
renderPage page = with html_ [lang_ "en"] $ do
renderPage :: Config -> Route a -> a -> Html ()
renderPage config route val = with html_ [lang_ "en"] $ do
head_ $ do
meta_ [httpEquiv_ "Content-Type", content_ "text/html; charset=utf-8"]
title_ $ case page of
Page_Index _ -> "My website!"
Page_Single src -> toHtml $ title $ getMeta src
title_ $ routeTitle
style_ [type_ "text/css"] $ C.render pageStyle
body_ $ do
with div_ [id_ "thesite"] $ do
with div_ [class_ "header"] $
with a_ [href_ "/"] "Back to Home"
case page of
Page_Index srcs -> div_ $ forM_ srcs $ \src ->
with li_ [class_ "pages"] $ do
let meta = getMeta src
b_ $ with a_ [href_ (Rib.sourceUrl src)] $ toHtml $ title meta
maybe mempty renderMarkdown $ description meta
Page_Single src ->
h1_ routeTitle
case route of
Route_Index ->
p_ $ do
"This site is work in progress. Meanwhile visit the "
with a_ [href_ $ routeUrl $ Route_Article ArticleRoute_Index] "articles"
" page."
Route_Article ArticleRoute_Index ->
div_ $ forM_ val $ \(r, src) ->
with li_ [class_ "pages"] $ do
let meta = getMeta src
b_ $ with a_ [href_ (Rib.routeUrl r)] $ toHtml $ title meta
maybe mempty renderMarkdown $ description meta
Route_Article (ArticleRoute_Article _) ->
with article_ [class_ "post"] $ do
h1_ $ toHtml $ title $ getMeta src
MMark.render $ Rib.sourceVal src
MMark.render val
where
routeTitle :: Html ()
routeTitle = case route of
Route_Index -> toHtml $ siteTitle config
Route_Article (ArticleRoute_Article _) -> toHtml $ title $ getMeta val
Route_Article ArticleRoute_Index -> "Articles"
renderMarkdown =
MMark.render . either (error . T.unpack) id . MMark.parsePure "<none>"

Expand All @@ -128,15 +167,15 @@ data SrcMeta
deriving (Show, Eq, Generic, FromJSON)

-- | Get metadata from Markdown's YAML block
getMeta :: Source MMark -> SrcMeta
getMeta src = case MMark.projectYaml (Rib.sourceVal src) of
getMeta :: MMark -> SrcMeta
getMeta src = case MMark.projectYaml src of
Nothing -> error "No YAML metadata"
Just val -> case fromJSON val of
Aeson.Error e -> error $ "JSON error: " <> e
Aeson.Success v -> v
```

(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/src/Main.hs) at rib-sample)

## Getting Started

Expand Down
2 changes: 1 addition & 1 deletion rib.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ bug-reports: https://github.com/srid/rib/issues
synopsis:
Static site generator using Shake
description:
Haskell library for writing your own static site generator
Haskell static site generator that aims to reuse existing libraries instead of reinventing the wheel
category: Web
build-type: Simple
extra-source-files:
Expand Down
2 changes: 1 addition & 1 deletion src/Rib/Extra/CSS.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}

-- | Extra CSS functionality
-- | Some commonly useful CSS styles
module Rib.Extra.CSS where

import Clay
Expand Down
7 changes: 5 additions & 2 deletions src/Rib/Parser/Dhall.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}

-- | Parsing Dhall files
-- | Parser for Dhall files.
module Rib.Parser.Dhall
( -- * Parsing
parse,
Expand All @@ -17,11 +17,14 @@ import Relude
import Rib.Shake (ribInputDir)
import System.Directory

-- | Parse Dhall files
-- | Parse a Dhall file as Haskell type.
--
-- Use `Dhall.TH.makeHaskellTypes` to create the Haskell type first.
parse ::
FromDhall a =>
-- | Dependent .dhall files, which must trigger a rebuild
[Path Rel File] ->
-- | The Dhall file to parse. Relative to `ribInputDir`.
Path Rel File ->
Action a
parse (map toFilePath -> deps) f = do
Expand Down
6 changes: 6 additions & 0 deletions src/Rib/Route.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}

-- | Type-safe routes
module Rib.Route
( IsRoute (..),
routeUrl,
Expand All @@ -26,6 +27,8 @@ import Rib.Shake (writeFileCached)
--
-- The GADT type parameter represents the data used to render that particular route.
class IsRoute (r :: Type -> Type) where
-- | Return the filepath (relative `Rib.Shake.ribInputDir`) where the
-- generated content for this route should be written.
routeFile :: MonadThrow m => r a -> m (Path Rel File)

data UrlType = Relative | Absolute
Expand All @@ -37,9 +40,11 @@ path2Url fp = toText . toFilePath . \case
Absolute ->
[absdir|/|] </> fp

-- | The absolute URL to this route (relative to site root)
routeUrl :: IsRoute r => r a -> Text
routeUrl = routeUrl' Absolute

-- | The relative URL to this route
routeUrlRel :: IsRoute r => r a -> Text
routeUrlRel = routeUrl' Relative

Expand All @@ -52,6 +57,7 @@ routeUrl' urlType = stripIndexHtml . flip path2Url urlType . either (error . toT
then T.dropEnd (T.length $ "index.html") s
else s

-- | Write the content `s` to the file corresponding to the given route.
writeRoute :: (IsRoute r, ToString s) => r a -> s -> Action ()
writeRoute r content = do
fp <- liftIO $ routeFile r
Expand Down

0 comments on commit 224161a

Please sign in to comment.