scotty-hastache-0.2.1: Easy Mustache templating support for Scotty

Safe HaskellNone

Web.Scotty.Hastache

Contents

Description

Hastache templating for Scotty

{-# LANGUAGE OverloadedStrings #-}
module Main where

import Text.Hastache
import Web.Scotty.Trans as S
import Web.Scotty.Hastache

main :: IO ()
main = scottyH' 3000 $ do
  setTemplatesDir "templates"
  -- ^ Setting up the director with templates
  get "/:word" $ do
    beam <- param "word"
    setH "action" $ MuVariable (beam :: String)
    -- ^ "action" will be binded to the contents of 'beam'
    hastache "greet.html"

Given the following template:

<h1>Scotty, {{action}} me up!</h1>

Upon the GET /beam the result will be:

<h1>Scotty, beam me up!</h1>

Synopsis

Runners and types

scottyH :: ScottyError e => Port -> ScottyH e () -> IO ()Source

The runner to use instead of scotty

scottyHOpts :: ScottyError e => Options -> ScottyH e () -> IO ()Source

The runner to use instead of scottyOpts

type ScottyH e = ScottyT e HStateSource

A type synonym for ScottyT e HState; with custom exception types

type ActionH e = ActionT e HStateSource

A type synonym for ScottyT e HState; with custom exception types

Specialized types and runners

The DSL itself

Configuration

setHastacheConfig :: MuConfig IO -> ScottyH e ()Source

Update the Hastache configuration as whole

modifyHastacheConfig :: (MuConfig IO -> MuConfig IO) -> ScottyH e ()Source

Modify the Hastache configuration as whole

setTemplatesDir :: FilePath -> ScottyH e ()Source

Set the path to the directory with templates. This affects how both hastache and the {{> template}} bit searches for the template files.

setTemplateFileExt :: String -> ScottyH e ()Source

Set the default extension for template files. This affects how both hastache and the {{> template}} bit searches for the template files.

Actions

hastache :: ScottyError e => FilePath -> ActionH e ()Source

This is a function, just like html or text. It takes a name of the template (the path is computed using the information about the templates dir and template files extension) and renders it using Hastache.

The variables that have been initialized using setH are substituted for their values, uninitialized variables are considered to be empty/null.

setH :: ScottyError e => String -> MuType IO -> ActionH e ()Source

Set the value of a mustache variable.

Internals

type HState = StateT (MuConfig IO, Map String (MuType IO)) IOSource

State with the Hastache config