Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type PencilApp = ReaderT Config (ExceptT PencilException IO)
- run :: PencilApp a -> Config -> IO ()
- data Page
- getPageEnv :: Page -> Env
- setPageEnv :: Env -> Page -> Page
- load :: (FilePath -> FilePath) -> FilePath -> PencilApp Page
- withEnv :: Env -> PencilApp a -> PencilApp a
- renderCss :: FilePath -> PencilApp ()
- type Structure = NonEmpty Page
- (<||) :: Page -> Page -> Structure
- (<|) :: Structure -> Page -> Structure
- structure :: Page -> Structure
- data Resource
- loadResource :: (FilePath -> FilePath) -> FilePath -> PencilApp Resource
- loadResources :: (FilePath -> FilePath) -> Bool -> Bool -> FilePath -> PencilApp [Resource]
- passthrough :: FilePath -> PencilApp Resource
- listDir :: Bool -> FilePath -> PencilApp [FilePath]
- class Render a where
- toHtml :: FilePath -> FilePath
- toDir :: FilePath -> FilePath
- toCss :: FilePath -> FilePath
- toExpected :: FilePath -> FilePath
- merge :: Env -> Env -> Env
- insertEnv :: Text -> Value -> Env -> Env
- insertText :: Text -> Text -> Env -> Env
- insertPages :: Text -> [Page] -> Env -> Env
- updateEnvVal :: (Value -> Value) -> Text -> Env -> Env
- sortByVar :: Text -> (Value -> Value -> Ordering) -> [Page] -> [Page]
- filterByVar :: Bool -> Text -> (Value -> Bool) -> [Page] -> [Page]
- groupByElements :: Text -> [Page] -> HashMap Text [Page]
- data Config
- defaultConfig :: Config
- getSourceDir :: Config -> FilePath
- setSourceDir :: FilePath -> Config -> Config
- getOutputDir :: Config -> FilePath
- setOutputDir :: FilePath -> Config -> Config
- getEnv :: Config -> Env
- setEnv :: Env -> Config -> Config
- updateEnv :: (Env -> Env) -> Config -> Config
- getDisplayValue :: Config -> Value -> Text
- setDisplayValue :: (Value -> Text) -> Config -> Config
- getSassOptions :: Config -> SassOptions
- setSassOptions :: SassOptions -> Config -> Config
- getPandocReaderOptions :: Config -> ReaderOptions
- setPandocReaderOptions :: ReaderOptions -> Config -> Config
- getPandocWriterOptions :: Config -> WriterOptions
- setPandocWriterOptions :: WriterOptions -> Config -> Config
- data FileType
- fileType :: FilePath -> FileType
- toExtension :: FileType -> Maybe String
- asks :: MonadReader r m => (r -> a) -> m a
- data PencilException
Getting started
To get started, let's look at this example, which is a very simple website with only a couple of pages. Browse through the site folder to see the source web pages we'll be using. You can run this example by following the instructions found in the README.md.
First, we have layout.html
, which will serve as the layout of all our
pages. Notice that layout.html
contains strings that look like ${title}
and ${body}
. These are variable directives that we'll need to fill values
in for.
index.markdown
is a pretty basic Markdown file, and style.scss
is a
Scss file.
Now let's look inside Main.hs
:
import Pencil config :: Config config = (updateEnv (insertText "title" "My Simple Website") . setSourceDir "examples/Simple/site/" . setOutputDir "examples/Simple/out/") defaultConfig website :: PencilApp () website = do layout <- load toHtml "layout.html" index <- load toHtml "index.markdown" render (layout <|| index) renderCss "style.scss" main :: IO () main = run website config
First, we need to set up a Config
. We start with defaultConfig
, and
modify it slightly, specifying where the source files live, and where we want
the output files to go. We also add a title
variable with the value "My
Simple Website"
into the environment.
An Env
, or environment, is just a mapping of variables to its values. A
variable can hold a string, number, boolean, date, and so forth. Once a
variable is defined, we can use that variable in our web pages via a
variable directive like ${title}
.
Let's now look at the website
function. Note that its type is PencilApp
()
. PencilApp
is the monad transformer that web pages are built under.
Don't worry if you aren't familiar with monad transformers; in simple terms,
PencilApp
is a function that takes a Config
, and does all the source file
loading and web page rendering under the IO
monad. So website
is a
function that is waiting for a Config
. We "give" website
a Config
with
this code, which is the main
function:
run website config
Now let's dissect the website
function itself. The first thing we do is
, which loads our layout file into something
called a load
toHtml "layout.html"Page
. In short, a Page
holds the contents of the file, plus the
environment of that file, plus the final output destination of that file if
it is rendered. The toHtml
function tells load
that you want the output
file to have the .html
extension.
It's important to realize that toHtml
is not telling load
how to load
layout.html
; it's telling it what kind of file you want when you spit it
out. load
itself looks at the file extension to figure out that
layout.html
is an HTML file, and index.markdown
is a Markdown file. So we
use toHtml
when loading index.markdown
because we want the index page to
be rendered as an .html
file.
Now, what about render (layout <|| index)
. What the heck is going on here?
In plain language, you can think of (layout <|| index)
as injecting the
contents of index
into layout
. The way this works is that the contents of
index
is rendered (Markdown is converted to HTML, variable directives are
resolved through the given environment, etc) and then stuffed into a special
body
variable in layout
's environment. When layout
is rendered, the
variable directive ${body}
in layout
is replaced with the contents of
index
.
(layout <|| index)
describes what will happen; it forms a Structure
.
Passing it into render
is what actually generates the web page.
Finally, we have
, which is a helper method to load
and render CSS files in one step.renderCss
"style.scss"
And that's it! If you run this code, it will spit out an index.html
file
and a style.css
file in the examples/Simple/out/
folder.
To learn more, read through the documentation found in this module. To build a blog, look at the Pencil.Blog module.
Templates
Pencil comes with a simple templating engine. Templates allow us to build web pages dynamically using Haskell code. This allows us to build modular components. Templates can be used for things like shared page layouts, navigation and blog post templates.
Pencil templates are regular text files that can contain a preamble and directives.
Preamble
Preambles are YAML-formatted environment variable declarations inside your
source files. They should be declared at the top of the file, and you may
only have one preamble per source file. Example preamble, in the first part
of my-blog-post.markdown
:
<!--PREAMBLE postTitle: "Behind Python's unittest.main()" date: 2010-01-30 tags: - python -->
In the above example, Pencil will intelligently parse the date
value as a
VDateTime
.
Directives
Directives are rendering commands. They are surrounded by ${...}
.
Variables
The simplest directive is the variable directive.
Hello ${name}!
The above template will render the value of the variable name
, which is
expected to be in the environment at render
. If the variable is not found,
Pencil will throw an exception with some debugging information.
If block
The if
directive allows us to render content based off the existence of a
variable in the current environment.
${if(name)} Hello ${name}! ${end}
In this case, we now make sure that name
is available before rendering.
For loop
The for
directive allows us to loop over array type variable. This is
useful for things like rendering a list of blog post titles, and URLs to the
individual blog posts.
<ul> ${for(posts)} <li><a href="${this.url}">${postTitle}</a> - ${date}</li> ${end} </ul>
Assuming that posts
exists in our environment as an array of Value
,
this will render each post's title, publish date, and will link it to
this.url
. Note that inside the for
block, you have access to the current
environment's variables. This is why we're able to simply request
${postTitle}
—it is the current post's postTitle
that will be rendered.
this.url
is a special variable that is automatically inserted for you
inside a loaded Page
. It points to the final file path destination of that
current Page
.
Partials
The partial
directive injects another template file into the current file.
The directives inside the partial are rendered in the same environmental
context as the partial
directive.
Think of partials as just copy-and-pasting snippet from one file to another.
Unlike Structure
s, partials cannot define environment variables.
In the example below, the first partial
is rendered with the current
environment. The partial
inside the for
loop receives the same
environemnt as any other snippet inside the loop, and thus has access to
the environment inside each post.
${partial("partials/nav-bar.html")} ${for(posts)} ${partial("partials/nav-bar.html")} ${end}
type PencilApp = ReaderT Config (ExceptT PencilException IO) Source #
The main monad transformer stack for a Pencil application.
This unrolls to:
PencilApp a = Config -> IO (Except PencilException a)
The ExceptT
monad allows us to catch "checked" exceptions; errors that we
know how to handle, in PencilException. Note that Unknown "unchecked"
exceptions can still go through IO.
run :: PencilApp a -> Config -> IO () Source #
Run the Pencil app.
Note that this can throw a fatal exception.
Pages, Structures and Resources
Page
, Structure
and Resource
are the "big three" data types you need to
know to effectively use Pencil.
The Page is an important data type in Pencil. It contains the parsed
template of a file (e.g. of Markdown or HTML files). It may have template
directives (e.g. ${body}
) that has not yet been rendered, and an
environment loaded from the preamble section of the file. A Page also
contains pageFilePath
, which is the output file path.
load :: (FilePath -> FilePath) -> FilePath -> PencilApp Page Source #
Loads a file into a Page, rendering the file (as determined by the file
extension) into the proper output format (e.g. Markdown rendered to
HTML, SCSS to CSS). Parses the template directives and preamble variables
into its environment. The Page'
s pageFilePath
is determined by the given
function, which expects the original file path, and returns the designated file
path.
The Page's designated file path is calculated and stored in the Page's
environment in the variable this.url
. This allows the template to use
${this.url}
to refer to the designated file path.
Example:
-- Loads index.markdown with the designated file path of index.html
load toHtml
"index.markdown"
-- Keep the file path as-is
load id "about.html"
withEnv :: Env -> PencilApp a -> PencilApp a Source #
Runs the computation with the given environment. This is useful when you
want to render a Page
or Structure
with a modified environment.
withEnv (insertText
"newvar" "newval" env) (render
page)
renderCss :: FilePath -> PencilApp () Source #
Loads and renders file as CSS.
-- Load, convert and render as style.css. renderCss "style.sass"
type Structure = NonEmpty Page Source #
A Structure
is a list of Page
s, defining a nesting order. Think of them
like Russian nesting dolls.
The first element defines the outer-most container, and subsequent elements
are inside the previous element.
You commonly use Structure
s to insert a Page
containing content (e.g. a blog
post) into a container (e.g. a layout shared across all your web pages).
Build structures using structure
, <||
and <|
.
layout <- load toHtml "layout.html" index <- load toHtml "index.markdown" about <- load toHtml "about.markdown" render (layout <|| index) render (layout <|| about)
In the example above we load a layout Page
, which can be an HTML page
defining the outer structures like <html></html>
. Assuming layout.html
has the template directive ${body}
(note that body
is a special variable
generated during structure-building), layout <|| index
tells render
that you want the rendered body of index
to be injected into
the ${body}
directive inside of layout
.
Structure
s also control the closure of variables. Variables defined in a
Page
s are accessible both by Page
s above and below. This allows inner
Page
s to define variables like the blog post title, which may be used in
the outer Page
to set the <title>
tag.
In this way, Structure
allows efficient Page
reuse. See the private
function apply
to learn more about how Structure
s are
evaluated.
Note that this differs than the ${partial(...)}
directive, which has no
such variable closures. The partial directive is much simpler—think of them
as copy-and-pasting snippets from one file to another. The partial has has
the same environment as the parent context.
(<||) :: Page -> Page -> Structure Source #
Creates a new Structure
from two Page
s.
layout <- load toHtml "layout.html" index <- load toHtml "index.markdown" render (layout <|| index)
(<|) :: Structure -> Page -> Structure Source #
Pushes Page
into Structure
.
layout <- load toHtml "layout.html" blogLayout <- load toHtml "blog-layout.html" blogPost <- load toHtml "myblogpost.markdown" render (layout <|| blogLayout <| blogPost)
Use Resource
to load and render files that don't need any manipulation
other than conversion (e.g. Sass to CSS), or for static files that you want
to copy as-is (e.g. binary files like images, or text files that require no
other processing).
Use passthrough
, loadResource
and loadResources
to build a Resource
from a file.
In the example below, robots.txt
and everything in the images/
directory
will be rendered as-is.
passthrough "robots.txt" >> render loadResources id True True "images/" >> render
loadResource :: (FilePath -> FilePath) -> FilePath -> PencilApp Resource Source #
Loads a file as a Resource
. Use this for binary files (e.g. images) and
for files without template directives. Regular files are still converted to
their web page formats (e.g. Markdown to HTML, SASS to CSS).
-- Loads and renders the image as-is. Underneath the hood -- this is just a file copy. loadResource id "images/profile.jpg" >> render -- Loads and renders to about.index loadResource toHtml "about.markdown" >> render
:: (FilePath -> FilePath) | |
-> Bool | Recursive if |
-> Bool | Handle as pass-throughs (file copy) if |
-> FilePath | |
-> PencilApp [Resource] |
Loads file in given directory as Resource
s.
passthrough :: FilePath -> PencilApp Resource Source #
Loads file as a pass-through. There is no content conversion, and template directives are ignored. In essence this is a file copy.
passthrough "robots.txt" >> render
Lists files in given directory. The file paths returned is prefixed with the given directory.
To render something is to create the output web pages, rendering template directives into their final form using the current environment.
toHtml :: FilePath -> FilePath Source #
Replaces the file path's extension with .html
.
load
toHtml "about.markdown"
toCss :: FilePath -> FilePath Source #
Replaces the file path's extension with .css
.
load
toCss "style.sass"
toExpected :: FilePath -> FilePath Source #
Converts file path into the expected extensions. This means .markdown
become .html
, .sass
becomes .css
, and so forth. See extensionMap
for
conversion table.
-- Load everything inside the "assets/" folder, renaming converted files as
-- expected, and leaving everything else alone.
loadResources
toExpected True True "assets/"
Environment Manipulation
merge :: Env -> Env -> Env Source #
Merges two Env
s together, biased towards the left-hand Env
on duplicates.
Insert Value
into the given Env
.
Insert text into the given Env
.
env <- asks getEnv insertText "title" "My Awesome Website" env
Insert Page
s into the given Env
.
posts <-loadBlogPosts
"blog/" env <- asksgetEnv
insertPages "posts" posts env
Modify a variable in the given environment.
:: Text | Environment variable name. |
-> (Value -> Value -> Ordering) | Ordering function to compare Value against. If the variable is not in the Env, the Page will be placed at the bottom of the order. |
-> [Page] | |
-> [Page] |
Sort given Page
s by the specified ordering function.
:: Bool | If true, include pages without the specified variable. |
-> Text | Environment variable name. |
-> (Value -> Bool) | |
-> [Page] | |
-> [Page] |
Filter by a variable's value in the environment.
Given a variable (whose value is assumed to be an array of VText) and list of pages, group the pages by the VText found in the variable.
For example, say each Page has a variable "tags" that is a list of tags. The first Page has a "tags" variable that is an VArray [VText "a"], and the second Page has a "tags" variable that is an VArray [VText "a", VText "b"]. The final output would be a map fromList [("a", [page1, page2]), ("b", [page2])].
Configuration
The main Config
needed to build your website. Your app's Config
is
passed into the PencilApp
monad transformer.
Use defaultConfig
as a starting point, along with the config-modification
helpers such as setSourceDir
.
defaultConfig :: Config Source #
This default Config
gives you everything you need to start.
Default values:
Config {configSourceDir
= "site/" ,configOutputDir
= "out/" ,configEnv
= HashMap.empty ,configDisplayValue
=toText
,configSassOptions
= Text.Sass.Options.defaultSassOptions ,configPandocReaderOptions
= Text.Pandoc.def { Text.Pandoc.readerExtensions = Text.Pandoc.Extensions.getDefaultExtensions "markdown" } ,configPandocWriterOptions
= Text.Pandoc.def { Text.Pandoc.writerHighlightStyle = Just Text.Pandoc.Highlighting.monochrome } , 'configDisplayValue =toText
}
getSourceDir :: Config -> FilePath Source #
The directory path of your web page source files.
setSourceDir :: FilePath -> Config -> Config Source #
Sets the source directory of your web page source files.
getOutputDir :: Config -> FilePath Source #
The directory path of your rendered web pages.
setOutputDir :: FilePath -> Config -> Config Source #
Sets the output directory of your rendered web pages.
getEnv :: Config -> Env Source #
The environment of the Config
, which is what the PencilApp
monad
transformer uses. This is where variables are set for rendering template
directives.
setDisplayValue :: (Value -> Text) -> Config -> Config Source #
Sets the function that renders Value
to text. Overwrite this with your
own function if you would like to change how certain Value
s are rendered
(e.g. VDateTime
).
myRender :: Value -> T.Text myRender (VDateTime
dt) =pack
$formatTime
defaultTimeLocale
"%e %B %Y" dt myRender t =toText
t ... setDisplayValue myRender config
In the above example, we change the VDateTime
rendering to show 25
December 2017
. Leave everything else unchanged.
getSassOptions :: Config -> SassOptions Source #
The SassOptions
for rendering Sass/Scss files.
setSassOptions :: SassOptions -> Config -> Config Source #
Sets the SassOptions
.
getPandocReaderOptions :: Config -> ReaderOptions Source #
The ReaderOptions
for reading files that use Pandoc.
Supported formats by Pencil are: Markdown.
setPandocReaderOptions :: ReaderOptions -> Config -> Config Source #
Sets the ReaderOptions
. For example, you may want to enable
some Pandoc extensions like Ext_literate_haskell
:
setPandocReaderOptions
(Text.Pandoc.def { readerExtensions
= extensionsFromList [Ext_literate_haskell] })
config
getPandocWriterOptions :: Config -> WriterOptions Source #
The WriterOptions
for rendering files that use Pandoc.
Supported formats by Pencil are: Markdown.
setPandocWriterOptions :: WriterOptions -> Config -> Config Source #
Sets the WriterOptions
.
Utils and re-exports
Enum for file types that can be parsed and converted by Pencil.
Instances
Eq FileType Source # | |
Generic FileType Source # | |
Hashable FileType Source # |
|
Defined in Pencil.Internal.Pencil | |
type Rep FileType Source # | |
Defined in Pencil.Internal.Pencil type Rep FileType = D1 (MetaData "FileType" "Pencil.Internal.Pencil" "pencil-0.1.3-inplace" False) ((C1 (MetaCons "Html" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Markdown" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Css" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Sass" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Other" PrefixI False) (U1 :: * -> *)))) |
toExtension :: FileType -> Maybe String Source #
Converts a FileType
into its converted webpage extension, if Pencil would
convert it (e.g. Markdown to HTML).
>>>
toExtension Markdown
Just "html"
:: MonadReader r m | |
=> (r -> a) | The selector function to apply to the environment. |
-> m a |
Retrieves a function of the current environment.
Error handling
data PencilException Source #
Known Pencil errors that we know how to either recover from or quit gracefully.
Instances
Show PencilException Source # | |
Defined in Pencil.Internal.Pencil showsPrec :: Int -> PencilException -> ShowS # show :: PencilException -> String # showList :: [PencilException] -> ShowS # |