mustache-2.1.4: A mustache template parser library.

Copyright(c) Justus Adam 2015
LicenseBSD3
Maintainerdev@justus.science
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Text.Mustache.Types

Contents

Description

 

Synopsis

Types for the Parser / Template

type ASTree α = [Node α] Source #

type STree = ASTree Text Source #

Syntax tree for a mustache template

data Node α Source #

Basic values composing the STree

data Template Source #

A compiled Template with metadata.

Constructors

Template 

type TemplateCache = HashMap String Template Source #

A collection of templates with quick access via their hashed names

Types for the Substitution / Data

type Key = Text Source #

Type of key used for retrieving data from Values

Converting

object :: [Pair] -> Value Source #

Convenience function for creating Object values.

This function is supposed to be used in conjuction with the ~> and ~= operators.

Examples

  data Address = Address { ... }

  instance Address ToJSON where
    ...

  data Person = Person { name :: String, address :: Address }

  instance ToMustache Person where
    toMustache (Person { name, address }) = object
      [ "name" ~> name
      , "address" ~= address
      ]

Here we can see that we can use the ~> operator for values that have themselves a ToMustache instance, or alternatively if they lack such an instance but provide an instance for the ToJSON typeclass we can use the ~= operator.

(~>) :: ToMustache ω => Text -> ω -> Pair infixr 8 Source #

Map keys to values that provide a ToMustache instance

Recommended in conjunction with the OverloadedStrings extension.

(↝) :: ToMustache ω => Text -> ω -> Pair infixr 8 Source #

Unicode version of ~>

(~=) :: ToJSON ι => Text -> ι -> Pair infixr 8 Source #

Map keys to values that provide a ToJSON instance

Recommended in conjunction with the OverloadedStrings extension.

(⥱) :: ToJSON ι => Text -> ι -> Pair infixr 8 Source #

Unicode version of ~=

class ToMustache ω where Source #

Conversion class

Minimal complete definition

toMustache

Methods

toMustache :: ω -> Value Source #

Instances

ToMustache Bool Source # 
ToMustache Char Source # 
ToMustache Double Source # 
ToMustache Float Source # 
ToMustache Int Source # 
ToMustache Integer Source # 
ToMustache () Source # 

Methods

toMustache :: () -> Value Source #

listToMustache :: [()] -> Value

ToMustache Scientific Source # 
ToMustache Text Source # 
ToMustache Value Source # 
ToMustache Text Source # 
ToMustache Value Source # 
ToMustache α => ToMustache [α] Source # 

Methods

toMustache :: [α] -> Value Source #

listToMustache :: [[α]] -> Value

ToMustache ω => ToMustache (Maybe ω) Source # 
ToMustache ω => ToMustache (Seq ω) Source # 

Methods

toMustache :: Seq ω -> Value Source #

listToMustache :: [Seq ω] -> Value

ToMustache ω => ToMustache (Set ω) Source # 

Methods

toMustache :: Set ω -> Value Source #

listToMustache :: [Set ω] -> Value

ToMustache ω => ToMustache (HashSet ω) Source # 
ToMustache ω => ToMustache (Vector ω) Source # 
ToMustache (Context Value -> STree -> String) Source # 
ToMustache (Context Value -> STree -> Text) Source # 
ToMustache (Context Value -> STree -> Text) Source # 
ToMustache (Context Value -> STree -> STree) Source # 
ToMustache (STree -> Text) Source # 
ToMustache (STree -> STree) Source # 
(ToMustache α, ToMustache β) => ToMustache (α, β) Source # 

Methods

toMustache :: (α, β) -> Value Source #

listToMustache :: [(α, β)] -> Value

ToMustache ω => ToMustache (HashMap String ω) Source # 
ToMustache ω => ToMustache (HashMap Text ω) Source # 
ToMustache ω => ToMustache (HashMap Text ω) Source # 
ToMustache ω => ToMustache (Map String ω) Source # 
ToMustache ω => ToMustache (Map Text ω) Source # 
ToMustache ω => ToMustache (Map Text ω) Source # 
(ToMustache α, ToMustache β, ToMustache γ) => ToMustache (α, β, γ) Source # 

Methods

toMustache :: (α, β, γ) -> Value Source #

listToMustache :: [(α, β, γ)] -> Value

(ToMustache α, ToMustache β, ToMustache γ, ToMustache δ) => ToMustache (α, β, γ, δ) Source # 

Methods

toMustache :: (α, β, γ, δ) -> Value Source #

listToMustache :: [(α, β, γ, δ)] -> Value

(ToMustache α, ToMustache β, ToMustache γ, ToMustache δ, ToMustache ε) => ToMustache (α, β, γ, δ, ε) Source # 

Methods

toMustache :: (α, β, γ, δ, ε) -> Value Source #

listToMustache :: [(α, β, γ, δ, ε)] -> Value

(ToMustache α, ToMustache β, ToMustache γ, ToMustache δ, ToMustache ε, ToMustache ζ) => ToMustache (α, β, γ, δ, ε, ζ) Source # 

Methods

toMustache :: (α, β, γ, δ, ε, ζ) -> Value Source #

listToMustache :: [(α, β, γ, δ, ε, ζ)] -> Value

(ToMustache α, ToMustache β, ToMustache γ, ToMustache δ, ToMustache ε, ToMustache ζ, ToMustache η) => ToMustache (α, β, γ, δ, ε, ζ, η) Source # 

Methods

toMustache :: (α, β, γ, δ, ε, ζ, η) -> Value Source #

listToMustache :: [(α, β, γ, δ, ε, ζ, η)] -> Value

(ToMustache α, ToMustache β, ToMustache γ, ToMustache δ, ToMustache ε, ToMustache ζ, ToMustache η, ToMustache θ) => ToMustache (α, β, γ, δ, ε, ζ, η, θ) Source # 

Methods

toMustache :: (α, β, γ, δ, ε, ζ, η, θ) -> Value Source #

listToMustache :: [(α, β, γ, δ, ε, ζ, η, θ)] -> Value

mFromJSON :: ToJSON ι => ι -> Value Source #

Converts a value that can be represented as JSON to a Value.

Representation

type Array = Vector Value Source #

A list-like structure used in Value

type Object = HashMap Text Value Source #

A map-like structure used in Value

type Pair = (Text, Value) Source #

Source type for constructing Objects

data Context α Source #

Representation of stateful context for the substitution process

Constructors

Context [α] α 

Instances

Orphan instances

Lift Text Source # 

Methods

lift :: Text -> Q Exp #