pencil-1.0.0: Static site generator

Safe HaskellNone
LanguageHaskell2010

Pencil.Content

Contents

Description

Load, compose and render content.

Synopsis

Page

data Page Source #

The Page is an important data type in Pencil.

Source files like Markdown and HTML are loaded (e.g. via load) as a Page. A page contains the contents of the file, their un-evaluated template directives (e.g. ${body}), the variables defined in the preamble, and the destination file path.

The contents may be in its converted form. load will convert Markdown to HTML, for example.

Pages can be combined together into a Structure, or inserted into the environment (see insertPages). But at the end of the day, even a structure is converted back into a page on render. This is because it is the page that is finally rendered into an actual web page when you run your program.

Instances
Eq Page Source # 
Instance details

Defined in Pencil.Content.Internal

Methods

(==) :: Page -> Page -> Bool #

(/=) :: Page -> Page -> Bool #

Show Page Source # 
Instance details

Defined in Pencil.Content.Internal

Methods

showsPrec :: Int -> Page -> ShowS #

show :: Page -> String #

showList :: [Page] -> ShowS #

HasFilePath Page Source # 
Instance details

Defined in Pencil.Content.Internal

Render Page Source # 
Instance details

Defined in Pencil.Content

Methods

render :: Page -> PencilApp () Source #

load :: FilePath -> PencilApp Page Source #

Loads a file as 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.

This loads index.markdown with the destination file path set to index.html:

load "index.markdown"

Because this is already an HTML file, the file path is kept as about.html:

load "about.html"

Using rename and toDir, the destination file path becomes pages/about/index.html:

render $ rename toDir <$> load "pages/about.markdown"

load' :: FilePath -> PencilApp Page Source #

Like load, loads a file as a page. Unlike load, the source file path is used as the destination file path (i.e. the extension name is not changed).

loadDir Source #

Arguments

:: Bool

If True, recursively load files in the directory

-> FilePath 
-> PencilApp [Page] 

A version of load for directories.

layout <- load "layout.html"
tutorials <- loadDir False "tutorials/"
render $ fmap ((layout <||) . rename toDir) tutorials

loadDir' Source #

Arguments

:: Bool

Recursive if true

-> FilePath 
-> PencilApp [Page] 

A version of load' for directories. Loads the files in the specified directory as pages. Keeps the original file path.

tutorials <- loadDir' False "tutorials/"
render $ fmap ((layout <||) . rename toDir) pages

loadAndRender :: FilePath -> PencilApp () Source #

Loads and renders file, converting content if it's convertible (e.g. Markdown to HTML). The final file path is the "default conversion", if Pencil knows how to convert the file (e.g. .markdown to .html). Otherwise, the same file name is kept (e.g. .txt).

Load style.sass, convert to CSS, and render as style.css:

loadAndRender "style.sass"

Load, convert and render everything in the assets/ folder. Binary files are copied as-is without any further processing:

loadAndRender "assets/"

rename :: HasFilePath a => (FilePath -> FilePath) -> a -> a Source #

Transforms the file path.

about <- load "about.htm"
render $ struct (rename toHtml about)

to :: HasFilePath a => FilePath -> a -> a Source #

Sets the target file path to the specified file path. If the given file path is a directory, the file name set to index.html. If the file path is a file name, then the file is renamed.

Move stuff/about.html to about/blah.html on render:

about <- to "about/blah.html" <$> load "stuff/about.htm"

Convert the destination file path to about/index.html:

about <- to "about/" <$> load "stuff/about.htm"
render about

Equivalent to the above example:

about <- load "stuff/about.htm"
render $ to "about/" about

move :: HasFilePath a => FilePath -> a -> a Source #

Moves the target file path to the specified file path. Behaves similar to the UNIX mv command: if the given file path is a directory, the file name is kept the same. If the file path is a file name, then the file is renamed.

Move assets/style.css to stylesheets/style.css:

move "stylesheets/" <$> load "assets/style.css"

Move assets/style.css to stylesheets/base.css.

move "stylesheets/base.css" <$> load "assets/style.css"

useFilePath :: Page -> Page Source #

Sets this Page as the designated final FilePath.

This is useful when you are building a Structure but don't want the file path of the last Page in the structure to be the destination file path on render.

The Pages and Structures guide describes this in detail.

a <- load "a.html"
b <- load "b.html"
c <- load "c.html"

-- Rendered file path is "c.html"
render $ a <|| b <| c

-- Rendered file path is "b.html"
render $ a <|| useFilePath b <| c

escapeXml :: Page -> Page Source #

Sets this Page to render with escaped XML/HTML tags.

This is useful when you are building an RSS feed, and you need the contents of each item in the feed to HTML-escaped.

rss <- load "rss.xml"
item1 <- load "item1.html"

render $ rss <|| escapeXml item1

getPageEnv :: Page -> Env Source #

Gets the Env of a Page.

setPageEnv :: Env -> Page -> Page Source #

Sets the Env of a Page.

filterByVar Source #

Arguments

:: Bool

If true, include pages without the specified variable.

-> Text

Environment variable name.

-> (Value -> Bool) 
-> [Page] 
-> [Page] 

Filters pages by a variable's value in the environment.

sortByVar Source #

Arguments

:: 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] 

Sorts pages by an ordering function.

groupByElements Source #

Arguments

:: Text

Environment variable name.

-> [Page] 
-> HashMap Text [Page] 

Given a variable (whose value is assumed to be an array of VText) and list of pages, groups 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])].

insertPages Source #

Arguments

:: Text

Environment variable name.

-> [Page]

Pages to insert.

-> Env

Environment to modify.

-> PencilApp Env 

Inserts pages into the environment. The pages are evaluated and applied before insertion.

posts <- loadPosts "blog/"
env <- asks getEnv
env' <- insertPages "posts" posts env

Structure

data Structure Source #

A Structure is a list of Pages, 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 Structures 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 struct, <|| and <|.

layout <- load "layout.html"
index <- load "index.markdown"
about <- load "about.markdown"
render (layout <|| index)
render (layout <|| about)

In the example above we load a layout page, which defines the outer HTML structure like <html></html>. We then "push" the index page and the about page into the layout.

When we render layout <|| index, the contents of the index (and about) page is injected into the layout page through the variable ${body}. So layout.html must use ${body} somewhere in its own body.

Structures also control the closure of variables. Variables defined in a page are accessible both by pages above and below. This allows inner pages to define variables like the blog post title, which may be used in the outer page to, say, set the <title> tag.

In this way, structures allows efficient page reuse. See the private function apply to learn more about how structures are evaluated.

The Default File Path Rule. When a structure is rendered, the last non-collection page in the structure is used as the destination file path. You can select a different page via useFilePath.

The Pages and Structures guide also describes structures in detail.

Note that structures differ from 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. A partial has the same environment as the context in which the partial directive appears.

struct :: Page -> Structure Source #

Converts a Page into a Structure. This is a "singleton" structure.

(<||) :: Page -> Page -> Structure Source #

Creates a new structure from two pages. Pronounced "smash".

layout <- load "layout.html"
index <- load "index.markdown"
render (layout <|| index)

(<|) :: Structure -> Page -> Structure Source #

Pushes Page into Structure. Pronounced "push".

layout <- load "layout.html"
blogLayout <- load "blog-layout.html"
blogPost <- load "myblogpost.markdown"
render (layout <|| blogLayout <| blogPost)

(<<|) :: Structure -> Node -> Structure Source #

Pushes Node into the Structure. Usually used in conjunction with coll.

blogLayout <- load "blog-layout.html"
blogPosts <- loadPosts "posts/"
render (struct blogLayout <<| coll "posts" blogPosts)

coll :: Text -> [Page] -> Node Source #

Creates a collection Node. Usually used in conjunction with <<|.

Resource

data Resource Source #

Resource is used to copy static binary files to the destination, and to load and render files that just needs conversion without template directives or structures.

This is how Pencil handles files like images, compiled JavaScript, or text files that require only a straight-forward conversion.

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
passthrough "images/" >>= render
Instances
HasFilePath Resource Source # 
Instance details

Defined in Pencil.Content.Internal

Render Resource Source # 
Instance details

Defined in Pencil.Content

Methods

render :: Resource -> PencilApp () Source #

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

render (move "images/profile.jpg" <$> passthrough "images/myProfile.jpg")

loadResource :: FilePath -> PencilApp Resource Source #

Loads a file as a Resource. Use this for binary files (e.g. images) and for files without template directives that may still need conversion (e.g. Markdown to HTML, SASS to CSS).

Generally, you can just use loadAndRender instead of this method.

Loads and renders the image as-is. Underneath the hood this is just a file copy:

loadResource "images/profile.jpg" >>= render

Loads and renders to about.html:

loadResource "about.markdown" >>= render

loadResources Source #

Arguments

:: Bool

Recursive if True.

-> Bool

Handle as pass-throughs (file copy) if True.

-> FilePath 
-> PencilApp [Resource] 

Loads file in given directory as Resources.

Generally, you can just use loadAndRender instead of this method.

Load everything inside the assets/ folder, renaming converted files as expected (e.g. SCSS to CSS):

loadResources True True "assets/"

Render

class Render a where Source #

To render something is to create the output web pages, evaluating template directives into their final form using the current environment.

Methods

render :: a -> PencilApp () Source #

Renders a as web page(s).

Instances
Render Resource Source # 
Instance details

Defined in Pencil.Content

Methods

render :: Resource -> PencilApp () Source #

Render Structure Source # 
Instance details

Defined in Pencil.Content

Render Page Source # 
Instance details

Defined in Pencil.Content

Methods

render :: Page -> PencilApp () Source #

Render r => Render [r] Source # 
Instance details

Defined in Pencil.Content

Methods

render :: [r] -> PencilApp () Source #

File paths and types

listDir Source #

Arguments

:: Bool

Recursive if True.

-> FilePath 
-> PencilApp [FilePath] 

Lists files in given directory. The file paths returned is prefixed with the given directory.

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.

toHtml :: FilePath -> FilePath Source #

Replaces the file path's extension with .html.

rename toHtml <$> load "about.htm"

toCss :: FilePath -> FilePath Source #

Replaces the file path's extension with .css.

rename toCss <$> load "style.sass"

toDir :: FilePath -> FilePath Source #

Converts a file path into a directory name, dropping the extension. Pages with a directory as its file path is rendered as an index file in that directory.

For example, pages/about.html is transformed into pages/about/, which upon render results in the destination file path pages/about/index.html:

toDir "pages/about.html"

Load and render as pages/about/:

render $ rename toDir <$> load "pages/about.html"

data FileType Source #

Enum for file types that can be parsed and converted by Pencil.

Instances
Eq FileType Source # 
Instance details

Defined in Pencil.Content.Internal

Generic FileType Source # 
Instance details

Defined in Pencil.Content.Internal

Associated Types

type Rep FileType :: Type -> Type #

Methods

from :: FileType -> Rep FileType x #

to :: Rep FileType x -> FileType #

Hashable FileType Source #

Hashable instance of FileType.

Instance details

Defined in Pencil.Content.Internal

Methods

hashWithSalt :: Int -> FileType -> Int #

hash :: FileType -> Int #

type Rep FileType Source # 
Instance details

Defined in Pencil.Content.Internal

type Rep FileType = D1 (MetaData "FileType" "Pencil.Content.Internal" "pencil-1.0.0-J6flYcnMNxZEYjuMQhPyoY" False) ((C1 (MetaCons "Html" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Markdown" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Css" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Sass" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Other" PrefixI False) (U1 :: Type -> Type))))

fileType :: FilePath -> FileType Source #

Takes a file path and returns the FileType, defaulting to Other if it's not a supported extension.

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"

class HasFilePath a where Source #

Class for types that has a final file path for rendering.

This allows file-path-changing methods to be re-used across Page, Structure and Resource types.