pencil-0.1.1: Static site generator

Safe HaskellNone
LanguageHaskell2010

Pencil.Internal.Pencil

Synopsis

Documentation

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.

data Config Source #

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.

Instances

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
 , configPandocWriterOptions = Text.Pandoc.def { Text.Pandoc.writerHighlight = True }
 , '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.

setEnv :: Env -> Config -> Config Source #

Sets the current environment. You may also want to look at withEnv if you want to render things in a modified environment.

updateEnv :: (Env -> Env) -> Config -> Config Source #

Update the Env inside the Config.

getSassOptions :: Config -> SassOptions Source #

The SassOptions for rendering Sass/Scss files.

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.

getDisplayValue :: Config -> Value -> Text Source #

The function that renders Value to text.

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 Values 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.

run :: PencilApp a -> Config -> IO () Source #

Run the Pencil app.

Note that this can throw a fatal exception.

mostSimilarFile :: FilePath -> PencilApp (Maybe FilePath) Source #

Given a file path, look at all file paths and find the one that seems most similar.

data PencilException Source #

Known Pencil errors that we know how to either recover from or quit gracefully.

Constructors

NotTextFile IOError

Failed to read a file as a text file.

FileNotFound (Maybe FilePath)

File not found. We may or may not know the file we were looking for.

VarNotInEnv Text FilePath

Variable is not in the environment. Variable name, and file where the variable was reference.

data FileType Source #

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

Constructors

Html 
Markdown 
Css 
Sass 
Other 

Instances

Eq FileType Source # 
Generic FileType Source # 

Associated Types

type Rep FileType :: * -> * #

Methods

from :: FileType -> Rep FileType x #

to :: Rep FileType x -> FileType #

Hashable FileType Source #

Hashable instance of FileType.

Methods

hashWithSalt :: Int -> FileType -> Int #

hash :: FileType -> Int #

type Rep FileType Source # 
type Rep FileType = D1 * (MetaData "FileType" "Pencil.Internal.Pencil" "pencil-0.1.1-1uSldPjknpJ3XhsyQP1vjM" 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 *)))))

fileTypeMap :: HashMap String FileType Source #

A HashMap of file extensions (e.g. markdown) to FileType.

extensionMap :: HashMap FileType String Source #

Mapping of FileType to the final converted format. Only contains FileTypes that Pencil will convert.

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"

fileType :: FilePath -> FileType Source #

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

data Page Source #

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.

Constructors

Page 

Fields

  • pageNodes :: [PNode]
     
  • pageEnv :: Env
     
  • pageFilePath :: FilePath

    The rendered output path of this page. Defaults to the input file path. This file path is used to generate the self URL that is injected into the environment.

Instances

getPageEnv :: Page -> Env Source #

Returns the Env from a Page.

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

Sets the Env in a Page.

apply :: Structure -> PencilApp Page Source #

Applies the environment variables on the given pages.

The Structure is expected to be ordered by inner-most content first (such that the final, HTML structure layout is last in the list).

The returned Page contains the Nodes of the fully rendered page, the fully-applied environment, and the URL of the last (inner-most) Page.

The variable application works by applying the outer environments down into the inner environments, until it hits the lowest environment, in which the page is rendered. Once done, this rendered content is saved as the ${body} variable for the parent structure, which is then applied, and so on.

As an example, there is the common scenario where we have a default layout (e.g. default.html), with the full HTML structure, but no body. It has only a ${body} template variable inside. This is the parent layout. There is a child layout, the partial called "blog-post.html", which has HTML for rendering a blog post, like usage of ${postTitle} and ${postDate}. Inside this, there is another child layout, the blog post content itself, which defines the variables postTitle and postDate, and may renderer parent variables such as websiteTitle.

+--------------+
|              | <--- default.html
|              |      Defines websiteTitle
|  +---------+ |
|  |         |<+----- blog-post.html
|  | +-----+ | |      Renders ${postTitle}, ${postDate}
|  | |     | | |
|  | |     | | |
|  | |     |<+-+----- blog-article-content.markdown
|  | |     | | |      Renders ${websiteTitle}
|  | +-----+ | |      Defines postTitle, postDate
|  +---------+ |
+--------------+

In this case, we want to accumulate the environment variables, starting from default.html, to blog-post.html, and the markdown file's variables. Combine all of that, then render the blog post content. This content is then injected into the parent's environment as a ${body} variable, for use in blog-post.html. Now that content is injected into the parent environment's ${body} variable, which is then used to render the full-blown HTML page.

apply_ :: Structure -> PencilApp Page Source #

Apply Structure and convert to Page.

It's simpler to implement if NonEmpty is ordered outer-structure first (e.g. HTML layout).

setVarNotInEnv :: FilePath -> PencilException -> PencilApp a Source #

Helper to inject a file path into a VarNotInEnv exception. Rethrow the exception afterwards.

loadTextFile :: FilePath -> PencilApp Text Source #

Loads the given file as a text file. Throws an exception into the ExceptT monad transformer if the file is not a text file.

toPencilException :: IOError -> Maybe PencilException Source #

Converts the IOError to a known PencilException.

How to test errors:

import Control.Exception
import qualified Data.Text.IO as TIO

(e -> print (ioe_description (e :: IOError)) >> return "") handle (TIO.readFile "foo")

isInvalidByteSequence :: IOError -> Bool Source #

Returns true if the IOError is an invalid byte sequence error. This suggests that the file is a binary file.

isNoSuchFile :: IOError -> Bool Source #

Returns true if the IOError is due to missing file.

parseAndConvertTextFiles :: FilePath -> PencilApp (Text, [PNode]) Source #

Loads and parses the given file path. Converts Markdown files to HTML, compiles Sass files into CSS, and leaves everything else alone.

evalNodes :: Env -> [PNode] -> PencilApp [PNode] Source #

Evaluate the nodes in the given environment. Note that it returns an IO because of ${partial(..)} calls that requires us to load a file.

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] 

Sort given Pages by the specified ordering function.

filterByVar Source #

Arguments

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

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, 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])].

loadResources Source #

Arguments

:: (FilePath -> FilePath) 
-> Bool

Recursive if True.

-> Bool

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

-> FilePath 
-> PencilApp [Resource] 

Loads file in given directory as Resources.

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.

merge :: Env -> Env -> Env Source #

Merges two Envs together, biased towards the left-hand Env on duplicates.

insertText Source #

Arguments

:: Text

Environment variable name.

-> Text

Text to insert.

-> Env

Environment to modify.

-> Env 

Insert text into the given Env.

env <- asks getEnv
insertText "title" "My Awesome Website" env

insertPages Source #

Arguments

:: Text

Environment variable name.

-> [Page]

Pages to insert.

-> Env

Environment to modify.

-> Env 

Insert Pages into the given Env.

posts <- loadBlogPosts "blog/"
env <- asks getEnv
insertPages "posts" posts env

updateEnvVal Source #

Arguments

:: (Value -> Value) 
-> Text

Environment variable name.

-> Env 
-> Env 

Modify a variable in the given environment.

insertEnv Source #

Arguments

:: Text

Environment variable name.

-> Value

Value to insert.

-> Env

Environment to modify.

-> Env 

Insert Value into the given Env.

maybeInsertIntoEnv :: Env -> Text -> Value -> Env Source #

Convert known Aeson types into known Env types.

aesonToEnv :: Object -> Env Source #

Converts an Aeson Object to an Env.

data Resource Source #

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

Constructors

Single Page 
Passthrough FilePath FilePath

in and out file paths

Instances

copyFile :: FilePath -> FilePath -> PencilApp () Source #

Copy file from source to output dir.

toHtml :: FilePath -> FilePath Source #

Replaces the file path's extension with .html.

load toHtml "about.markdown"

toDir :: FilePath -> FilePath Source #

Converts a file path into a directory name, dropping the extension. Pages with a directory as its FilePath is rendered as an index file in that directory. For example, the pages/about.html is transformed into pages/about/, which render would render the Page to the file path pages/about/index.html.

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/"

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

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

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"

findEnv :: [PNode] -> Env Source #

Find preamble node, and load as an Env. If no preamble is found, return a blank Env.

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 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 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 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.

Structures also control the closure of variables. Variables defined in a Pages 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 set the <title> tag.

In this way, Structure allows efficient Page reuse. See the private function apply to learn more about how Structures 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 Pages.

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)

structure :: Page -> Structure Source #

Converts a Page into a Structure.

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)

class Render a where Source #

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

Minimal complete definition

render

Methods

render :: a -> PencilApp () Source #

Renders a as web page(s).