pencil-1.0.0: Static site generator

Safe HaskellNone
LanguageHaskell2010

Pencil.Content.Internal

Description

Internal implementation for functions that content.

Synopsis

Documentation

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.

Constructors

Page 

Fields

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

  • pageUseFilePath :: Bool

    Whether or not this Page's URL should be used as the final URL in the render.

  • pageEscapeXml :: Bool

    Whether or not XML/HTML tags should be escaped when rendered.

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 #

getPageEnv :: Page -> Env Source #

Gets the Env of a Page.

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

Sets the Env of a Page.

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

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.

Constructors

Structure 

Fields

data Node Source #

An inner element in the Structure. Either a singular Page, or a collection of Pages. The Text element is the variable name that the inner page's content is injected as. Defaults to "body".

Constructors

Node Text Page 
Nodes Text [Page] 

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

Constructors

Single Page 
Passthrough FilePath FilePath

in and out file paths (can be dir or files)

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 #

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 # 
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))))

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.

isDir :: FilePath -> Bool Source #

Returns True if the file path is a directory. Examples: foobar Examples of not directories: foo, foobar, foo/bar.baz

toHtml :: FilePath -> FilePath Source #

Replaces the file path's extension with .html.

rename toHtml <$> load "about.htm"

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"

toCss :: FilePath -> FilePath Source #

Replaces the file path's extension with .css.

rename toCss <$> load "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.

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"

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

Internal implemenation for move and to.

Moves the target file path to the specified FilePath. If the given FilePath is a directory, the file name is kept the same. If the FilePath is a file name, then fromFileName is used as the file name.

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.